Hello Mat.
This is my code.
fortran openacc, using A100 gpu, nvhpc/22.11,
compile flags
ACC = -fast -acc -Minfo=accel -ta=tesla:cc80
My code
subroutine subroutine_name()
USE MODULES
IMPLICIT NONE
real*8, allocatable, dimension(:,:,:) :: ValueTMP
INTEGER*8 :: I,J,K,II,JJ,KK
allocate(ValueTMP(-1:n1sub+1,-1:n2sub+1,-1:n3sub+1))
ValueTMP= 1.d0
!$acc enter data copyin (ValueTMP(-1:n1sub+1,-1:n2sub+1,-1:n3sub+1))
!!! something
!$acc parallel loop collapse(3) present(ValueTMP(-1:n1sub+1,-1:n2sub+1,-1:n3sub+1), T(:,:,:,:))
do k = 1, n3sub-1
do j = 1, n2sub-1
do i = 1, n1sub-1
ValueTMP(i,j,k)=T(I,J,K,MS)
end do
end do
end do
!$acc end loop
call mpi_function1()
call mpi_function2()
!!! something
!$acc exit data delete (ValueTMP)
end subroutine subroutine_name
compile message
628, Generating enter data copyin(valuetmp(-1:n1sub+1,-1:n2sub+1,-1:n3sub+1))
631, Generating present(t(:,:,:,:),valuetmp(:,:,:))
error message
FATAL ERROR: variable in data clause is partially present on the device: name=valuetmp
file:/home/jsera.lee/lica/LICA/apply_openACC/src/mod_passivescalar.f90 rhs_ibm_ps line:628
Debug
valuetmp lives at 0x7ffedec6c000 size 54080000 partially present
Present table dump for device[1]: NVIDIA Tesla GPU 0, compute capability 8.0, threadid=1
host:0x78b130 device:0x7fffb3302200 size:128 presentcount:0+1 line:150 name:descriptor
.........
.........
host:0x7ffedb8d0df0 device:0x7ffed2000000 size:54080000 presentcount:0+1 line:1256 name:rhstmp
host:0x7ffedec6cbe0 device:0x7ffed6000000 size:54080000 presentcount:0+1 line:1256 name:valuetmp
host:0x7ffeeafff9d0 device:0x7ffee6000000 size:50331648 presentcount:0+1 line:125 name:nwall_dvm_sub
.........
.........
allocated block device:0x7fffb33e3c00 size:512 thread:1
deleted block device:0x7fffb33e4000 size:512 threadid=1
deleted block device:0x7fffb33e3e00 size:512 threadid=1
deleted block device:0x7fffb33e4400 size:512 threadid=1
deleted block device:0x7fffb33e4200 size:512 threadid=1
deleted block device:0x7fffb33e7a00 size:512 threadid=1
FATAL ERROR: variable in data clause is partially present on the device: name=valuetmp
file:/home/jsera.lee/lica/LICA/apply_openACC/src/mod_passivescalar.f90 rhs_ibm_ps line:628
line:628 means → “!$acc enter data copyin (ValueTMP(-1:n1sub+1,-1:n2sub+1,-1:n3sub+1))”
I wonder that is openACC can not use -1 start index?
I need negative index because of some MPI functions. It contains ghost cell communication.
I can’t understand why partially present message
cpu buffer size → allocate(ValueTMP(-1:n1sub+1,-1:n2sub+1,-1:n3sub+1))
gpu buffer size → !$acc enter data copyin (ValueTMP(-1:n1sub+1,-1:n2sub+1,-1:n3sub+1))
It looks like same array size to me
Is there anything i missing?