1 ! RUN: %python %S/../test_errors.py %s %flang -fopenacc
3 ! Check OpenACC clause validity for the following construct and directive:
6 program openacc_serial_loop_validity
11 integer, parameter :: N
= 256
12 integer, dimension(N
) :: c
13 logical, dimension(N
) :: d
, e
15 integer :: wait1
, wait2
17 logical :: reduction_l
18 logical :: ifCondition
= .TRUE
.
19 real(8), dimension(N
) :: a
22 !$acc serial loop reduction(+: reduction_r)
24 reduction_r
= a(i
) + i
27 !$acc serial loop reduction(*: reduction_r)
29 reduction_r
= reduction_r
* (a(i
) + i
)
32 !$acc serial loop reduction(min: reduction_r)
34 reduction_r
= min(reduction_r
, a(i
) * i
)
37 !$acc serial loop reduction(max: reduction_r)
39 reduction_r
= max(reduction_r
, a(i
) * i
)
42 !$acc serial loop reduction(iand: b)
47 !$acc serial loop reduction(ior: b)
52 !$acc serial loop reduction(ieor: b)
57 !$acc serial loop reduction(.and.: reduction_l)
59 reduction_l
= d(i
) .and
. e(i
)
62 !$acc serial loop reduction(.or.: reduction_l)
64 reduction_l
= d(i
) .or
. e(i
)
67 !$acc serial loop reduction(.eqv.: reduction_l)
69 reduction_l
= d(i
) .eqv
. e(i
)
72 !$acc serial loop reduction(.neqv.: reduction_l)
74 reduction_l
= d(i
) .neqv
. e(i
)
77 !ERROR: Clause IF is not allowed after clause DEVICE_TYPE on the SERIAL LOOP directive
78 !$acc serial loop device_type(*) if(.TRUE.)
84 !$acc serial loop if(ifCondition)
94 !ERROR: Unmatched END PARALLEL LOOP directive
95 !$acc end parallel loop
101 !$acc end serial loop
114 end program openacc_serial_loop_validity