Skip gnat.dg/prot7.adb on hppa.
[official-gcc.git] / libgomp / testsuite / libgomp.oacc-fortran / optional-reduction.f90
blob0bb05b9b869d9d4f2dbaaceabb7ffdc1f76e7ac6
1 ! Test optional arguments in reduction clauses. The effect of
2 ! non-present arguments in reduction clauses is undefined, and is not tested
3 ! for. The tests are based on those in reduction-1.f90.
5 ! { dg-do run }
7 ! { dg-additional-options -Wuninitialized }
9 !TODO
10 ! { dg-xfail-run-if TODO { openacc_radeon_accel_selected && { ! __OPTIMIZE__ } } }
12 program optional_reduction
13 implicit none
15 integer :: rg, rw, rv, rc
17 rg = 0
18 rw = 0
19 rv = 0
20 rc = 0
22 call do_test(rg, rw, rv, rc)
23 contains
24 subroutine do_test(rg, rw, rv, rc)
25 integer, parameter :: n = 10, ng = 8, nw = 4, vl = 32
26 integer, optional :: rg, rw, rv, rc
27 integer :: i, vresult
28 integer, dimension (n) :: array
30 vresult = 0
31 do i = 1, n
32 array(i) = i
33 end do
35 !$acc parallel num_gangs(ng) copy(rg)
36 !$acc loop reduction(+:rg) gang
37 ! { dg-bogus {'rg\.[0-9]+' is used uninitialized} TODO { xfail *-*-* } .-1 }
38 ! { dg-note {'rg\.[0-9]+' was declared here} {} { target *-*-* } .-2 }
39 do i = 1, n
40 rg = rg + array(i)
41 end do
42 !$acc end parallel
44 !$acc parallel num_workers(nw) copy(rw)
45 !$acc loop reduction(+:rw) worker
46 ! { dg-bogus {'rw\.[0-9]+' is used uninitialized} TODO { xfail *-*-* } .-1 }
47 ! { dg-note {'rw\.[0-9]+' was declared here} {} { target *-*-* } .-2 }
48 do i = 1, n
49 rw = rw + array(i)
50 end do
51 !$acc end parallel
53 !$acc parallel vector_length(vl) copy(rv)
54 !$acc loop reduction(+:rv) vector
55 ! { dg-bogus {'rv\.[0-9]+' is used uninitialized} TODO { xfail *-*-* } .-1 }
56 ! { dg-note {'rv\.[0-9]+' was declared here} {} { target *-*-* } .-2 }
57 do i = 1, n
58 rv = rv + array(i)
59 end do
60 !$acc end parallel
62 !$acc parallel num_gangs(ng) num_workers(nw) vector_length(vl) copy(rc)
63 !$acc loop reduction(+:rc) gang worker vector
64 ! { dg-bogus {'rc\.[0-9]+' is used uninitialized} TODO { xfail *-*-* } .-1 }
65 ! { dg-note {'rc\.[0-9]+' was declared here} {} { target *-*-* } .-2 }
66 do i = 1, n
67 rc = rc + array(i)
68 end do
69 !$acc end parallel
71 ! Verify the results
72 do i = 1, n
73 vresult = vresult + array(i)
74 end do
76 if (rg .ne. vresult) STOP 1
77 if (rw .ne. vresult) STOP 2
78 if (rv .ne. vresult) STOP 3
79 if (rc .ne. vresult) STOP 4
80 end subroutine do_test
81 end program optional_reduction