aboutsummaryrefslogtreecommitdiff
path: root/libgomp/testsuite/libgomp.fortran/target-has-device-addr-2.f90
blob: a8d78a75af3afcb4a7c2ae5db05146ee821929de (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
program main
  use omp_lib
  use iso_c_binding
  implicit none

  integer, parameter :: N = 5
  integer :: i, x(N), y(N), z(N:2*N-1)
  target :: z

  x = 42
  y = 43
  z = 44

  call foo (x, y, z)
  if (any (x /= [(i, i = 1, N)])) stop 1
  if (any (y /= [(2*i, i = 1, N)])) stop 2
  if (any (z /= [(3*i, i = 1, N)])) stop 3

  contains
  subroutine foo(a, b, c)
    integer :: a(:)
    integer :: b(*)
    integer, pointer, intent(in) :: c(:)

    !$omp target data map(a,b(:N),c) use_device_addr(a,b(:N),c)
      !$omp target has_device_addr(A,B(:N),C)
        if (lbound(a,dim=1) /= 1 .or. ubound(a,dim=1) /= N) stop 10
        if (lbound(b,dim=1) /= 1) stop 11
        if (lbound(c,dim=1) /= N .or. ubound(c,dim=1) /= 2*N-1) stop 12
        if (any (a /= 42)) stop 13
        if (any (b(:N) /= 43)) stop 14
        if (any (c /= 44)) stop 15
        a = [(i, i=1, N)]
        b(:N) = [(2*i, i = 1, N)]
        c = [(3*i, i = 1, N)]
      !$omp end target
    !$omp end target data
  end subroutine foo

end program main