Pass by reference

Does Fortran standard require function/subroutine arguments to be passed by reference?

If you mean how do you pass by value, see the VALUE attribute. The following program will print “10,2”.

program passbyvalue
implicit none
real :: a,b
   a=1
   b=2
   call pass(a,b)
   write(*,*)'A=',a,'B=',b
contains
subroutine pass(a,b)
real :: a
real,value :: b
   a=10
   b=20
end subroutine pass
end program passbyvalue
! 5.3.18     VALUE attribute
! The VALUE attribute specifies a type of argument association (12.5.2.4) for a dummy argument.
! C556     An entity with the VALUE attribute shall be a scalar dummy data object.
! C557     An entity with the VALUE attribute shall not have the ALLOCATABLE, INTENT (INOUT), INTENT
!          (OUT), POINTER, or VOLATILE attributes.
! C558     If an entity has the VALUE attribute, any length type parameter value in its declaration shall be omitted
!          or specified by an initialization expression.
! If the actual argument is a coindexed object with an allocatable ultimate component, the dummy argument shall
! have the INTENT (IN) or the VALUE attribute.
! NOTE 12.23
!      If the actual argument is a coindexed object, a processor that uses distributed memory might create a copy
!      on the executing image of the actual argument, including copies of any allocated allocatable subcomponents,
!      and associate the dummy argument with that copy. If necessary, on return from the procedure, the value
!      of the copy would be copied back to the actual argument.

Under what conditions is it “No”

J3/22-007r1(Draft Fortran 2023)
15.5.2.4 Argument association
NOTE 2
Fortran argument association is usually similar to call by reference and call by value-result. If the VALUE attribute is specified, the effect is as if the actual argument were assigned to a temporary variable, and that variable were then argument associated with the dummy argument. Subsequent changes to the value or definition status of the dummy argument do not affect the actual argument. The actual mechanism by which this happens is determined by the processor.

This question sort of came up recently in something I’m working on, but the gist of it is (and I’m about to go read the standard very carefully to confirm), copy-in/copy-out would be a perfectly standards conforming approach. There is nothing standards conforming that can be done to observe any difference between pass-by-reference and copy-in/copy-out. I.e. aliasing of arguments is not standards conforming, so any reference to the actual argument not made through the dummy argument would not be valid until the completion of execution of the procedure. For example

program demonstrate
  integer :: x

  x = 42
  print *, "x is: ", x
  call try_it(x)
  print *, "x is: ", x
contains
  subroutine try_it(y)
    integer :: y

    print *, "y is: ", y
    ! this is not allowed when y is associated with x
    ! print *, "x is: ", x
    y = 24
    print *, "y is: ", y
    ! this is not allowed when y is associated with x
    ! print *, "x is: ", x
  end subroutine
end program
2 Likes

There are many situations involving actual arguments that are array strides or arrays with vector subscripts that must invoke the equivalent of copy-in/copy-out in order to be associated with the dummy argument. This sometimes hurts performance, and it sometimes helps performance.

2 Likes

In conjunction with this, concerned readers may want to note the standard mostly places the onus on the programmers and it does not include any numbered constraints and like for the processors to detect and report any nonconformance. Thus coders paying close attention to sections such as “Restrictions on entities associated with dummy arguments” (section 15.5.2.14 in 22-007r1 document toward Fortran 2023) can prove helpful.

A really silly, egregious variant of the shown code will be

  integer, allocatable :: x
  x = 42
  call try_it( x )
contains
  subroutine try_it( a )
    integer, allocatable, intent(out) :: a
    print *, "x = ", x
    a = 1
  end subroutine
end program

where a processor can technically do anything with the program (even fry your computer as the argument goes!) but not be required to warn you about it! - see below:

  • gfortran
C:\temp>gfortran p.f90 -Wall -o p.exe

C:\temp>p.exe
 x =            0
  • Intel Fortran
C:\temp>ifx /standard-semantics /warn:all p.f90
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2023.0.0 Build 20221201
Copyright (C) 1985-2022 Intel Corporation. All rights reserved.

Microsoft (R) Incremental Linker Version 14.34.31937.0
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:p.exe
-subsystem:console
p.obj

C:\temp>p.exe
forrtl: severe (157): Program Exception - access violation
Image              PC                Routine            Line        Source
p.exe              00007FF785BD10DD  Unknown               Unknown  Unknown
p.exe              00007FF785BDC3BE  Unknown               Unknown  Unknown
p.exe              00007FF785C23230  Unknown               Unknown  Unknown
KERNEL32.DLL       00007FFDBDE97614  Unknown               Unknown  Unknown
ntdll.dll          00007FFDBFCE26A1  Unknown               Unknown  Unknown

C:\temp>

Of course, implicit none and disciplined use of import statements can help in certain circumstances.

  implicit none
  integer, allocatable :: x
  x = 42
  call try_it( x )
