Allocation and pointer assignment should be done on the host side.
Fortran pointer assignment is not supported on the device. If you do need device pointer assignment, youāll need to switch to use Cray pointers (which are basically C pointers).
While allocation is supported on the device, itās not recommended given the device heap is small so a program can easily overflow the heap and it can hurt performance.
Also here, it would be illegal OpenACC. The device and host copies of an array in a data region need to match and an allocate will create both a host and device copy.
Now you can use the pointer in device code, but do need to āattachā it so itās pointing at the correct device address.
Something like the following:
% cat test2.f90
MODULE DMP_mf_pointers
!This module replaces automatic arrays with pointers for the GPU
IMPLICIT NONE
REAL, DIMENSION(:,:,:,:), ALLOCATABLE, TARGET :: UPCHEMI
REAL, DIMENSION(:,:,:) , POINTER :: UPCHEM
!$acc declare create( UPCHEMI )
!$acc declare create( UPCHEM )
CONTAINS
SUBROUTINE allocate_DMP_mf_pointers(KTS,KTE,NUP,nchem,ITS,ITE)
INTEGER, INTENT(IN) :: KTS,KTE,NUP,nchem,ITS,ITE
! OpenACC allocates both the host and device copies of the array
! when the array is in a declare create directive
ALLOCATE ( UPCHEMI (KTS:KTE+1,1:NUP,1:nchem,ITS:ITE) )
END SUBROUTINE allocate_DMP_mf_pointers
SUBROUTINE set_DMP_mf_pointers(index)
INTEGER,INTENT(in) :: index
UPCHEM => UPCHEMI (:,:,:,index)
! Update the device pointer to point at the correct UPCHEMI index
!$acc enter data attach(UPCHEM)
END SUBROUTINE set_DMP_mf_pointers
END MODULE DMP_mf_pointers
program foo
use DMP_mf_pointers
integer :: KTS,KTE,NUP,nchem,ITS,ITE,idx,i,j,k
KTS=1
KTE=64
NUP=64
nchem=64
ITS=1
ITE=64
call allocate_DMP_mf_pointers(KTS,KTE,NUP,nchem,ITS,ITE)
do idx = ITS,ITE
call set_DMP_mf_pointers(idx)
!$acc parallel loop collapse(3) present(UPCHEM)
do i=KTS,KTE
do j=1,NUP
do k=1,nchem
UPCHEM(i,j,k) = 1
enddo
enddo
enddo
enddo
!$acc update self(UPCHEMI)
print *, UPCHEMI(1,1,1,1)
end program
% nvfortran test2.f90 -acc -Minfo=accel; a.out
set_dmp_mf_pointers:
24, Generating enter data attach(upchem)
foo:
45, Generating NVIDIA GPU code
46, !$acc loop gang, vector(128) collapse(3) ! blockidx%x threadidx%x
47, ! blockidx%x threadidx%x collapsed
48, ! blockidx%x threadidx%x collapsed
54, Generating update self(upchemi(:,:,:,:))
1.000000