gcc/libgomp/testsuite/libgomp.oacc-fortran/lib-15.f90
Tobias Burnus 12fd2ec5ae libgomp/testsuite - use unique numbers with Fortran's 'stop'
PR fortran/92305
        * testsuite/libgomp.fortran/allocatable2.f90: Use
        unique numbers with 'stop'.
        * testsuite/libgomp.fortran/use_device_addr-1.f90: Ditto.
        * testsuite/libgomp.fortran/use_device_addr-2.f90: Ditto.
        * testsuite/libgomp.fortran/use_device_ptr-1.f90: Ditto.
        * testsuite/libgomp.oacc-fortran/lib-15.f90: Ditto.
        * testsuite/libgomp.oacc-fortran/pset-1.f90: Ditto.

From-SVN: r277769
2019-11-04 11:01:22 +01:00

53 lines
796 B
Fortran

! { dg-do run }
! { dg-skip-if "" { *-*-* } { "*" } { "-DACC_MEM_SHARED=0" } }
program main
use openacc
implicit none
integer, parameter :: N = 256
integer, allocatable :: h(:)
integer :: i
allocate (h(N))
do i = 1, N
h(i) = i
end do
call acc_copyin (h)
do i = 1, N
h(i) = i + i
end do
call acc_update_device (h, sizeof (h))
if (acc_is_present (h) .neqv. .TRUE.) stop 1
h(:) = 0
call acc_copyout (h, sizeof (h))
do i = 1, N
if (h(i) /= i + i) stop 2
end do
call acc_copyin (h, sizeof (h))
h(:) = 0
call acc_update_self (h, sizeof (h))
if (acc_is_present (h) .neqv. .TRUE.) stop 3
do i = 1, N
if (h(i) /= i + i) stop 4
end do
call acc_delete (h)
if (acc_is_present (h) .neqv. .FALSE.) stop 5
end program