Fix gcc.c-torture/execute/ieee/cdivchkf.c on hpux
[official-gcc.git] / libgomp / testsuite / libgomp.fortran / target-has-device-addr-2.f90
bloba8d78a75af3afcb4a7c2ae5db05146ee821929de
1 program main
2 use omp_lib
3 use iso_c_binding
4 implicit none
6 integer, parameter :: N = 5
7 integer :: i, x(N), y(N), z(N:2*N-1)
8 target :: z
10 x = 42
11 y = 43
12 z = 44
14 call foo (x, y, z)
15 if (any (x /= [(i, i = 1, N)])) stop 1
16 if (any (y /= [(2*i, i = 1, N)])) stop 2
17 if (any (z /= [(3*i, i = 1, N)])) stop 3
19 contains
20 subroutine foo(a, b, c)
21 integer :: a(:)
22 integer :: b(*)
23 integer, pointer, intent(in) :: c(:)
25 !$omp target data map(a,b(:N),c) use_device_addr(a,b(:N),c)
26 !$omp target has_device_addr(A,B(:N),C)
27 if (lbound(a,dim=1) /= 1 .or. ubound(a,dim=1) /= N) stop 10
28 if (lbound(b,dim=1) /= 1) stop 11
29 if (lbound(c,dim=1) /= N .or. ubound(c,dim=1) /= 2*N-1) stop 12
30 if (any (a /= 42)) stop 13
31 if (any (b(:N) /= 43)) stop 14
32 if (any (c /= 44)) stop 15
33 a = [(i, i=1, N)]
34 b(:N) = [(2*i, i = 1, N)]
35 c = [(3*i, i = 1, N)]
36 !$omp end target
37 !$omp end target data
38 end subroutine foo
40 end program main