Skip gnat.dg/prot7.adb on hppa.
[official-gcc.git] / libgomp / testsuite / libgomp.oacc-fortran / reduction-5.f90
blob88a691f7ca159c03abf2fc79f1316ee0ae854ef7
1 ! { dg-do run }
3 ! { dg-additional-options -Wuninitialized }
5 ! { dg-additional-options "-Wopenacc-parallelism" } for testing/documenting
6 ! aspects of that functionality.
8 ! subroutine reduction
10 program reduction
11 integer, parameter :: n = 40, c = 10
12 integer :: i, vsum, gs, ws, vs, cs, ns
14 call redsub_gang (gs, n, c)
15 call redsub_worker (ws, n, c)
16 call redsub_vector (vs, n, c)
17 call redsub_combined (cs, n, c)
18 call redsub_nested (ns, n, c)
20 vsum = 0
22 ! Verify the results
23 do i = 1, n
24 vsum = vsum + c
25 end do
27 if (gs .ne. vsum) STOP 1
28 if (ws .ne. vsum) STOP 2
29 if (vs .ne. vsum) STOP 3
30 if (cs .ne. vsum) STOP 4
31 if (ns .ne. vsum) STOP 5
32 end program reduction
34 subroutine redsub_gang(sum, n, c)
35 integer :: sum, n, c
37 sum = 0
39 !$acc parallel copyin (n, c) num_gangs(n) copy(sum)
40 !$acc loop reduction(+:sum) gang
41 ! { dg-bogus {'sum\.[0-9]+' is used uninitialized} TODO { xfail *-*-* } .-1 }
42 ! { dg-note {'sum\.[0-9]+' was declared here} {} { target *-*-* } .-2 }
43 do i = 1, n
44 sum = sum + c
45 end do
46 !$acc end parallel
47 end subroutine redsub_gang
49 subroutine redsub_worker(sum, n, c)
50 integer :: sum, n, c
52 sum = 0
54 !$acc parallel copyin (n, c) num_workers(4) vector_length (32) copy(sum)
55 ! { dg-warning "region is vector partitioned but does not contain vector partitioned code" "" { target *-*-* } .-1 }
56 !$acc loop reduction(+:sum) worker
57 ! { dg-bogus {'sum\.[0-9]+' is used uninitialized} TODO { xfail *-*-* } .-1 }
58 ! { dg-note {'sum\.[0-9]+' was declared here} {} { target *-*-* } .-2 }
59 do i = 1, n
60 sum = sum + c
61 end do
62 !$acc end parallel
63 end subroutine redsub_worker
65 subroutine redsub_vector(sum, n, c)
66 integer :: sum, n, c
68 sum = 0
70 !$acc parallel copyin (n, c) vector_length(32) copy(sum)
71 !$acc loop reduction(+:sum) vector
72 ! { dg-bogus {'sum\.[0-9]+' is used uninitialized} TODO { xfail *-*-* } .-1 }
73 ! { dg-note {'sum\.[0-9]+' was declared here} {} { target *-*-* } .-2 }
74 do i = 1, n
75 sum = sum + c
76 end do
77 !$acc end parallel
78 end subroutine redsub_vector
80 subroutine redsub_combined(sum, n, c)
81 integer :: sum, n, c
83 sum = 0
85 !$acc parallel num_gangs (8) num_workers (4) vector_length(32) copy(sum)
86 !$acc loop reduction(+:sum) gang worker vector
87 ! { dg-bogus {'sum\.[0-9]+' is used uninitialized} TODO { xfail *-*-* } .-1 }
88 ! { dg-note {'sum\.[0-9]+' was declared here} {} { target *-*-* } .-2 }
89 do i = 1, n
90 sum = sum + c
91 end do
92 !$acc end parallel
93 end subroutine redsub_combined
95 subroutine redsub_nested(sum, n, c)
96 integer :: sum, n, c
97 integer :: ii, jj
99 ii = n / 10;
100 jj = 10;
101 sum = 0
103 !$acc parallel num_gangs (8) copy(sum)
104 !$acc loop reduction(+:sum) gang
105 ! { dg-bogus {'sum\.[0-9]+' is used uninitialized} TODO { xfail *-*-* } .-1 }
106 ! { dg-note {'sum\.[0-9]+' was declared here} {} { target *-*-* } .-2 }
107 do i = 1, ii
108 !$acc loop reduction(+:sum) vector
109 ! { dg-bogus {'sum\.[0-9]+' may be used uninitialized} TODO { xfail { ! __OPTIMIZE__ } } .-1 }
110 ! { dg-note {'sum\.[0-9]+' was declared here} {} { target { ! __OPTIMIZE__ } } .-2 }
111 do j = 1, jj
112 sum = sum + c
113 end do
114 end do
115 !$acc end parallel
116 end subroutine redsub_nested