xref: /llvm-project/flang/test/Examples/omp-nowait.f90 (revision 2aec2549e8e52f57bc9e9b082be06ece69be61ad)
1*2aec2549SJosh Mottley! REQUIRES: plugins, examples, shell
2*2aec2549SJosh Mottley
3*2aec2549SJosh Mottley! RUN: %flang_fc1 -load %llvmshlibdir/flangOmpReport.so -plugin flang-omp-report -fopenmp %s -o - | FileCheck %s
4*2aec2549SJosh Mottley
5*2aec2549SJosh Mottleysubroutine sb(n)
6*2aec2549SJosh Mottleyimplicit none
7*2aec2549SJosh Mottley
8*2aec2549SJosh Mottleyinteger :: n
9*2aec2549SJosh Mottleyinteger :: arr(n,n), brr(n,n), crr(n,n)
10*2aec2549SJosh Mottleyinteger :: arr_single(n),arr_quad(n,n,n,n)
11*2aec2549SJosh Mottleyinteger :: i,j,k,l,tmp,tmp1,tmp2
12*2aec2549SJosh Mottley
13*2aec2549SJosh Mottley! CHECK:---
14*2aec2549SJosh Mottley
15*2aec2549SJosh Mottley!Simple check with nowait
16*2aec2549SJosh Mottley!$omp do
17*2aec2549SJosh Mottleydo i = 1, n
18*2aec2549SJosh Mottley    arr_single(i) = i
19*2aec2549SJosh Mottleyend do
20*2aec2549SJosh Mottley!$omp end do nowait
21*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
22*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-6]]
23*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       do
24*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:
25*2aec2549SJosh Mottley! CHECK-NEXT:    - clause:      nowait
26*2aec2549SJosh Mottley! CHECK-NEXT:      details:     ''
27*2aec2549SJosh Mottley
28*2aec2549SJosh Mottley!Check for no effects on loop without nowait
29*2aec2549SJosh Mottley!$omp do
30*2aec2549SJosh Mottleydo i = 1, n
31*2aec2549SJosh Mottley    arr_single(i) = i
32*2aec2549SJosh Mottleyend do
33*2aec2549SJosh Mottley!$omp end do
34*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
35*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-6]]
36*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       do
37*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:         []
38*2aec2549SJosh Mottley
39*2aec2549SJosh Mottley!Check with another construct nested inside loop with nowait
40*2aec2549SJosh Mottley!$omp parallel shared(arr)
41*2aec2549SJosh Mottley!$omp do
42*2aec2549SJosh Mottleydo i = 1, n
43*2aec2549SJosh Mottley!$omp critical
44*2aec2549SJosh Mottley    arr_single(i) = i
45*2aec2549SJosh Mottley!$omp end critical
46*2aec2549SJosh Mottleyend do
47*2aec2549SJosh Mottley!$omp end do nowait
48*2aec2549SJosh Mottley!$omp end parallel
49*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
50*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-7]]
51*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       critical
52*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:         []
53*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
54*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-13]]
55*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       do
56*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:
57*2aec2549SJosh Mottley! CHECK-NEXT:    - clause:      nowait
58*2aec2549SJosh Mottley! CHECK-NEXT:      details:     ''
59*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
60*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-20]]
61*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       parallel
62*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:
63*2aec2549SJosh Mottley! CHECK-NEXT:    - clause:      shared
64*2aec2549SJosh Mottley! CHECK-NEXT:      details:     arr
65*2aec2549SJosh Mottley
66*2aec2549SJosh Mottley!Check with back to back loops (one with nowait) inside a parallel construct
67*2aec2549SJosh Mottley!$omp parallel shared(arr)
68*2aec2549SJosh Mottley!$omp do
69*2aec2549SJosh Mottleydo i=1,10
70*2aec2549SJosh Mottley    arr(i,j) = i+j
71*2aec2549SJosh Mottleyend do
72*2aec2549SJosh Mottley!$omp end do nowait
73*2aec2549SJosh Mottley!$omp do schedule(guided)
74*2aec2549SJosh Mottleydo j=1,10
75*2aec2549SJosh Mottleyend do
76*2aec2549SJosh Mottley!$omp end do
77*2aec2549SJosh Mottley!$omp end parallel
78*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
79*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-11]]
80*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       do
81*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:
82*2aec2549SJosh Mottley! CHECK-NEXT:    - clause:      nowait
83*2aec2549SJosh Mottley! CHECK-NEXT:      details:     ''
84*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
85*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-12]]
86*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       do
87*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:
88*2aec2549SJosh Mottley! CHECK-NEXT:    - clause:      schedule
89*2aec2549SJosh Mottley! CHECK-NEXT:      details:     guided
90*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
91*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-24]]
92*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       parallel
93*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:
94*2aec2549SJosh Mottley! CHECK-NEXT:    - clause:      shared
95*2aec2549SJosh Mottley! CHECK-NEXT:      details:     arr
96*2aec2549SJosh Mottley
97*2aec2549SJosh Mottley
98*2aec2549SJosh Mottley!Check nested parallel do loops with a nowait outside
99*2aec2549SJosh Mottley!$omp parallel shared(arr)
100*2aec2549SJosh Mottley!$omp do
101*2aec2549SJosh Mottleydo i=1,10
102*2aec2549SJosh Mottley    arr_single(i)=i
103*2aec2549SJosh Mottley    !$omp parallel
104*2aec2549SJosh Mottley    !$omp do
105*2aec2549SJosh Mottley    do j=1,10
106*2aec2549SJosh Mottley        !$omp critical
107*2aec2549SJosh Mottley        arr(i,j) = i+j
108*2aec2549SJosh Mottley        !$omp end critical
109*2aec2549SJosh Mottley    end do
110*2aec2549SJosh Mottley    !$omp end do
111*2aec2549SJosh Mottley    !$omp end parallel
112*2aec2549SJosh Mottleyend do
113*2aec2549SJosh Mottley!$omp end do nowait
114*2aec2549SJosh Mottley!$omp end parallel
115*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
116*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-10]]
117*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       critical
118*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:         []
119*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
120*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-16]]
121*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       do
122*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:         []
123*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
124*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-21]]
125*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       parallel
126*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:         []
127*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
128*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-28]]
129*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       do
130*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:
131*2aec2549SJosh Mottley! CHECK-NEXT:    - clause:      nowait
132*2aec2549SJosh Mottley! CHECK-NEXT:      details:     ''
133*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
134*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-35]]
135*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       parallel
136*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:
137*2aec2549SJosh Mottley! CHECK-NEXT:    - clause:      shared
138*2aec2549SJosh Mottley! CHECK-NEXT:      details:     arr
139*2aec2549SJosh Mottley
140*2aec2549SJosh Mottley!Check nested parallel do loops with a nowait inside
141*2aec2549SJosh Mottley!$omp parallel shared(arr)
142*2aec2549SJosh Mottley!$omp do
143*2aec2549SJosh Mottleydo i=1,10
144*2aec2549SJosh Mottley    arr_single(i)=i
145*2aec2549SJosh Mottley    !$omp parallel
146*2aec2549SJosh Mottley    !$omp do
147*2aec2549SJosh Mottley    do j=1,10
148*2aec2549SJosh Mottley        !$omp critical
149*2aec2549SJosh Mottley        arr(i,j) = i+j
150*2aec2549SJosh Mottley        !$omp end critical
151*2aec2549SJosh Mottley    end do
152*2aec2549SJosh Mottley    !$omp end do nowait
153*2aec2549SJosh Mottley    !$omp end parallel
154*2aec2549SJosh Mottleyend do
155*2aec2549SJosh Mottley!$omp end do
156*2aec2549SJosh Mottley!$omp end parallel
157*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
158*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-10]]
159*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       critical
160*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:         []
161*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
162*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-16]]
163*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       do
164*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:
165*2aec2549SJosh Mottley! CHECK-NEXT:    - clause:      nowait
166*2aec2549SJosh Mottley! CHECK-NEXT:      details:     ''
167*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
168*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-23]]
169*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       parallel
170*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:         []
171*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
172*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-30]]
173*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       do
174*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:         []
175*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
176*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-35]]
177*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       parallel
178*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:
179*2aec2549SJosh Mottley! CHECK-NEXT:    - clause:      shared
180*2aec2549SJosh Mottley! CHECK-NEXT:      details:     arr
181*2aec2549SJosh Mottley
182*2aec2549SJosh Mottley!Check nested parallel do loops with a nowait inside
183*2aec2549SJosh Mottley!$omp parallel
184*2aec2549SJosh Mottley!$omp do
185*2aec2549SJosh Mottleydo i=1,10
186*2aec2549SJosh Mottley    arr_single(i)=i
187*2aec2549SJosh Mottley    !$omp parallel shared(arr_quad)
188*2aec2549SJosh Mottley    !$omp do schedule(dynamic)
189*2aec2549SJosh Mottley    do j=1,10
190*2aec2549SJosh Mottley        !$omp parallel
191*2aec2549SJosh Mottley        !$omp do
192*2aec2549SJosh Mottley        do k=1,10
193*2aec2549SJosh Mottley            !$omp parallel
194*2aec2549SJosh Mottley            !$omp do
195*2aec2549SJosh Mottley            do l=1,10
196*2aec2549SJosh Mottley                arr_quad(i,j,k,l) = i+j+k+l
197*2aec2549SJosh Mottley            end do
198*2aec2549SJosh Mottley            !$omp end do nowait
199*2aec2549SJosh Mottley            !$omp end parallel
200*2aec2549SJosh Mottley        end do
201*2aec2549SJosh Mottley        !$omp end do
202*2aec2549SJosh Mottley        !$omp end parallel
203*2aec2549SJosh Mottley    end do
204*2aec2549SJosh Mottley    !$omp end do nowait
205*2aec2549SJosh Mottley    !$omp end parallel
206*2aec2549SJosh Mottleyend do
207*2aec2549SJosh Mottley!$omp end do
208*2aec2549SJosh Mottley!$omp end parallel
209*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
210*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-16]]
211*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       do
212*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:
213*2aec2549SJosh Mottley! CHECK-NEXT:    - clause:      nowait
214*2aec2549SJosh Mottley! CHECK-NEXT:      details:     ''
215*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
216*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-23]]
217*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       parallel
218*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:         []
219*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
220*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-29]]
221*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       do
222*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:         []
223*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
224*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-34]]
225*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       parallel
226*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:         []
227*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
228*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-40]]
229*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       do
230*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:
231*2aec2549SJosh Mottley! CHECK-NEXT:    - clause:      nowait
232*2aec2549SJosh Mottley! CHECK-NEXT:      details:     ''
233*2aec2549SJosh Mottley! CHECK-NEXT:    - clause:      schedule
234*2aec2549SJosh Mottley! CHECK-NEXT:      details:     dynamic
235*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
236*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-49]]
237*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       parallel
238*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:
239*2aec2549SJosh Mottley! CHECK-NEXT:    - clause:      shared
240*2aec2549SJosh Mottley! CHECK-NEXT:      details:     arr_quad
241*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
242*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-58]]
243*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       do
244*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:         []
245*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
246*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-63]]
247*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       parallel
248*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:         []
249*2aec2549SJosh Mottley
250*2aec2549SJosh Mottley
251*2aec2549SJosh Mottley!Check a do simd with nowait
252*2aec2549SJosh Mottley!$omp do simd private(tmp)
253*2aec2549SJosh Mottleydo j = 1,n
254*2aec2549SJosh Mottley    do i = 1,n
255*2aec2549SJosh Mottley        tmp = arr(i,j) + brr(i,j)
256*2aec2549SJosh Mottley        crr(i,j) = tmp
257*2aec2549SJosh Mottley    end do
258*2aec2549SJosh Mottleyend do
259*2aec2549SJosh Mottley!$omp end do simd nowait
260*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
261*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-9]]
262*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       do simd
263*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:
264*2aec2549SJosh Mottley! CHECK-NEXT:    - clause:      nowait
265*2aec2549SJosh Mottley! CHECK-NEXT:      details:     ''
266*2aec2549SJosh Mottley! CHECK-NEXT:    - clause:      private
267*2aec2549SJosh Mottley! CHECK-NEXT:      details:     tmp
268*2aec2549SJosh Mottley
269*2aec2549SJosh Mottley
270*2aec2549SJosh Mottley!test nowait on non-do construct
271*2aec2549SJosh Mottley!$omp parallel
272*2aec2549SJosh Mottley!$omp single
273*2aec2549SJosh Mottleytmp1 = i+j
274*2aec2549SJosh Mottley!$omp end single
275*2aec2549SJosh Mottley
276*2aec2549SJosh Mottley!$omp single
277*2aec2549SJosh Mottleytmp2 = i-j
278*2aec2549SJosh Mottley!$omp end single nowait
279*2aec2549SJosh Mottley!$omp end parallel
280*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
281*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-9]]
282*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       single
283*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:         []
284*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
285*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-9]]
286*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       single
287*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:
288*2aec2549SJosh Mottley! CHECK-NEXT:    - clause:      nowait
289*2aec2549SJosh Mottley! CHECK-NEXT:      details:     ''
290*2aec2549SJosh Mottley! CHECK-NEXT:- file:            '{{[^"]*}}omp-nowait.f90'
291*2aec2549SJosh Mottley! CHECK-NEXT:  line:            [[@LINE-20]]
292*2aec2549SJosh Mottley! CHECK-NEXT:  construct:       parallel
293*2aec2549SJosh Mottley! CHECK-NEXT:  clauses:         []
294*2aec2549SJosh Mottley
295*2aec2549SJosh Mottleyend subroutine
296*2aec2549SJosh Mottley
297*2aec2549SJosh Mottley! CHECK-NEXT:...
298