RISC-V: Bugfix vfmv insn honor zvfhmin for FP16 SEW [PR115763]
[official-gcc.git] / libgomp / testsuite / libgomp.oacc-fortran / parallel-reduction.f90
bloba7b7adebb09e3ac8b0ccc7230f0ec7a8f04edb55
1 ! { dg-do run }
3 ! { dg-additional-options -Wuninitialized }
5 ! { dg-additional-options "-Wopenacc-parallelism" } for testing/documenting
6 ! aspects of that functionality.
8 program reduction
9 implicit none
10 integer, parameter :: n = 10
11 integer s1, s2
12 include "openacc_lib.h"
14 s1 = 0
15 s2 = 0
17 !$acc parallel reduction(+:s1,s2) num_gangs (n) copy(s1)
18 ! { dg-bogus "\[Ww\]arning: region is gang partitioned but does not contain gang partitioned code" "TODO 'reduction'" { xfail *-*-* } .-1 }
19 s1 = s1 + 1
20 s2 = s2 + 1
21 !$acc end parallel
23 if (acc_get_device_type () .ne. acc_device_host) then
24 if (s1 .ne. n) STOP 1
25 if (s2 .ne. n) STOP 2
26 else
27 if (s1 .ne. 1) STOP 3
28 if (s2 .ne. 1) STOP 4
29 end if
31 ! Test reductions inside subroutines
33 s1 = 0
34 s2 = 0
35 call redsub (s1, s2, n)
37 if (acc_get_device_type () .ne. acc_device_host) then
38 if (s1 .ne. n) STOP 5
39 else
40 if (s2 .ne. 1) STOP 6
41 end if
42 end program reduction
44 subroutine redsub(s1, s2, n)
45 implicit none
46 integer :: s1, s2, n
48 !$acc parallel reduction(+:s1,s2) num_gangs (10) copy(s1)
49 ! { dg-bogus {'s1\.[0-9]+' is used uninitialized} TODO { xfail *-*-* } .-1 }
50 ! { dg-note {'s1\.[0-9]+' was declared here} {} { target *-*-* } .-2 }
51 ! { dg-bogus {'s2\.[0-9]+' is used uninitialized} TODO { xfail *-*-* } .-3 }
52 ! { dg-note {'s2\.[0-9]+' was declared here} {} { target *-*-* } .-4 }
53 ! { dg-bogus "\[Ww\]arning: region is gang partitioned but does not contain gang partitioned code" "TODO 'reduction'" { xfail *-*-* } .-5 }
54 s1 = s1 + 1
55 s2 = s2 + 1
56 !$acc end parallel
57 end subroutine redsub