Now in the context of working with large data like with OP or the use cases of yore with the legacy nonstandard codebases that used dialects of FORTRAN 77
(and 66
) which usually then lead to shared data (MODULE entity
s or COMMON
blocks), note the message implied in some posts here as TRANSFER
being equivalent (bad pun intended) to EQUIVALENCE
is inaccurate.
This is because EQUIVALENCE
semantics pointed Fortran processors toward shared memory and a rough equivalent of union
data type kind of semantics in C and its offshoots. I don’t think this is possible with TRANSFER
. Consider a silly example:
module m
use, intrinsic :: iso_c_binding, only : c_intptr_t
private
integer, parameter :: n = 2
integer, save :: a(2*n) = 0
double precision, save :: x(n)
equivalence ( a, x )
public :: set_x, consume_x
contains
subroutine set_x( vals )
double precision, intent(in) :: vals(:)
x = vals
end subroutine
subroutine consume_x()
integer(c_intptr_t) :: add_a, add_x
add_a = transfer( source=loc(a), mold=add_a )
add_x = transfer( source=loc(x), mold=add_x )
print *, "m::x = ", x
print "(g0,z0)", "Address of data store 'a' (in hex): ", add_a
print "(g0,z0)", "Address of data store 'x' (in hex): ", add_x
end subroutine
end module
use m
call set_x( [ 1D0, 2D0 ] )
call consume_x()
end
With gfortran
, see how the EQUIVALENCE
data objects share the same memory address:
C:\temp>gfortran p.f90 -o p.exe
C:\temp>p.exe
m::x = 1.0000000000000000 2.0000000000000000
Address of data store 'a' (in hex): 7FF702EAD040
Address of data store 'x' (in hex): 7FF702EAD040
C:\temp>
The equivalent of the above with TRANSFER
shall be:
module m
use, intrinsic :: iso_c_binding, only : c_intptr_t
private
integer, parameter :: n = 2
integer, save :: a(2*n) = 0
double precision, save :: x(n)
public :: init_x, set_x, consume_x
contains
subroutine init_x()
x = transfer( source=a, mold=x )
end subroutine
subroutine set_x( vals )
double precision, intent(in) :: vals(:)
x = vals
end subroutine
subroutine consume_x()
integer(c_intptr_t) :: add_a, add_x
add_a = transfer( source=loc(a), mold=add_a )
add_x = transfer( source=loc(x), mold=add_x )
print *, "m::x = ", x
print "(g0,z0)", "Address of data store 'a' (in hex): ", add_a
print "(g0,z0)", "Address of data store 'x' (in hex): ", add_x
end subroutine
end module
use m
call init_x()
call set_x( [ 1D0, 2D0 ] )
call consume_x()
end
which with gfortran
will give:
C:\temp>gfortran p.f90 -o p.exe
C:\temp>p.exe
m::x = 1.0000000000000000 2.0000000000000000
Address of data store 'a' (in hex): 7FF692D4E040
Address of data store 'x' (in hex): 7FF692D4E050
C:\temp>