xref: /llvm-project/flang/test/Semantics/OpenACC/acc-serial.f90 (revision a6c02edd6eac476523b5c73f29619a7a9e054872)
1! RUN: %python %S/../test_errors.py %s %flang -fopenacc -pedantic
2
3! Check OpenACC clause validity for the following construct and directive:
4!   2.5.2 Serial
5
6program openacc_serial_validity
7
8  implicit none
9
10  type atype
11    real(8), dimension(10) :: arr
12    real(8) :: s
13  end type atype
14
15  integer :: i, j, b, gang_size, vector_size, worker_size
16  integer, parameter :: N = 256
17  integer, dimension(N) :: c
18  logical, dimension(N) :: d, e
19  integer :: async1
20  integer :: wait1, wait2
21  real :: reduction_r
22  logical :: reduction_l
23  real(8), dimension(N, N) :: aa, bb, cc
24  real(8), dimension(:), allocatable :: dd
25  real(8), pointer :: p
26  logical :: ifCondition = .TRUE.
27  type(atype) :: t
28  type(atype), dimension(10) :: ta
29
30  real(8), dimension(N) :: a, f, g, h
31
32  !$acc serial
33  !ERROR: Directive SET may not be called within a compute region
34  !$acc set default_async(i)
35  !$acc end serial
36
37  !$acc serial
38  !$acc loop
39  do i = 1, N
40    !ERROR: Directive SET may not be called within a compute region
41    !$acc set default_async(i)
42    a(i) = 3.14
43  end do
44  !$acc end serial
45
46  !$acc serial
47  !$acc end serial
48
49  !$acc serial async
50  !$acc end serial
51
52  !$acc serial async(1)
53  !$acc end serial
54
55  !ERROR: At most one ASYNC clause can appear on the SERIAL directive
56  !$acc serial async(1) async(2)
57  !$acc end serial
58
59  !$acc serial async(async1)
60  !$acc end serial
61
62  !$acc serial wait
63  !$acc end serial
64
65  !$acc serial wait(1)
66  !$acc end serial
67
68  !$acc serial wait(wait1)
69  !$acc end serial
70
71  !$acc serial wait(1,2)
72  !$acc end serial
73
74  !$acc serial wait(wait1, wait2)
75  !$acc end serial
76
77  !$acc serial wait(wait1) wait(wait2)
78  !$acc end serial
79
80  !PORTABILITY: NUM_GANGS clause is not allowed on the SERIAL directive and will be ignored
81  !$acc serial num_gangs(8)
82  !$acc end serial
83
84  !PORTABILITY: NUM_WORKERS clause is not allowed on the SERIAL directive and will be ignored
85  !$acc serial num_workers(8)
86  !$acc end serial
87
88  !PORTABILITY: VECTOR_LENGTH clause is not allowed on the SERIAL directive and will be ignored
89  !$acc serial vector_length(128)
90  !$acc end serial
91
92  !$acc serial if(.true.)
93  !$acc end serial
94
95  !ERROR: At most one IF clause can appear on the SERIAL directive
96  !$acc serial if(.true.) if(ifCondition)
97  !$acc end serial
98
99  !$acc serial if(ifCondition)
100  !$acc end serial
101
102  !$acc serial self
103  !$acc end serial
104
105  !$acc serial self(.true.)
106  !$acc end serial
107
108  !$acc serial self(ifCondition)
109  !$acc end serial
110
111  !$acc serial reduction(.neqv.: reduction_l)
112  !$acc loop reduction(.neqv.: reduction_l)
113  do i = 1, N
114    reduction_l = d(i) .neqv. e(i)
115  end do
116  !$acc end serial
117
118  !$acc serial copy(aa) copyin(bb) copyout(cc)
119  !$acc end serial
120
121  !$acc serial copy(aa, bb) copyout(zero: cc)
122  !$acc end serial
123
124  !$acc serial present(aa, bb) create(cc)
125  !$acc end serial
126
127  !$acc serial copyin(readonly: aa, bb) create(zero: cc)
128  !$acc end serial
129
130  !$acc serial deviceptr(aa, bb) no_create(cc)
131  !$acc end serial
132
133  !ERROR: Argument `aa` on the ATTACH clause must be a variable or array with the POINTER or ALLOCATABLE attribute
134  !$acc serial attach(aa, dd, p)
135  !$acc end serial
136
137  !$acc serial firstprivate(bb, cc)
138  !$acc end serial
139
140  !$acc serial private(aa)
141  !$acc end serial
142
143  !$acc serial default(none)
144  !$acc end serial
145
146  !$acc serial default(present)
147  !$acc end serial
148
149  !ERROR: At most one DEFAULT clause can appear on the SERIAL directive
150  !$acc serial default(present) default(none)
151  !$acc end serial
152
153  !$acc serial device_type(*) async wait
154  !$acc end serial
155
156  !$acc serial device_type(*) async
157  do i = 1, N
158    a(i) = 3.14
159  end do
160  !$acc end serial
161
162  !ERROR: Clause IF is not allowed after clause DEVICE_TYPE on the SERIAL directive
163  !$acc serial device_type(*) if(.TRUE.)
164  do i = 1, N
165    a(i) = 3.14
166  end do
167  !$acc end serial
168
169  do i = 1, 100
170    !$acc serial
171    !ERROR: CYCLE to construct outside of SERIAL construct is not allowed
172    if (i == 10) cycle
173    !$acc end serial
174  end do
175
176  !$acc serial
177  do i = 1, 100
178    if (i == 10) cycle
179  end do
180  !$acc end serial
181
182end program openacc_serial_validity
183