gcc/libgomp/testsuite/libgomp.fortran/reverse-offload-6.f90
Thomas Schwinge 7ab75a6e6d Fix 'libgomp.fortran/reverse-offload-6.f90' nvptx offloading compilation
Fix-up for recent commit 0b1ce70a81
"libgomp: Fix reverse offload issues".

	libgomp/
	* testsuite/libgomp.fortran/reverse-offload-6.f90: Fix nvptx
	offloading compilation.
2023-02-07 23:44:33 +01:00

34 lines
771 B
Fortran

!
! Ensure that a mapping with no argument works
!
! { dg-additional-options -foffload-options=nvptx-none=-misa=sm_35 { target offload_target_nvptx } }
module m
implicit none (type, external)
integer :: x = 32
integer :: dev_num2 = -1
contains
subroutine foo()
use omp_lib, only: omp_get_device_num
x = x + 10
dev_num2 = omp_get_device_num()
end
end module m
use m
use omp_lib
!$omp requires reverse_offload
implicit none (type, external)
integer :: dev_num = -1
!$omp target map(from:dev_num)
dev_num = omp_get_device_num()
! This calls GOMP_target_ext with number of maps = 0
!$omp target device(ancestor:1)
call foo
!$omp end target
!$omp end target
if (omp_get_num_devices() > 0 .and. dev_num2 == dev_num) stop 1
if (x /= 42) stop 2
end