gcc/libgomp/testsuite/libgomp.oacc-fortran/acc-memcpy-2.f90
Tobias Burnus 8b3f1edf9b OpenACC: Add Fortran routines acc_{alloc,free,hostptr,deviceptr,memcpy_{to,from}_device*}
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.
2024-02-27 17:30:38 +01:00

42 lines
805 B
Fortran

! { dg-do run }
! { dg-skip-if "" { *-*-* } { "*" } { "-DACC_MEM_SHARED=0" } }
! Fortran version of libgomp.oacc-c-c++-common/lib-95.c
program main
use iso_c_binding
use openacc
implicit none (type, external)
integer(c_size_t), parameter :: N = 127
integer(c_size_t) :: i
integer(acc_handle_kind) :: q = 5
integer(kind=1), allocatable :: h(:), g(:)
type(c_ptr) :: d
q = 5
allocate (h(-N:N), g(-N:N))
do i = -N, N
g(i) = i
end do
call acc_create_async (h, 2*N + 1, q)
call acc_memcpy_to_device_async (acc_deviceptr (h), g, 2*N + 1, q)
call acc_wait (q)
h = 0
call acc_update_self_async (h, 2*N + 1, q + 1)
call acc_delete_async (h, 2*N + 1, q + 1)
call acc_wait (q + 1)
do i = -N, N
if (h(i) /= i) &
stop 1
end do
deallocate (h, g)
end