Understanding gfortran's and Fortran's pass by reference nature

Hi all,
recently read this in the gfortran manual

GNU Fortran passes most arguments by reference, i.e. by passing a pointer to the data. Note that the compiler might use a temporary variable into which the actual argument has been copied, if required semantically (copy-in/copy-out).

Consider this module :

module addition
  use,intrinsic :: iso_fortran_env,only: real64
  implicit none
  private

  public :: add_two_numbers,add_two_numbers_using_pointers

contains

  pure function add_two_numbers(number1,number2) result(sum_of_two)
    real(kind=real64),intent(in) :: number1,number2
    real(kind=real64) :: sum_of_two

    sum_of_two = number1 + number2

  end function add_two_numbers

  pure function add_two_numbers_using_pointers(number1,number2) result(sum_of_two)
    real(kind=real64),pointer,intent(in) :: number1,number2
    real(kind=real64) :: sum_of_two

    sum_of_two = number1 + number2

  end function add_two_numbers_using_pointers

end module addition

and these two main programs
main without pointers :

program main
  use,intrinsic :: iso_fortran_env,only: real64
  use addition
  implicit none

  real(kind=real64) :: data1,data2

  write(unit=*,fmt="(a,1x)",advance="no") "Please enter two numbers:"
  read *, data1,data2
  print "(a,1x,f12.6)", "The sum is:",add_two_numbers(data1, data2)

end program main

main with pointers :

program main
  use,intrinsic :: iso_fortran_env,only: real64
  use addition
  implicit none

  real(kind=real64),target :: data1,data2

  write(unit=*,fmt="(a,1x)",advance="no") "Please enter two numbers:"
  read *, data1,data2
  print "(a,1x,f12.6)", "The sum is:",add_two_numbers_using_pointers(data1, data2)

end program main

  1. When I use valgrind on both the programs, they appear to use the same amount of memory. Why is that ?
  2. In which instances are variables fully copied and not just referenced ?
  3. When are pointers useful in Fortran ?

This is actually rather “Everything looks like arguments are passed by reference”. The standard doesn’t require compiler to pass by reference, it just requires that everything looks like that. Compilers are free to copy-in/copy-out all arguments.

  1. Why would you expect something else?
  2. Just looking at this code, you cannot tell. In both cases the compiler can pass the arguments by reference, but it is also free to pass them by copy-in/copy-out
  3. Since allocatables have been allowed in derived types and for dummy arguments, pointers are not often needed. Still there are some usages, e.g. linked lists.

Keep also in my that a Fortran pointer is a quite different thing than a C pointer.

1 Like

I was under the naive impression that pointers would help lower memory usage since they only contain the memory address and not the value itself.

Could I trouble you to explain the differences to me please, or give me a link. :pray:

First, as already pointed out, a fortran pointer is not simply an address. There is also rank, size, and bound information in the metadata.

Second, your statement might have been true when addresses were 16-bits and pointed to 32-bit or 64-bit data. On modern architectures, addresses are usually 64-bit entities, so the address itself often takes more memory than the data to which it points.

1 Like

@PierU and @RonShepard Thank you two for the answers.

Even if they were containing only an address, the actual values have to be actually stored. So at best the pointer version of the program requires the same amount of memory.

As previously written, a Fortran pointer contains the whole description of the pointed object, not only its address. In that sense, Fortran pointers are strongly typed. C pointers are also typed, but to a lesser extent (being essentially an address, a C pointer can be easily casted to any other pointer, whatever the type).

Another difference is that one can never access the address of a Fortran pointer: if you try to do so, you get the address of the pointed object. See this code (loc() is not a standard function, but in practice many compilers have it to get the address of an object):

integer, target :: a
integer, pointer :: b
b => a
write(*,*) loc(a), loc(b)

which outputs the same address for b and a:
4769164 4769164

The “equivalent” C code does output 2 different values:

    int a;
    int* b;
    b = &a;
    printf("%p %p\n",&a,&b);

output:

 0x7fffef5cf56c 0x7fffef5cf560
1 Like