aboutsummaryrefslogtreecommitdiff
path: root/libgomp/testsuite/libgomp.fortran/target7.f90
blob: 73a7485a63830c8753b62207c090f878452e6de8 (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
! { dg-do run }

  interface
    real function foo (x)
      !$omp declare target
      real, intent(in) :: x
    end function foo
  end interface
  integer, parameter :: n = 1000
  integer, parameter :: c = 100
  integer :: i, j
  real :: a(n)
  do i = 1, n
    a(i) = i
  end do
  !$omp parallel
  !$omp single
  do i = 1, n, c
    !$omp task shared(a)
      !$omp target map(a(i:i+c-1))
        !$omp parallel do
          do j = i, i + c - 1
            a(j) = foo (a(j))
          end do
      !$omp end target
    !$omp end task
  end do
  !$omp end single
  !$omp end parallel
  do i = 1, n
    if (a(i) /= i + 1) stop 1
  end do
end
real function foo (x)
  !$omp declare target
  real, intent(in) :: x
  foo = x + 1
end function foo