
These routines map simply to the C counterpart and are meanwhile defined in OpenACC 3.3. (There are additional routine changes, including the Fortran addition of acc_attach/acc_detach, that require more work than a simple addition of an interface and are therefore excluded.) libgomp/ChangeLog: * libgomp.texi (OpenACC Runtime Library Routines): Document new 3.3 routines that simply map to their C counterpart. * openacc.f90 (openacc): Add them. * openacc_lib.h: Likewise. * testsuite/libgomp.oacc-fortran/acc_host_device_ptr.f90: New test. * testsuite/libgomp.oacc-fortran/acc-memcpy.f90: New test. * testsuite/libgomp.oacc-fortran/acc-memcpy-2.f90: New test. * testsuite/libgomp.oacc-c-c++-common/lib-59.c: Crossref to f90 test. * testsuite/libgomp.oacc-c-c++-common/lib-60.c: Likewise. * testsuite/libgomp.oacc-c-c++-common/lib-95.c: Likewise.
43 lines
1.1 KiB
Fortran
43 lines
1.1 KiB
Fortran
! { dg-do run }
|
|
! { dg-skip-if "" { *-*-* } { "*" } { "-DACC_MEM_SHARED=0" } }
|
|
|
|
! Fortran version of libgomp.oacc-c-c++-common/lib-59.c
|
|
|
|
program main
|
|
use iso_c_binding
|
|
use openacc
|
|
implicit none (type, external)
|
|
|
|
integer(c_size_t), parameter :: N = 256
|
|
character(c_char), allocatable, target :: h_data(:)
|
|
type(c_ptr) :: dptr, dptr_t
|
|
integer(c_intptr_t) :: iptr, i
|
|
|
|
allocate(h_data(0:N))
|
|
dptr = acc_malloc (N+1)
|
|
|
|
call acc_map_data (h_data, dptr, N+1)
|
|
|
|
! The following assumes sizeof(void*) being the same on host and device:
|
|
do i = 0, N
|
|
dptr_t = transfer (transfer(dptr, iptr) + i, dptr_t)
|
|
if (.not. c_associated (acc_hostptr (dptr_t), c_loc (h_data(i)))) &
|
|
stop 1
|
|
if (.not. c_associated (dptr_t, acc_deviceptr (h_data(i)))) &
|
|
stop 2
|
|
end do
|
|
|
|
call acc_unmap_data (h_data)
|
|
|
|
do i = 0, N
|
|
dptr_t = transfer (transfer(dptr, iptr) + i, dptr_t)
|
|
if (c_associated (acc_hostptr (dptr_t))) &
|
|
stop 3
|
|
if (c_associated (acc_deviceptr (h_data(i)))) &
|
|
stop 4
|
|
end do
|
|
|
|
call acc_free (dptr)
|
|
|
|
deallocate (h_data)
|
|
end
|