contains
  subroutine try_it( a )
    import, none  !<-- Fortran 2018 feature not supported yet by some compilers
    integer, allocatable, intent(out) :: a
    print *, "x = ", x
    a = 1
  end subroutine
end program

This is what NAG does:

$ nagfor xxx.f90 && a.out
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7114
[NAG Fortran Compiler normal termination]
Segmentation fault: 11

If the nonconforming code runs at all, then there are three outputs that a programmer might expect:

x = 42
x = 0
x = 1

Which one is observed just depends on when during the execution sequence the intent(out) argument is allocated, which order the two seemingly independent statements are executed, and whether copy-in/copy-out (or just copy-out, in this case more like a move_alloc) is invoked to associate the arguments.

As for the pass-by-reference aspect, I would think this is the most likely argument association in this case because of the allocatable attribute of the argument. If that is removed, then both nag and gfortran print “x = 42”, suggesting a simple pass-by-reference argument association where the illegal argument alias is undetected.

Is that correct? I thought if the aliased argument was modified, and it was even referenced through some other alias, it was nonconforming?

That’s the point. And one can say that from the developer point of view everything behaves as if the arguments were always passed by reference (unless “value” is specified, of course).

In the spirit of full information, it has been pointed out to me that there is one nuanced situation where this is not strictly true.

If the dummy argument has the TARGET attribute, does not have the VALUE attribute, and either the effective argument is simply contiguous or the dummy argument is scalar, assumed-rank, or assumed-shape, and does not have the CONTIGUOUS attribute, and the effective argument has the TARGET attribute but is not a coindexed object or an array section with a vector subscript then

  • any pointers associated with the effective argument become associated with the corresponding dummy argument on invocation of the procedure, and
  • when execution of the procedure completes, any pointers that do not become undefined (19.5.2.5) and are associated with the dummy argument remain associated with the effective argument.

Example

   real, target :: x
   real, pointer :: p
   x = 123
   call sub(x)
   p = 234
   print *, x ! 234
contains
   subroutine sub(y)
     real, target :: y
     p => y
   end
end

The above statement does hold in all other cases though.

Others have pointed out some corner cases where this is not true. Another such situation is with the standard conforming c_loc() function. You can obtain and print the address of the actual and the dummy arguments, and if they are different, then you can know that some kind of copy-in/copy-out is occurring, and if they are the same, then you can know that the compiler is associating the arguments through their address. Of course the value of that function is not defined by the standard, but the behavior and the use of the function itself is standard conforming (provided the arguments are interoperable, etc.).

So with c_loc in the discussion mix, the interoperability with a C companion processor means one can be further malicious and indulge in obfuscation by working with C-style void * opaque pointer parameters without dealing with squiggly bracket scopes i.e., with all Fortran code! The standard is somewhat weak on indicating to the coder to not reference the actual argument but the spirit of above-mentioned requirement applies. The coders should take care to avoid the pitfalls even as the processors are not required to detect and report anything, here’s another egregious variant of the trouble case mentioned earlier:

   use, intrinsic :: iso_c_binding, only : c_int, c_ptr, c_loc, c_f_pointer
   integer(c_int), allocatable, target :: x
   allocate( x )
   call sub( c_loc(x) )
   print *, "x = ", x
contains
   subroutine sub( cp )
      type(c_ptr), intent(in), value :: cp !<-- !! pass-by-reference semantics via passing the pointer by value!
      integer(c_int), pointer :: px
      deallocate( x )  !<-- hmmm.. 
      call c_f_pointer( cptr=cp, fptr=px )
      px = 42
   end subroutine 
end 
  • gfortran - no compile-time diagnostics available and unsurprising segmentation fault at run-time
C:\temp>gfortran -Wall p.f90 -o p.exe

C:\temp>p.exe

Program received signal SIGSEGV: Segmentation fault - invalid memory reference.

Backtrace for this error:

C:\temp>
  • Intel Fortran - same, run-time exception only
C:\temp>ifx /standard-semantics p.f90
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2023.0.0 Build 20221201
Copyright (C) 1985-2022 Intel Corporation. All rights reserved.

Microsoft (R) Incremental Linker Version 14.34.31937.0
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:p.exe
-subsystem:console
p.obj

C:\temp>p.exe
forrtl: severe (157): Program Exception - access violation
Image              PC                Routine            Line        Source
p.exe              00007FF7BD1610DA  Unknown               Unknown  Unknown
p.exe              00007FF7BD16CC6E  Unknown               Unknown  Unknown
p.exe              00007FF7BD1B3AB0  Unknown               Unknown  Unknown
KERNEL32.DLL       00007FFDBDE97614  Unknown               Unknown  Unknown
ntdll.dll          00007FFDBFCE26A1  Unknown               Unknown  Unknown