How to let a(:)=b(:) without copying b to a?

Dear all,

A simple question, How to let a(:)=b(:) without copying b to a? You know I just want b equivalent with a, but I do not want copy b to a, so that I should have better performance.

I am asking this because I have my MPI module for MPI program. I also have my Non-MPI module which is for non-MPI program. My MPI program and non-MPI program are the same, the only difference is this MPI and non-MPI module. So the non-MPI module have exactly the same subroutines and the interfaces as the MPI module, it just mimic mpirun -n 1 case, without installing any version of MPI.

Eg, one of my mpi_gather subroutine,

   subroutine gatherr1d(r,rgather)
   real(kind=r8) :: r(:),rgather(:)
   integer :: ierror
   call mpi_gather(r,size(r),mpir8,rgather,size(r),mpir8,0, &
      mpi_comm_world,ierror)
   return
   end subroutine gatherr1d 

Its non-MPI version is,

   subroutine gatherr1d(r,rgather)
   real(kind=r8) :: r(:),rgather(:)
   integer :: ierror
   rgather=r
   return

However, it seems still need to copy r to rgather. From performance point of view, this may be not the most efficient. So I wonder, is there a way to let r and rgather are the same, you know so no need to copy r to rgather?
I know Fortran has something like equivalence, does that prevent array copying? But the latest standard seems make it obsolete?

Thank you very much in advance!

2 Likes

I tweeted about using a pointer or ASSOCIATE to do this, and the code is here

Tweets are listed by topic here. There are a few others about ASSOCIATE.

3 Likes

Thank you very much @Beliavsky , this is great!
I remember Dr. Fortran @sblionel taught me a similar trick,

program main
integer, pointer :: rank1_array (:)
integer, pointer :: rank4_array(:,:,:,:)
allocate (rank1_array(100))
rank1_array = [(i,i=1,100)]
print *, shape(rank1_array)
rank4_array(1:2,1:5,1:5,1:2) => rank1_array
print *, shape(rank4_array)
print *, rank4_array(2,1,5,1)
end

That is great, but here in this example, it may require me to change the property of my r and rgather array to pointer? which may require me to slightly change my code a little bit, which is fine actually.
Uhm, just a very stupid question, is there way that does not require to change the property of my r and rgather array? But anyway, I definitely can change their properties.

The variable that is pointed to does not need to be a pointer, but then it must have the target attribute:

program main
implicit none
integer :: i
integer, allocatable, target :: rank1_array(:)
integer, pointer :: rank4_array(:,:,:,:)
rank1_array = [(i,i=1,100)]
print *, shape(rank1_array)
rank4_array(1:2,1:5,1:5,1:2) => rank1_array
print *, shape(rank4_array)
print *, rank4_array(2,1,5,1)
end program main
2 Likes

Thank you @Beliavsky ! About your code, I have some small questions,

  1. What does the (a) mean in the below code? I mean what does the () of a do?
associate (e => (a)) ! e is a deep copy since (a) is expression
  1. I see there are two associate and two end associate,
associate (d => a)   ! d is a shallow copy
associate (e => (a)) ! e is a deep copy since (a) is expression
...
end associate ; end associate

Uhm, I mean, these two end associate, how do I know which one is to end associate (d => a), and which is to end associate (e => (a))?

() creates an expression.

End associate acts like end if.

1 Like

Expanding on what @themos wrote about () – code is here.

2 Likes

Could somebody comment/explain this pointer assignment? I can see it works (by compiling and running) but still I don’t quite understand how a rank-4 array pointer can point to a rank-1 array. Analogous snippet using real arrays, not pointers, clearly fails to compile:

program main
integer :: rank1_array (100)
integer :: rank4_array(5,5,5,5)
rank1_array = [(i,i=1,100)]
print *, shape(rank1_array)
rank4_array(1:2,1:5,1:5,1:2) = rank1_array
print *, shape(rank4_array)
print *, rank4_array(2,1,5,1)
end program main
$ gfortran-11 arrayrank.f90
arrayrank.f90:7:0:

    7 | rank4_array(1:2,1:5,1:5,1:2) = rank1_array
      |
Error: Incompatible ranks 4 and 1 in assignment at (1)
1 Like
rank4_array(1:2,1:5,1:5,1:2) => rank1_array

It is like reshape, but without memory copying I think, which is taught by Dr. Fortran @sblionel ,

real :: rank4_array(1:2,1:5,1:5,1:2)
rank4_array = reshape(rank1_array,shape(rank4_array))

However good explanation may need to left to someone who is much more advanced than me :slight_smile:

This is “pointer bounds remapping”. rank4_array is a pointer - the assignment causes it to point to the target of rank1_array, giving it the bounds specified. No data is moved.

3 Likes

Thanks for the explanation. I was not aware that array pointers can automatically reshape the target arrays. So it is something analogous to old days sending an array to a subprogram and having the dummy array a different shape as the actual one. Now done straight in the very same program unit.

1 Like