1 ! RUN: %python %S/../test_symbols.py %s %flang_fc1 -fopenmp
3 ! 2.15.1.1 Predetermined rules for associated do-loops index variable
4 ! a) The loop iteration variable(s) in the associated do-loop(s) of a do,
5 ! parallel do, taskloop, or distribute construct is (are) private.
6 ! b) The loop iteration variable in the associated do-loop of a simd construct
7 ! with just one associated do-loop is linear with a linear-step that is the
8 ! increment of the associated do-loop.
9 ! c) The loop iteration variables in the associated do-loops of a simd
10 ! construct with multiple associated do-loops are lastprivate.
11 ! d) A loop iteration variable for a sequential loop in a parallel or task
12 ! generating construct is private in the innermost such construct that
16 ! All the tests assume that the do-loops association for collapse/ordered
17 ! clause has been performed (the number of nested do-loops >= n).
20 ! TODO: nested constructs (k should be private too)
21 !DEF: /test_do (Subroutine) Subprogram
24 !DEF: /test_do/a ObjectEntity REAL(4)
26 !DEF: /test_do/i ObjectEntity INTEGER(4)
27 !DEF: /test_do/j ObjectEntity INTEGER(4)
28 !DEF: /test_do/k ObjectEntity INTEGER(4)
34 !DEF: /test_do/OtherConstruct1/OtherConstruct1/i (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
36 !DEF: /test_do/OtherConstruct1/OtherConstruct1/j (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
40 !DEF: /test_do/OtherConstruct1/k (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
43 !REF: /test_do/OtherConstruct1/k
44 !REF: /test_do/OtherConstruct1/OtherConstruct1/j
45 !REF: /test_do/OtherConstruct1/OtherConstruct1/i
51 end subroutine test_do
54 !DEF: /test_pardo (Subroutine) Subprogram
57 !DEF: /test_pardo/a ObjectEntity REAL(4)
59 !DEF: /test_pardo/i ObjectEntity INTEGER(4)
60 !DEF: /test_pardo/j ObjectEntity INTEGER(4)
61 !DEF: /test_pardo/k ObjectEntity INTEGER(4)
63 !$omp parallel do collapse(2) private(k) ordered(2)
64 !DEF: /test_pardo/OtherConstruct1/i (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
66 !DEF: /test_pardo/OtherConstruct1/j (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
70 !DEF: /test_pardo/OtherConstruct1/k (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
73 !REF: /test_pardo/OtherConstruct1/k
74 !REF: /test_pardo/OtherConstruct1/j
75 !REF: /test_pardo/OtherConstruct1/i
80 end subroutine test_pardo
83 !DEF: /test_taskloop (Subroutine) Subprogram
84 subroutine test_taskloop
86 !DEF: /test_taskloop/a ObjectEntity REAL(4)
88 !DEF: /test_taskloop/i ObjectEntity INTEGER(4)
89 !DEF: /test_taskloop/j ObjectEntity INTEGER(4)
91 !$omp taskloop private(j)
92 !DEF: /test_taskloop/OtherConstruct1/i (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
94 !DEF: /test_taskloop/OtherConstruct1/j (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
95 !REF: /test_taskloop/OtherConstruct1/i
97 !REF: /test_taskloop/a
98 !REF: /test_taskloop/OtherConstruct1/j
99 !REF: /test_taskloop/OtherConstruct1/i
104 end subroutine test_taskloop
106 ! Rule a); OpenMP 4.5 Examples teams.2.f90
107 ! TODO: reduction; data-mapping attributes
108 !DEF: /dotprod (Subroutine) Subprogram
109 !DEF: /dotprod/b ObjectEntity REAL(4)
110 !DEF: /dotprod/c ObjectEntity REAL(4)
111 !DEF: /dotprod/n ObjectEntity INTEGER(4)
112 !DEF: /dotprod/block_size ObjectEntity INTEGER(4)
113 !DEF: /dotprod/num_teams ObjectEntity INTEGER(4)
114 !DEF: /dotprod/block_threads ObjectEntity INTEGER(4)
115 subroutine dotprod (b
, c
, n
, block_size
, num_teams
, block_threads
)
122 !DEF: /dotprod/sum ObjectEntity REAL(4)
124 !REF: /dotprod/block_size
125 !REF: /dotprod/num_teams
126 !REF: /dotprod/block_threads
127 !DEF: /dotprod/i ObjectEntity INTEGER(4)
128 !DEF: /dotprod/i0 ObjectEntity INTEGER(4)
129 integer block_size
, num_teams
, block_threads
, i
, i0
132 !$omp target map(to:b,c) map(tofrom:sum)
133 !$omp teams num_teams(num_teams) thread_limit(block_threads) reduction(+:sum)
135 !DEF: /dotprod/OtherConstruct1/OtherConstruct1/OtherConstruct1/i0 (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
137 !REF: /dotprod/block_size
139 !$omp parallel do reduction(+:sum)
140 !DEF: /dotprod/OtherConstruct1/OtherConstruct1/OtherConstruct1/OtherConstruct1/i (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
141 !REF: /dotprod/OtherConstruct1/OtherConstruct1/OtherConstruct1/i0
142 !DEF: /dotprod/min ELEMENTAL, INTRINSIC, PURE (Function) ProcEntity
143 !REF: /dotprod/block_size
145 do i
=i0
,min(i0
+block_size
, n
)
146 !DEF: /dotprod/OtherConstruct1/OtherConstruct1/OtherConstruct1/OtherConstruct1/sum (OmpReduction) HostAssoc REAL(4)
148 !REF: /dotprod/OtherConstruct1/OtherConstruct1/OtherConstruct1/OtherConstruct1/i
157 end subroutine dotprod
160 ! TODO: nested constructs (j, k should be private too)
161 !DEF: /test_simd (Subroutine) Subprogram
164 !DEF: /test_simd/a ObjectEntity REAL(4)
166 !DEF: /test_simd/i ObjectEntity INTEGER(4)
167 !DEF: /test_simd/j ObjectEntity INTEGER(4)
168 !DEF: /test_simd/k ObjectEntity INTEGER(4)
170 !$omp parallel do simd
171 !DEF: /test_simd/OtherConstruct1/i (OmpLinear, OmpPreDetermined) HostAssoc INTEGER(4)
173 !DEF: /test_simd/OtherConstruct1/j (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
175 !DEF: /test_simd/OtherConstruct1/k (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
178 !REF: /test_simd/OtherConstruct1/k
179 !REF: /test_simd/OtherConstruct1/j
180 !REF: /test_simd/OtherConstruct1/i
185 end subroutine test_simd
188 !DEF: /test_simd_multi (Subroutine) Subprogram
189 subroutine test_simd_multi
191 !DEF: /test_simd_multi/a ObjectEntity REAL(4)
193 !DEF: /test_simd_multi/i ObjectEntity INTEGER(4)
194 !DEF: /test_simd_multi/j ObjectEntity INTEGER(4)
195 !DEF: /test_simd_multi/k ObjectEntity INTEGER(4)
197 !$omp parallel do simd collapse(3)
198 !DEF: /test_simd_multi/OtherConstruct1/i (OmpLastPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
200 !DEF: /test_simd_multi/OtherConstruct1/j (OmpLastPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
202 !DEF: /test_simd_multi/OtherConstruct1/k (OmpLastPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
204 !REF: /test_simd_multi/a
205 !REF: /test_simd_multi/OtherConstruct1/k
206 !REF: /test_simd_multi/OtherConstruct1/j
207 !REF: /test_simd_multi/OtherConstruct1/i
212 end subroutine test_simd_multi
215 !DEF: /test_seq_loop (Subroutine) Subprogram
216 subroutine test_seq_loop
218 !DEF: /test_seq_loop/i ObjectEntity INTEGER(4)
219 !DEF: /test_seq_loop/j ObjectEntity INTEGER(4)
221 !REF: /test_seq_loop/i
223 !REF: /test_seq_loop/j
226 !REF: /test_seq_loop/i
227 !REF: /test_seq_loop/j
230 !REF: /test_seq_loop/i
231 !DEF: /test_seq_loop/OtherConstruct1/OtherConstruct1/j (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
234 !DEF: /test_seq_loop/OtherConstruct1/OtherConstruct1/OtherConstruct1/i (OmpPrivate, OmpPreDetermined) HostAssoc INTEGER(4)
236 !REF: /test_seq_loop/OtherConstruct1/OtherConstruct1/j
240 !REF: /test_seq_loop/i
241 !REF: /test_seq_loop/OtherConstruct1/OtherConstruct1/j
244 !REF: /test_seq_loop/i
245 !REF: /test_seq_loop/j
248 !REF: /test_seq_loop/i
249 !REF: /test_seq_loop/j
251 end subroutine test_seq_loop