How to use cudaMemset3D in Cuda Fortran?

Hello!
In Cuda Fortran: Cuda 11.4 pgfortran
we try to set int value=9 to a 3D arrary “idev” by cudaMemset3D.

However, after
error = cudaMalloc3D(devPtr, extent)
error =cudaMemset3D(devPtr, 9, extent)
devPtr%ptr is a pointer

THEN, we try to use
call c_f_pointer(devPtr%ptr, idev, ishap)
the value of the returned “idev” !=9
**
use cudafor
use iso_c_binding

  INTEGER,PARAMETER::m = 600
  INTEGER,PARAMETER::n = 300
  INTEGER,PARAMETER::p = 3

  integer,pointer,device :: idev(:,:,:)
  integer ishap(3)
  type(cudaPitchedPtr) :: devPtr
  type(cudaExtent) :: extent
  INTEGER::i,wz(m,n,p),error

  extent%width = m
  extent%height = n
  extent%depth = p

  error = cudaMalloc3D(devPtr, extent)
 
  ishap(1) = devPtr%pitch / 4
  ishap(2) = n
  ishap(3) = p

  call c_f_pointer(devPtr%ptr, idev, ishap)

  error = cudaMemset3D(devPtr, 9, extent)

  call c_f_pointer(devPtr%ptr, idev, ishap)

  wz=idev(1:m,1:n,1:p)

  write(*,*),'wz =',wz(1,1,:)

end program cublasTest
**

the code is compiled and executed without errors.
** pgfortran -acc -Mcuda -o a.out a.f90**
the results is:
wz = 151587081 151587081 151587081

Question ?:
How can i set idev=9 through cudaMemset3D IN FORTRAN.

Thank you for your help,

hwei

2 Likes

Welcome, hwei, to the forum!

I am not very familiar with Cuda programming, but the code you shared presumes that the memory on the GPU is directly available to the main program - the fact that you retrieve a Fortran array pointer from the Cuda-related derived type devPtr. Is it not necessary then to explicitly copy the data? Just a thought.

Thanks so much.

devPtr%ptr seems to be a C pointer. According to the answer, forums nvidia. c_f_pointer is necessary.
however it does work well in my program.

i just try to find a way to initialize 3D arrary idev=0, quicker than idev(:,:,:)=0.

or, what function should i use? when i have the C pointer devPtr%ptr (point to a valued 3D array). if Next i want to do idev(i,j,k)=idev(i,j,k)+i+2*j

hwei

Judging from the thread on the Cuda forum I think the procedure is correct. However, I can imagine that the order of the indices is not what you expect. The extent structure gives no clue as to whether the first index is the width or the depth. There might be a discrepancy here. Just thinking out loud, mind you!

thanks.
i found the reason yesterday. just the a mistake similar to that in cuda c. cudaMemset3D

In Nvidia cuda fortran declare that:

4.9.43. cudaMemset3D

integer function cudaMemset3D(pitchptr, value, cext)
type(cudaPitchedPtr) :: pitchptr
integer :: value
type(cudaExtent) :: cext
the value is integer in cudaMemset3D

However, with my pgfortran option, the value was read as byte in fact.
that is why i get 151587081,when i set value=9
just 151587081=16843009*9

in my program, value should be
value- Value to set for each byte of specified memory

so, we can only set value=0 with cudaMemset3D. here
or find the option in cuda fortran for integer value

hwei

Yes, I see that now in the documentation - the “value” argument is an int (integer in Fortran), but only the lower byte is used apparently. And indeed all bytes are set to that value.

thanks a lot.