Add support for ARMv8-R architecture
[official-gcc.git] / libgomp / testsuite / libgomp.fortran / examples-4 / teams-3.f90
blob9de77afd7d2abf659ac54895632764f98914ccc6
1 ! { dg-do run }
3 function dotprod_ref (B, C, N) result (sum)
4 implicit none
5 real :: B(N), C(N), sum
6 integer :: N, i
7 sum = 0.0e0
8 do i = 1, N
9 sum = sum + B(i) * C(i)
10 end do
11 end function
13 function dotprod (B, C, N) result(sum)
14 real :: B(N), C(N), sum
15 integer :: N, i
16 sum = 0.0e0
17 !$omp target teams map(to: B, C) map(tofrom: sum) &
18 !$omp& reduction(+:sum)
19 !$omp distribute parallel do reduction(+:sum)
20 do i = 1, N
21 sum = sum + B(i) * C(i)
22 end do
23 !$omp end target teams
24 end function
26 subroutine init (B, C, N)
27 real :: B(N), C(N)
28 integer :: N, i
29 do i = 1, N
30 B(i) = 0.0001 * i
31 C(i) = 0.000001 * i * i
32 end do
33 end subroutine
35 subroutine check (a, b)
36 real :: a, b, err
37 real, parameter :: EPS = 0.0001
38 if (b == 0.0) then
39 err = a
40 else if (a == 0.0) then
41 err = b
42 else
43 err = (a - b) / b
44 end if
45 if (err > EPS .or. err < -EPS) call abort
46 end subroutine
48 program e_54_3
49 integer :: n
50 real :: ref, d
51 real, pointer, dimension(:) :: B, C
52 n = 1024 * 1024
53 allocate (B(n), C(n))
54 call init (B, C, n)
55 ref = dotprod_ref (B, C, n)
56 d = dotprod (B, C, n)
57 call check (ref, d)
58 deallocate (B, C)
59 end program