Add support for ARMv8-R architecture
[official-gcc.git] / libgomp / testsuite / libgomp.fortran / target8.f90
blob0564e90e08eac0c1004612381d37fa586c4ea5b7
1 ! { dg-do run }
3 integer, parameter :: n = 1000
4 integer, parameter :: c = 100
5 integer :: i, j
6 real :: a(n)
7 do i = 1, n
8 a(i) = i
9 end do
10 !$omp parallel
11 !$omp single
12 do i = 1, n, c
13 !$omp task shared(a)
14 !$omp target map(a(i:i+c-1))
15 !$omp parallel do
16 do j = i, i + c - 1
17 a(j) = foo (a(j))
18 end do
19 !$omp end target
20 !$omp end task
21 end do
22 !$omp end single
23 !$omp end parallel
24 do i = 1, n
25 if (a(i) /= i + 1) call abort
26 end do
27 contains
28 real function foo (x)
29 !$omp declare target
30 real, intent(in) :: x
31 foo = x + 1
32 end function foo
33 end