xref: /llvm-project/flang/test/Lower/OpenMP/target.f90 (revision 937cbce14c9aa956342a9c818c26a8a557802843)
1! The "thread_limit" clause was added to the "target" construct in OpenMP 5.1.
2! RUN: %flang_fc1 -emit-hlfir -fopenmp -fopenmp-version=51 %s -o - | FileCheck %s
3
4!===============================================================================
5! Target_Enter Simple
6!===============================================================================
7
8!CHECK-LABEL: func.func @_QPomp_target_enter_simple() {
9subroutine omp_target_enter_simple
10   integer :: a(1024)
11   !CHECK: %[[BOUNDS:.*]] = omp.map.bounds   lower_bound({{.*}}) upper_bound({{.*}}) extent({{.*}}) stride({{.*}}) start_idx({{.*}})
12   !CHECK: %[[MAP:.*]] = omp.map.info var_ptr({{.*}})   map_clauses(to) capture(ByRef) bounds(%[[BOUNDS]]) -> !fir.ref<!fir.array<1024xi32>> {name = "a"}
13   !CHECK: omp.target_enter_data   map_entries(%[[MAP]] : !fir.ref<!fir.array<1024xi32>>)
14   !$omp target enter data map(to: a)
15    return
16end subroutine omp_target_enter_simple
17
18!===============================================================================
19! Target_Enter `depend` clause
20!===============================================================================
21
22!CHECK-LABEL: func.func @_QPomp_target_enter_depend() {
23subroutine omp_target_enter_depend
24   !CHECK: %[[A:.*]]:2 = hlfir.declare %{{.*}}(%{{.*}}) {uniq_name = "_QFomp_target_enter_dependEa"} : (!fir.ref<!fir.array<1024xi32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<1024xi32>>, !fir.ref<!fir.array<1024xi32>>)
25   integer :: a(1024)
26
27   !CHECK: omp.task depend(taskdependout -> %[[A]]#1 : !fir.ref<!fir.array<1024xi32>>) private({{.*}}) {
28   !$omp task depend(out: a)
29   call foo(a)
30   !$omp end task
31   !CHECK: %[[BOUNDS:.*]] = omp.map.bounds   lower_bound({{.*}}) upper_bound({{.*}}) extent({{.*}}) stride({{.*}}) start_idx({{.*}})
32   !CHECK: %[[MAP:.*]] = omp.map.info var_ptr({{.*}})   map_clauses(to) capture(ByRef) bounds(%[[BOUNDS]]) -> !fir.ref<!fir.array<1024xi32>> {name = "a"}
33   !CHECK: omp.target_enter_data depend(taskdependin -> %[[A]]#1 : !fir.ref<!fir.array<1024xi32>>) map_entries(%[[MAP]] : !fir.ref<!fir.array<1024xi32>>)
34   !$omp target enter data map(to: a) depend(in: a)
35    return
36end subroutine omp_target_enter_depend
37
38!===============================================================================
39! Target_Enter Map types
40!===============================================================================
41
42!CHECK-LABEL: func.func @_QPomp_target_enter_mt() {
43subroutine omp_target_enter_mt
44   integer :: a(1024)
45   integer :: b(1024)
46   integer :: c(1024)
47   integer :: d(1024)
48   !CHECK: %[[BOUNDS_0:.*]] = omp.map.bounds   lower_bound({{.*}}) upper_bound({{.*}}) extent({{.*}}) stride({{.*}}) start_idx({{.*}})
49   !CHECK: %[[MAP_0:.*]] = omp.map.info var_ptr({{.*}})   map_clauses(to) capture(ByRef) bounds(%[[BOUNDS_0]]) -> !fir.ref<!fir.array<1024xi32>> {name = "a"}
50   !CHECK: %[[BOUNDS_1:.*]] = omp.map.bounds   lower_bound({{.*}}) upper_bound({{.*}}) extent({{.*}}) stride({{.*}}) start_idx({{.*}})
51   !CHECK: %[[MAP_1:.*]] = omp.map.info var_ptr(%{{.*}})  map_clauses(to) capture(ByRef) bounds(%[[BOUNDS_1]]) -> !fir.ref<!fir.array<1024xi32>> {name = "b"}
52   !CHECK: %[[BOUNDS_2:.*]] = omp.map.bounds   lower_bound({{.*}}) upper_bound({{.*}}) extent({{.*}}) stride({{.*}}) start_idx({{.*}})
53   !CHECK: %[[MAP_2:.*]] = omp.map.info var_ptr({{.*}})   map_clauses(always, exit_release_or_enter_alloc) capture(ByRef) bounds(%[[BOUNDS_2]]) -> !fir.ref<!fir.array<1024xi32>> {name = "c"}
54   !CHECK: %[[BOUNDS_3:.*]] = omp.map.bounds   lower_bound({{.*}}) upper_bound({{.*}}) extent({{.*}}) stride({{.*}}) start_idx({{.*}})
55   !CHECK: %[[MAP_3:.*]] = omp.map.info var_ptr({{.*}})   map_clauses(to) capture(ByRef) bounds(%[[BOUNDS_3]]) -> !fir.ref<!fir.array<1024xi32>> {name = "d"}
56   !CHECK: omp.target_enter_data   map_entries(%[[MAP_0]], %[[MAP_1]], %[[MAP_2]], %[[MAP_3]] : !fir.ref<!fir.array<1024xi32>>, !fir.ref<!fir.array<1024xi32>>, !fir.ref<!fir.array<1024xi32>>, !fir.ref<!fir.array<1024xi32>>)
57   !$omp target enter data map(to: a, b) map(always, alloc: c) map(to: d)
58end subroutine omp_target_enter_mt
59
60!===============================================================================
61! `Nowait` clause
62!===============================================================================
63
64!CHECK-LABEL: func.func @_QPomp_target_enter_nowait() {
65subroutine omp_target_enter_nowait
66   integer :: a(1024)
67   !CHECK: %[[BOUNDS:.*]] = omp.map.bounds   lower_bound({{.*}}) upper_bound({{.*}}) extent({{.*}}) stride({{.*}}) start_idx({{.*}})
68   !CHECK: %[[MAP:.*]] = omp.map.info var_ptr({{.*}})   map_clauses(to) capture(ByRef) bounds(%[[BOUNDS]]) -> !fir.ref<!fir.array<1024xi32>> {name = "a"}
69   !CHECK: omp.target_enter_data map_entries(%[[MAP]] : !fir.ref<!fir.array<1024xi32>>) nowait
70   !$omp target enter data map(to: a) nowait
71end subroutine omp_target_enter_nowait
72
73!===============================================================================
74! `if` clause
75!===============================================================================
76
77!CHECK-LABEL: func.func @_QPomp_target_enter_if() {
78subroutine omp_target_enter_if
79   integer :: a(1024)
80   integer :: i
81   i = 5
82   !CHECK: %[[VAL_3:.*]] = fir.load %[[VAL_1:.*]] : !fir.ref<i32>
83   !CHECK: %[[VAL_4:.*]] = arith.constant 10 : i32
84   !CHECK: %[[VAL_5:.*]] = arith.cmpi slt, %[[VAL_3]], %[[VAL_4]] : i32
85   !CHECK: %[[BOUNDS:.*]] = omp.map.bounds   lower_bound({{.*}}) upper_bound({{.*}}) extent({{.*}}) stride({{.*}}) start_idx({{.*}})
86   !CHECK: %[[MAP:.*]] = omp.map.info var_ptr({{.*}})   map_clauses(to) capture(ByRef) bounds(%[[BOUNDS]]) -> !fir.ref<!fir.array<1024xi32>> {name = "a"}
87   !CHECK: omp.target_enter_data   if(%[[VAL_5]]) map_entries(%[[MAP]] : !fir.ref<!fir.array<1024xi32>>)
88   !$omp target enter data if(i<10) map(to: a)
89end subroutine omp_target_enter_if
90
91!===============================================================================
92! `device` clause
93!===============================================================================
94
95!CHECK-LABEL: func.func @_QPomp_target_enter_device() {
96subroutine omp_target_enter_device
97   integer :: a(1024)
98   !CHECK: %[[VAL_1:.*]] = arith.constant 2 : i32
99   !CHECK: %[[BOUNDS:.*]] = omp.map.bounds   lower_bound({{.*}}) upper_bound({{.*}}) extent({{.*}}) stride({{.*}}) start_idx({{.*}})
100   !CHECK: %[[MAP:.*]] = omp.map.info var_ptr({{.*}})   map_clauses(to) capture(ByRef) bounds(%[[BOUNDS]]) -> !fir.ref<!fir.array<1024xi32>> {name = "a"}
101   !CHECK: omp.target_enter_data   device(%[[VAL_1]] : i32) map_entries(%[[MAP]] : !fir.ref<!fir.array<1024xi32>>)
102   !$omp target enter data map(to: a) device(2)
103end subroutine omp_target_enter_device
104
105!===============================================================================
106! Target_Exit Simple
107!===============================================================================
108
109!CHECK-LABEL: func.func @_QPomp_target_exit_simple() {
110subroutine omp_target_exit_simple
111   integer :: a(1024)
112   !CHECK: %[[BOUNDS:.*]] = omp.map.bounds   lower_bound({{.*}}) upper_bound({{.*}}) extent({{.*}}) stride({{.*}}) start_idx({{.*}})
113   !CHECK: %[[MAP:.*]] = omp.map.info var_ptr({{.*}})   map_clauses(from) capture(ByRef) bounds(%[[BOUNDS]]) -> !fir.ref<!fir.array<1024xi32>> {name = "a"}
114   !CHECK: omp.target_exit_data   map_entries(%[[MAP]] : !fir.ref<!fir.array<1024xi32>>)
115   !$omp target exit data map(from: a)
116end subroutine omp_target_exit_simple
117
118!===============================================================================
119! Target_Exit Map types
120!===============================================================================
121
122!CHECK-LABEL: func.func @_QPomp_target_exit_mt() {
123subroutine omp_target_exit_mt
124   integer :: a(1024)
125   integer :: b(1024)
126   integer :: c(1024)
127   integer :: d(1024)
128   integer :: e(1024)
129   !CHECK: %[[BOUNDS_0:.*]] = omp.map.bounds   lower_bound({{.*}}) upper_bound({{.*}}) extent({{.*}}) stride({{.*}}) start_idx({{.*}})
130   !CHECK: %[[MAP_0:.*]] = omp.map.info var_ptr({{.*}})   map_clauses(from) capture(ByRef) bounds(%[[BOUNDS_0]]) -> !fir.ref<!fir.array<1024xi32>> {name = "a"}
131   !CHECK: %[[BOUNDS_1:.*]] = omp.map.bounds   lower_bound({{.*}}) upper_bound({{.*}}) extent({{.*}}) stride({{.*}}) start_idx({{.*}})
132   !CHECK: %[[MAP_1:.*]] = omp.map.info var_ptr({{.*}})   map_clauses(from) capture(ByRef) bounds(%[[BOUNDS_1]]) -> !fir.ref<!fir.array<1024xi32>> {name = "b"}
133   !CHECK: %[[BOUNDS_2:.*]] = omp.map.bounds   lower_bound({{.*}}) upper_bound({{.*}}) extent({{.*}}) stride({{.*}}) start_idx({{.*}})
134   !CHECK: %[[MAP_2:.*]] = omp.map.info var_ptr({{.*}})   map_clauses(exit_release_or_enter_alloc) capture(ByRef) bounds(%[[BOUNDS_2]]) -> !fir.ref<!fir.array<1024xi32>> {name = "c"}
135   !CHECK: %[[BOUNDS_3:.*]] = omp.map.bounds   lower_bound({{.*}}) upper_bound({{.*}}) extent({{.*}}) stride({{.*}}) start_idx({{.*}})
136   !CHECK: %[[MAP_3:.*]] = omp.map.info var_ptr({{.*}})   map_clauses(always, delete) capture(ByRef) bounds(%[[BOUNDS_3]]) -> !fir.ref<!fir.array<1024xi32>> {name = "d"}
137   !CHECK: %[[BOUNDS_4:.*]] = omp.map.bounds   lower_bound({{.*}}) upper_bound({{.*}}) extent({{.*}}) stride({{.*}}) start_idx({{.*}})
138   !CHECK: %[[MAP_4:.*]] = omp.map.info var_ptr({{.*}})   map_clauses(from) capture(ByRef) bounds(%[[BOUNDS_4]]) -> !fir.ref<!fir.array<1024xi32>> {name = "e"}
139   !CHECK: omp.target_exit_data map_entries(%[[MAP_0]], %[[MAP_1]], %[[MAP_2]], %[[MAP_3]], %[[MAP_4]] : !fir.ref<!fir.array<1024xi32>>, !fir.ref<!fir.array<1024xi32>>, !fir.ref<!fir.array<1024xi32>>, !fir.ref<!fir.array<1024xi32>>, !fir.ref<!fir.array<1024xi32>>)
140   !$omp target exit data map(from: a,b) map(release: c) map(always, delete: d) map(from: e)
141end subroutine omp_target_exit_mt
142
143!===============================================================================
144! `device` clause
145!===============================================================================
146
147!CHECK-LABEL: func.func @_QPomp_target_exit_device() {
148subroutine omp_target_exit_device
149   integer :: a(1024)
150   integer :: d
151   !CHECK: %[[VAL_2:.*]] = fir.load %[[VAL_1:.*]] : !fir.ref<i32>
152   !CHECK: %[[BOUNDS:.*]] = omp.map.bounds   lower_bound({{.*}}) upper_bound({{.*}}) extent({{.*}}) stride({{.*}}) start_idx({{.*}})
153   !CHECK: %[[MAP:.*]] = omp.map.info var_ptr({{.*}})   map_clauses(from) capture(ByRef) bounds(%[[BOUNDS]]) -> !fir.ref<!fir.array<1024xi32>> {name = "a"}
154   !CHECK: omp.target_exit_data   device(%[[VAL_2]] : i32) map_entries(%[[MAP]] : !fir.ref<!fir.array<1024xi32>>)
155   !$omp target exit data map(from: a) device(d)
156end subroutine omp_target_exit_device
157
158!===============================================================================
159! Target_Exit `depend` clause
160!===============================================================================
161
162!CHECK-LABEL: func.func @_QPomp_target_exit_depend() {
163subroutine omp_target_exit_depend
164   !CHECK: %[[A:.*]]:2 = hlfir.declare %{{.*}}(%{{.*}}) {uniq_name = "_QFomp_target_exit_dependEa"} : (!fir.ref<!fir.array<1024xi32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<1024xi32>>, !fir.ref<!fir.array<1024xi32>>)
165   integer :: a(1024)
166   !CHECK: omp.task depend(taskdependout -> %[[A]]#1 : !fir.ref<!fir.array<1024xi32>>) private({{.*}}) {
167   !$omp task depend(out: a)
168   call foo(a)
169   !$omp end task
170   !CHECK: %[[BOUNDS:.*]] = omp.map.bounds   lower_bound({{.*}}) upper_bound({{.*}}) extent({{.*}}) stride({{.*}}) start_idx({{.*}})
171   !CHECK: %[[MAP:.*]] = omp.map.info var_ptr({{.*}})   map_clauses(from) capture(ByRef) bounds(%[[BOUNDS]]) -> !fir.ref<!fir.array<1024xi32>> {name = "a"}
172   !CHECK: omp.target_exit_data depend(taskdependout -> %[[A]]#1 : !fir.ref<!fir.array<1024xi32>>) map_entries(%[[MAP]] : !fir.ref<!fir.array<1024xi32>>)
173   !$omp target exit data map(from: a) depend(out: a)
174end subroutine omp_target_exit_depend
175
176
177!===============================================================================
178! Target_Update `depend` clause
179!===============================================================================
180
181!CHECK-LABEL: func.func @_QPomp_target_update_depend() {
182subroutine omp_target_update_depend
183   !CHECK: %[[A:.*]]:2 = hlfir.declare %{{.*}}(%{{.*}}) {uniq_name = "_QFomp_target_update_dependEa"} : (!fir.ref<!fir.array<1024xi32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<1024xi32>>, !fir.ref<!fir.array<1024xi32>>)
184   integer :: a(1024)
185
186   !CHECK: omp.task depend(taskdependout -> %[[A]]#1 : !fir.ref<!fir.array<1024xi32>>) private({{.*}}) {
187   !$omp task depend(out: a)
188   call foo(a)
189   !$omp end task
190
191   !CHECK: %[[BOUNDS:.*]] = omp.map.bounds
192   !CHECK: %[[MAP:.*]] = omp.map.info var_ptr(%[[A]]#1 : !fir.ref<!fir.array<1024xi32>>, !fir.array<1024xi32>) map_clauses(to) capture(ByRef) bounds(%[[BOUNDS]]) -> !fir.ref<!fir.array<1024xi32>> {name = "a"}
193   !CHECK: omp.target_update depend(taskdependin -> %[[A]]#1 : !fir.ref<!fir.array<1024xi32>>) map_entries(%[[MAP]] : !fir.ref<!fir.array<1024xi32>>)
194   !$omp target update to(a) depend(in:a)
195end subroutine omp_target_update_depend
196
197!===============================================================================
198! Target_Update `to` clause
199!===============================================================================
200
201!CHECK-LABEL: func.func @_QPomp_target_update_to() {
202subroutine omp_target_update_to
203   integer :: a(1024)
204
205   !CHECK-DAG: %[[A_DECL:.*]]:2 = hlfir.declare %{{.*}}(%{{.*}})
206   !CHECK-DAG: %[[BOUNDS:.*]] = omp.map.bounds
207
208   !CHECK: %[[TO_MAP:.*]] = omp.map.info var_ptr(%[[A_DECL]]#1 : !fir.ref<!fir.array<1024xi32>>, !fir.array<1024xi32>)
209   !CHECK-SAME: map_clauses(to) capture(ByRef)
210   !CHECK-SAME: bounds(%[[BOUNDS]]) -> !fir.ref<!fir.array<1024xi32>> {name = "a"}
211
212   !CHECK: omp.target_update map_entries(%[[TO_MAP]] : !fir.ref<!fir.array<1024xi32>>)
213   !$omp target update to(a)
214end subroutine omp_target_update_to
215
216!===============================================================================
217! Target_Update `from` clause
218!===============================================================================
219
220!CHECK-LABEL: func.func @_QPomp_target_update_from() {
221subroutine omp_target_update_from
222   integer :: a(1024)
223
224   !CHECK-DAG: %[[A_DECL:.*]]:2 = hlfir.declare %{{.*}}(%{{.*}})
225   !CHECK-DAG: %[[BOUNDS:.*]] = omp.map.bounds
226
227   !CHECK: %[[FROM_MAP:.*]] = omp.map.info var_ptr(%[[A_DECL]]#1 : !fir.ref<!fir.array<1024xi32>>, !fir.array<1024xi32>)
228   !CHECK-SAME: map_clauses(from) capture(ByRef)
229   !CHECK-SAME: bounds(%[[BOUNDS]]) -> !fir.ref<!fir.array<1024xi32>> {name = "a"}
230
231   !CHECK: omp.target_update map_entries(%[[FROM_MAP]] : !fir.ref<!fir.array<1024xi32>>)
232   !$omp target update from(a)
233end subroutine omp_target_update_from
234
235!===============================================================================
236! Target_Update `if` clause
237!===============================================================================
238
239!CHECK-LABEL: func.func @_QPomp_target_update_if() {
240subroutine omp_target_update_if
241   integer :: a(1024)
242   logical :: i
243
244   !CHECK-DAG: %[[A_DECL:.*]]:2 = hlfir.declare %{{.*}}(%{{.*}})
245   !CHECK-DAG: %[[BOUNDS:.*]] = omp.map.bounds
246   !CHECK-DAG: %[[COND:.*]] = fir.convert %{{.*}} : (!fir.logical<4>) -> i1
247
248   !CHECK: omp.target_update if(%[[COND]]) map_entries
249   !$omp target update from(a) if(i)
250end subroutine omp_target_update_if
251
252!===============================================================================
253! Target_Update `device` clause
254!===============================================================================
255
256!CHECK-LABEL: func.func @_QPomp_target_update_device() {
257subroutine omp_target_update_device
258   integer :: a(1024)
259   logical :: i
260
261   !CHECK-DAG: %[[A_DECL:.*]]:2 = hlfir.declare %{{.*}}(%{{.*}})
262   !CHECK-DAG: %[[BOUNDS:.*]] = omp.map.bounds
263   !CHECK-DAG: %[[DEVICE:.*]] = arith.constant 1 : i32
264
265   !CHECK: omp.target_update device(%[[DEVICE]] : i32) map_entries
266   !$omp target update from(a) device(1)
267end subroutine omp_target_update_device
268
269!===============================================================================
270! Target_Update `nowait` clause
271!===============================================================================
272
273!CHECK-LABEL: func.func @_QPomp_target_update_nowait() {
274subroutine omp_target_update_nowait
275   integer :: a(1024)
276   logical :: i
277
278   !CHECK-DAG: %[[A_DECL:.*]]:2 = hlfir.declare %{{.*}}(%{{.*}})
279   !CHECK-DAG: %[[BOUNDS:.*]] = omp.map.bounds
280
281   !CHECK: omp.target_update map_entries({{.*}}) nowait
282   !$omp target update from(a) nowait
283end subroutine omp_target_update_nowait
284
285!===============================================================================
286! Target_Data with region
287!===============================================================================
288
289!CHECK-LABEL: func.func @_QPomp_target_data() {
290subroutine omp_target_data
291   !CHECK: %[[VAL_0:.*]] = fir.alloca !fir.array<1024xi32> {bindc_name = "a", uniq_name = "_QFomp_target_dataEa"}
292   !CHECK: %[[A_DECL:.*]]:2 = hlfir.declare %[[VAL_0]](%{{.*}}) {uniq_name = "_QFomp_target_dataEa"} : (!fir.ref<!fir.array<1024xi32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<1024xi32>>, !fir.ref<!fir.array<1024xi32>>)
293   integer :: a(1024)
294   !CHECK: %[[BOUNDS:.*]] = omp.map.bounds   lower_bound({{.*}}) upper_bound({{.*}}) extent({{.*}}) stride({{.*}}) start_idx({{.*}})
295   !CHECK: %[[MAP:.*]] = omp.map.info var_ptr(%[[A_DECL]]#1 : !fir.ref<!fir.array<1024xi32>>, !fir.array<1024xi32>)   map_clauses(tofrom) capture(ByRef) bounds(%[[BOUNDS]]) -> !fir.ref<!fir.array<1024xi32>> {name = "a"}
296   !CHECK: omp.target_data   map_entries(%[[MAP]] : !fir.ref<!fir.array<1024xi32>>) {
297   !$omp target data map(tofrom: a)
298      !CHECK: %[[C10:.*]] = arith.constant 10 : i32
299      !CHECK: %[[C1:.*]] = arith.constant 1 : index
300      !CHECK: %[[A_1:.*]] = hlfir.designate %[[A_DECL]]#0 (%[[C1]])  : (!fir.ref<!fir.array<1024xi32>>, index) -> !fir.ref<i32>
301      !CHECK: hlfir.assign %[[C10]] to %[[A_1]] : i32, !fir.ref<i32
302      a(1) = 10
303   !CHECK: omp.terminator
304   !$omp end target data
305   !CHECK: }
306end subroutine omp_target_data
307
308!CHECK-LABEL: func.func @_QPomp_target_data_mt
309subroutine omp_target_data_mt
310   integer :: a(1024)
311   integer :: b(1024)
312   !CHECK: %[[VAR_A:.*]] = fir.alloca !fir.array<1024xi32> {bindc_name = "a", uniq_name = "_QFomp_target_data_mtEa"}
313   !CHECK: %[[VAR_A_DECL:.*]]:2 = hlfir.declare %[[VAR_A]](%{{.*}}) {uniq_name = "_QFomp_target_data_mtEa"} : (!fir.ref<!fir.array<1024xi32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<1024xi32>>, !fir.ref<!fir.array<1024xi32>>)
314   !CHECK: %[[VAR_B:.*]] = fir.alloca !fir.array<1024xi32> {bindc_name = "b", uniq_name = "_QFomp_target_data_mtEb"}
315   !CHECK: %[[VAR_B_DECL:.*]]:2 = hlfir.declare %[[VAR_B]](%{{.*}}) {uniq_name = "_QFomp_target_data_mtEb"} : (!fir.ref<!fir.array<1024xi32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<1024xi32>>, !fir.ref<!fir.array<1024xi32>>)
316   !CHECK: %[[BOUNDS_A:.*]] = omp.map.bounds   lower_bound({{.*}}) upper_bound({{.*}}) extent({{.*}}) stride({{.*}}) start_idx({{.*}})
317   !CHECK: %[[MAP_A:.*]] = omp.map.info var_ptr(%[[VAR_A_DECL]]#1 : !fir.ref<!fir.array<1024xi32>>, !fir.array<1024xi32>)   map_clauses(tofrom) capture(ByRef) bounds(%[[BOUNDS_A]]) -> !fir.ref<!fir.array<1024xi32>> {name = "a"}
318   !CHECK: omp.target_data   map_entries(%[[MAP_A]] : !fir.ref<!fir.array<1024xi32>>) {
319   !$omp target data map(a)
320   !CHECK: omp.terminator
321   !$omp end target data
322   !CHECK: }
323   !CHECK: %[[BOUNDS_B:.*]] = omp.map.bounds   lower_bound({{.*}}) upper_bound({{.*}}) extent({{.*}}) stride({{.*}}) start_idx({{.*}})
324   !CHECK: %[[MAP_B:.*]] = omp.map.info var_ptr(%[[VAR_B_DECL]]#1 : !fir.ref<!fir.array<1024xi32>>, !fir.array<1024xi32>)   map_clauses(always, from) capture(ByRef) bounds(%[[BOUNDS_B]]) -> !fir.ref<!fir.array<1024xi32>> {name = "b"}
325   !CHECK: omp.target_data   map_entries(%[[MAP_B]] : !fir.ref<!fir.array<1024xi32>>) {
326   !$omp target data map(always, from : b)
327   !CHECK: omp.terminator
328   !$omp end target data
329   !CHECK: }
330end subroutine omp_target_data_mt
331
332!===============================================================================
333! Target with region
334!===============================================================================
335
336!CHECK-LABEL: func.func @_QPomp_target() {
337subroutine omp_target
338   !CHECK: %[[VAL_1:.*]]:2 = hlfir.declare %{{.*}}(%{{.*}}) {uniq_name = "_QFomp_targetEa"} : (!fir.ref<!fir.array<1024xi32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<1024xi32>>, !fir.ref<!fir.array<1024xi32>>)
339   integer :: a(1024)
340   !CHECK: %[[BOUNDS:.*]] = omp.map.bounds   lower_bound({{.*}}) upper_bound({{.*}}) extent({{.*}}) stride({{.*}}) start_idx({{.*}})
341   !CHECK: %[[MAP:.*]] = omp.map.info var_ptr(%[[VAL_1]]#1 : !fir.ref<!fir.array<1024xi32>>, !fir.array<1024xi32>) map_clauses(tofrom) capture(ByRef) bounds(%[[BOUNDS]]) -> !fir.ref<!fir.array<1024xi32>> {name = "a"}
342   !CHECK: omp.target   map_entries(%[[MAP]] -> %[[ARG_0:.*]] : !fir.ref<!fir.array<1024xi32>>) {
343   !$omp target map(tofrom: a)
344      !CHECK: %[[VAL_7:.*]] = arith.constant 1024 : index
345      !CHECK: %[[VAL_2:.*]] = fir.shape %[[VAL_7]] : (index) -> !fir.shape<1>
346      !CHECK: %[[VAL_3:.*]]:2 = hlfir.declare %[[ARG_0]](%[[VAL_2]]) {uniq_name = "_QFomp_targetEa"} : (!fir.ref<!fir.array<1024xi32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<1024xi32>>, !fir.ref<!fir.array<1024xi32>>)
347      !CHECK: %[[VAL_4:.*]] = arith.constant 10 : i32
348      !CHECK: %[[VAL_5:.*]] = arith.constant 1 : index
349      !CHECK: %[[VAL_6:.*]] = hlfir.designate %[[VAL_3]]#0 (%[[VAL_5]])  : (!fir.ref<!fir.array<1024xi32>>, index) -> !fir.ref<i32>
350      !CHECK: hlfir.assign %[[VAL_4]] to %[[VAL_6]] : i32, !fir.ref<i32>
351      a(1) = 10
352      !CHECK: omp.terminator
353   !$omp end target
354   !CHECK: }
355end subroutine omp_target
356
357!===============================================================================
358! Target with region `depend` clause
359!===============================================================================
360
361!CHECK-LABEL: func.func @_QPomp_target_depend() {
362subroutine omp_target_depend
363   !CHECK: %[[EXTENT_A:.*]] = arith.constant 1024 : index
364   !CHECK: %[[A:.*]]:2 = hlfir.declare %{{.*}}(%{{.*}}) {uniq_name = "_QFomp_target_dependEa"} : (!fir.ref<!fir.array<1024xi32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<1024xi32>>, !fir.ref<!fir.array<1024xi32>>)
365   integer :: a(1024)
366   !CHECK: omp.task depend(taskdependout -> %[[A]]#1 : !fir.ref<!fir.array<1024xi32>>) private({{.*}}) {
367   !$omp task depend(out: a)
368   call foo(a)
369   !$omp end task
370   !CHECK: %[[STRIDE_A:.*]] = arith.constant 1 : index
371   !CHECK: %[[LBOUND_A:.*]] = arith.constant 0 : index
372   !CHECK: %[[UBOUND_A:.*]] = arith.subi %c1024, %c1 : index
373   !CHECK: %[[BOUNDS_A:.*]] = omp.map.bounds lower_bound(%[[LBOUND_A]] : index) upper_bound(%[[UBOUND_A]] : index) extent(%[[EXTENT_A]] : index) stride(%[[STRIDE_A]] : index) start_idx(%[[STRIDE_A]] : index)
374   !CHECK: %[[MAP_A:.*]] = omp.map.info var_ptr(%[[A]]#1 : !fir.ref<!fir.array<1024xi32>>, !fir.array<1024xi32>) map_clauses(tofrom) capture(ByRef) bounds(%[[BOUNDS_A]]) -> !fir.ref<!fir.array<1024xi32>> {name = "a"}
375   !CHECK: omp.target depend(taskdependin -> %[[A]]#1 : !fir.ref<!fir.array<1024xi32>>) map_entries(%[[MAP_A]] -> %[[BB0_ARG:.*]] : !fir.ref<!fir.array<1024xi32>>) {
376   !$omp target map(tofrom: a) depend(in: a)
377      a(1) = 10
378      !CHECK: omp.terminator
379   !$omp end target
380   !CHECK: }
381 end subroutine omp_target_depend
382
383!===============================================================================
384! Target implicit capture
385!===============================================================================
386
387!CHECK-LABEL: func.func @_QPomp_target_implicit() {
388subroutine omp_target_implicit
389   !CHECK: %[[VAL_0:.*]] = arith.constant 1024 : index
390   !CHECK: %[[VAL_1:.*]] = fir.alloca !fir.array<1024xi32> {bindc_name = "a", uniq_name = "_QFomp_target_implicitEa"}
391   !CHECK: %[[VAL_2:.*]] = fir.shape %[[VAL_0]] : (index) -> !fir.shape<1>
392   !CHECK: %[[VAL_3:.*]]:2 = hlfir.declare %[[VAL_1]](%[[VAL_2]]) {uniq_name = "_QFomp_target_implicitEa"} : (!fir.ref<!fir.array<1024xi32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<1024xi32>>, !fir.ref<!fir.array<1024xi32>>)
393   integer :: a(1024)
394   !CHECK: %[[VAL_4:.*]] = omp.map.info var_ptr(%[[VAL_3]]#1 : !fir.ref<!fir.array<1024xi32>>, !fir.array<1024xi32>)   map_clauses(implicit, tofrom) capture(ByRef) bounds(%{{.*}}) -> !fir.ref<!fir.array<1024xi32>> {name = "a"}
395   !CHECK: omp.target   map_entries(%[[VAL_4]] -> %[[VAL_6:.*]] : !fir.ref<!fir.array<1024xi32>>) {
396   !$omp target
397      !CHECK: %[[VAL_7:.*]] = arith.constant 1024 : index
398      !CHECK: %[[VAL_8:.*]] = fir.shape %[[VAL_7]] : (index) -> !fir.shape<1>
399      !CHECK: %[[VAL_9:.*]]:2 = hlfir.declare %[[VAL_6]](%[[VAL_8]]) {uniq_name = "_QFomp_target_implicitEa"} : (!fir.ref<!fir.array<1024xi32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<1024xi32>>, !fir.ref<!fir.array<1024xi32>>)
400      !CHECK: %[[VAL_10:.*]] = arith.constant 10 : i32
401      !CHECK: %[[VAL_11:.*]] = arith.constant 1 : index
402      !CHECK: %[[VAL_12:.*]] = hlfir.designate %[[VAL_9]]#0 (%[[VAL_11]])  : (!fir.ref<!fir.array<1024xi32>>, index) -> !fir.ref<i32>
403      !CHECK: hlfir.assign %[[VAL_10]] to %[[VAL_12]] : i32, !fir.ref<i32>
404      a(1) = 10
405      !CHECK: omp.terminator
406   !$omp end target
407   !CHECK: }
408end subroutine omp_target_implicit
409
410!===============================================================================
411! Target implicit capture nested
412!===============================================================================
413
414!CHECK-LABEL: func.func @_QPomp_target_implicit_nested() {
415subroutine omp_target_implicit_nested
416   integer::a, b
417   !CHECK: omp.target   map_entries(%{{.*}} -> %[[ARG0:.*]], %{{.*}} -> %[[ARG1:.*]] : !fir.ref<i32>, !fir.ref<i32>) {
418   !$omp target
419      !CHECK: %[[VAL_8:.*]]:2 = hlfir.declare %[[ARG0]] {uniq_name = "_QFomp_target_implicit_nestedEa"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
420      !CHECK: %[[VAL_9:.*]]:2 = hlfir.declare %[[ARG1]] {uniq_name = "_QFomp_target_implicit_nestedEb"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
421      !CHECK: %[[VAL_10:.*]] = arith.constant 10 : i32
422      !CHECK: hlfir.assign %[[VAL_10]] to %[[VAL_8]]#0 : i32, !fir.ref<i32>
423      a = 10
424      !CHECK: omp.parallel
425      !$omp parallel
426         !CHECK: %[[VAL_11:.*]] = arith.constant 20 : i32
427         !CHECK: hlfir.assign %[[VAL_11]] to %[[VAL_9]]#0 : i32, !fir.ref<i32>
428         b = 20
429         !CHECK: omp.terminator
430      !$omp end parallel
431      !CHECK: omp.terminator
432   !$omp end target
433   !CHECK: }
434end subroutine omp_target_implicit_nested
435
436!===============================================================================
437! Target implicit capture with bounds
438!===============================================================================
439
440!CHECK-LABEL: func.func @_QPomp_target_implicit_bounds(
441!CHECK: %[[VAL_0:.*]]: !fir.ref<i32> {fir.bindc_name = "n"}) {
442subroutine omp_target_implicit_bounds(n)
443   !CHECK: %[[VAL_COPY:.*]] = fir.alloca i32
444   !CHECK: %[[VAL_1:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %{{[0-9]+}} {uniq_name = "_QFomp_target_implicit_boundsEn"} : (!fir.ref<i32>, !fir.dscope) -> (!fir.ref<i32>, !fir.ref<i32>)
445   !CHECK: %[[VAL_2:.*]] = fir.load %[[VAL_1]]#0 : !fir.ref<i32>
446   !CHECK: fir.store %[[VAL_2]] to %[[VAL_COPY]] : !fir.ref<i32>
447   !CHECK: %[[VAL_3:.*]] = fir.convert %[[VAL_2]] : (i32) -> i64
448   !CHECK: %[[VAL_4:.*]] = fir.convert %[[VAL_3]] : (i64) -> index
449   !CHECK: %[[VAL_5:.*]] = arith.constant 0 : index
450   !CHECK: %[[VAL_6:.*]] = arith.cmpi sgt, %[[VAL_4]], %[[VAL_5]] : index
451   !CHECK: %[[VAL_7:.*]] = arith.select %[[VAL_6]], %[[VAL_4]], %[[VAL_5]] : index
452   !CHECK: %[[VAL_8:.*]] = fir.alloca !fir.array<?xi32>, %[[VAL_7]] {bindc_name = "a", uniq_name = "_QFomp_target_implicit_boundsEa"}
453   !CHECK: %[[VAL_9:.*]] = fir.shape %[[VAL_7]] : (index) -> !fir.shape<1>
454   !CHECK: %[[VAL_10:.*]]:2 = hlfir.declare %[[VAL_8]](%[[VAL_9]]) {uniq_name = "_QFomp_target_implicit_boundsEa"} : (!fir.ref<!fir.array<?xi32>>, !fir.shape<1>) -> (!fir.box<!fir.array<?xi32>>, !fir.ref<!fir.array<?xi32>>)
455   !CHECK: %[[UB:.*]] = arith.subi %[[VAL_7]], %c1{{.*}} : index
456
457   integer :: n
458   integer :: a(n)
459   !CHECK: %[[VAL_14:.*]] = omp.map.bounds lower_bound(%c0{{.*}} : index) upper_bound(%[[UB]] : index) extent(%[[VAL_7]] : index) stride(%c1{{.*}} : index) start_idx(%c1{{.*}} : index)
460   !CHECK: %[[VAL_15:.*]] = omp.map.info var_ptr(%[[VAL_10]]#1 : !fir.ref<!fir.array<?xi32>>, i32) map_clauses(implicit, tofrom) capture(ByRef) bounds(%[[VAL_14]]) -> !fir.ref<!fir.array<?xi32>> {name = "a"}
461   !CHECK: %[[VAL_16:.*]] = omp.map.info var_ptr(%[[VAL_COPY]] : !fir.ref<i32>, i32) map_clauses(implicit, exit_release_or_enter_alloc) capture(ByCopy) -> !fir.ref<i32> {name = ""}
462   !CHECK: omp.target map_entries(%[[VAL_15]] -> %[[VAL_17:.*]], %[[VAL_16]] -> %[[VAL_18:.*]] : !fir.ref<!fir.array<?xi32>>, !fir.ref<i32>) {
463   !$omp target
464      !CHECK: %[[VAL_19:.*]] = fir.load %[[VAL_18]] : !fir.ref<i32>
465      !CHECK: %[[VAL_20:.*]] = fir.convert %[[VAL_19]] : (i32) -> i64
466      !CHECK: %[[VAL_21:.*]] = arith.constant 0 : index
467      !CHECK: %[[VAL_22:.*]] = fir.convert %[[VAL_20]] : (i64) -> index
468      !CHECK: %[[VAL_23:.*]] = arith.cmpi sgt, %[[VAL_22]], %[[VAL_21]] : index
469      !CHECK: %[[VAL_24:.*]] = arith.select %[[VAL_23]], %[[VAL_22]], %[[VAL_21]] : index
470      !CHECK: %[[VAL_25:.*]] = fir.shape %[[VAL_24]] : (index) -> !fir.shape<1>
471      !CHECK: %[[VAL_26:.*]]:2 = hlfir.declare %[[VAL_17]](%[[VAL_25]]) {uniq_name = "_QFomp_target_implicit_boundsEa"} : (!fir.ref<!fir.array<?xi32>>, !fir.shape<1>) -> (!fir.box<!fir.array<?xi32>>, !fir.ref<!fir.array<?xi32>>)
472      !CHECK: %[[VAL_27:.*]] = arith.constant 22 : i32
473      !CHECK: %[[VAL_28:.*]] = arith.constant 11 : index
474      !CHECK: %[[VAL_29:.*]] = hlfir.designate %[[VAL_26]]#0 (%[[VAL_28]])  : (!fir.box<!fir.array<?xi32>>, index) -> !fir.ref<i32>
475      !CHECK: hlfir.assign %[[VAL_27]] to %[[VAL_29]] : i32, !fir.ref<i32>
476      a(11) = 22
477      !CHECK: omp.terminator
478   !$omp end target
479!CHECK: }
480end subroutine omp_target_implicit_bounds
481
482!===============================================================================
483! Target `thread_limit` clause
484!===============================================================================
485
486!CHECK-LABEL: func.func @_QPomp_target_thread_limit() {
487subroutine omp_target_thread_limit
488   integer :: a
489   !CHECK: %[[MAP:.*]] = omp.map.info var_ptr({{.*}})   map_clauses(tofrom) capture(ByRef) -> !fir.ref<i32> {name = "a"}
490   !CHECK: %[[VAL_1:.*]] = arith.constant 64 : i32
491   !CHECK: omp.target thread_limit(%[[VAL_1]] : i32) map_entries(%[[MAP]] -> %{{.*}} : !fir.ref<i32>) {
492   !$omp target map(tofrom: a) thread_limit(64)
493      a = 10
494   !CHECK: omp.terminator
495   !$omp end target
496   !CHECK: }
497end subroutine omp_target_thread_limit
498
499!===============================================================================
500! Target `use_device_ptr` clause
501!===============================================================================
502
503!CHECK-LABEL: func.func @_QPomp_target_device_ptr() {
504subroutine omp_target_device_ptr
505   use iso_c_binding, only : c_ptr, c_loc
506   type(c_ptr) :: a
507   integer, target :: b
508   !CHECK: %[[MAP:.*]] = omp.map.info var_ptr({{.*}})   map_clauses(tofrom) capture(ByRef) -> {{.*}} {name = "a"}
509   !CHECK: omp.target_data map_entries(%[[MAP]]{{.*}}) use_device_ptr({{.*}} -> %[[VAL_1:.*]] : !fir.ref<!fir.type<_QM__fortran_builtinsT__builtin_c_ptr{__address:i64}>>)
510   !$omp target data map(tofrom: a) use_device_ptr(a)
511   !CHECK: {{.*}} = fir.coordinate_of %[[VAL_1:.*]], {{.*}} : (!fir.ref<!fir.type<_QM__fortran_builtinsT__builtin_c_ptr{__address:i64}>>, !fir.field) -> !fir.ref<i64>
512      a = c_loc(b)
513   !CHECK: omp.terminator
514   !$omp end target data
515   !CHECK: }
516end subroutine omp_target_device_ptr
517
518 !===============================================================================
519 ! Target `use_device_addr` clause
520 !===============================================================================
521
522 !CHECK-LABEL: func.func @_QPomp_target_device_addr() {
523subroutine omp_target_device_addr
524   integer, pointer :: a
525   !CHECK: %[[VAL_0:.*]] = fir.alloca !fir.box<!fir.ptr<i32>> {bindc_name = "a", uniq_name = "_QFomp_target_device_addrEa"}
526   !CHECK: %[[VAL_0_DECL:.*]]:2 = hlfir.declare %0 {fortran_attrs = #fir.var_attrs<pointer>, uniq_name = "_QFomp_target_device_addrEa"} : (!fir.ref<!fir.box<!fir.ptr<i32>>>) -> (!fir.ref<!fir.box<!fir.ptr<i32>>>, !fir.ref<!fir.box<!fir.ptr<i32>>>)
527   !CHECK: %[[MAP_MEMBERS:.*]] = omp.map.info var_ptr({{.*}} : !fir.ref<!fir.box<!fir.ptr<i32>>>, i32) var_ptr_ptr({{.*}} : !fir.llvm_ptr<!fir.ref<i32>>) map_clauses(tofrom) capture(ByRef) -> !fir.llvm_ptr<!fir.ref<i32>> {name = ""}
528   !CHECK: %[[MAP:.*]] = omp.map.info var_ptr({{.*}} : !fir.ref<!fir.box<!fir.ptr<i32>>>, !fir.box<!fir.ptr<i32>>) map_clauses(to) capture(ByRef) members(%[[MAP_MEMBERS]] : [0] : !fir.llvm_ptr<!fir.ref<i32>>) -> !fir.ref<!fir.box<!fir.ptr<i32>>> {name = "a"}
529   !CHECK: %[[DEV_ADDR_MEMBERS:.*]] = omp.map.info var_ptr({{.*}} : !fir.ref<!fir.box<!fir.ptr<i32>>>, i32) var_ptr_ptr({{.*}} : !fir.llvm_ptr<!fir.ref<i32>>) map_clauses(tofrom) capture(ByRef) -> !fir.llvm_ptr<!fir.ref<i32>> {name = ""}
530   !CHECK: %[[DEV_ADDR:.*]] = omp.map.info var_ptr({{.*}} : !fir.ref<!fir.box<!fir.ptr<i32>>>, !fir.box<!fir.ptr<i32>>) map_clauses(to) capture(ByRef) members(%[[DEV_ADDR_MEMBERS]] : [0] : !fir.llvm_ptr<!fir.ref<i32>>) -> !fir.ref<!fir.box<!fir.ptr<i32>>> {name = "a"}
531   !CHECK: omp.target_data map_entries(%[[MAP]], %[[MAP_MEMBERS]] : {{.*}}) use_device_addr(%[[DEV_ADDR]] -> %[[ARG_0:.*]], %[[DEV_ADDR_MEMBERS]] -> %[[ARG_1:.*]] : !fir.ref<!fir.box<!fir.ptr<i32>>>, !fir.llvm_ptr<!fir.ref<i32>>) {
532   !$omp target data map(tofrom: a) use_device_addr(a)
533   !CHECK: %[[VAL_1_DECL:.*]]:2 = hlfir.declare %[[ARG_0]] {fortran_attrs = #fir.var_attrs<pointer>, uniq_name = "_QFomp_target_device_addrEa"} : (!fir.ref<!fir.box<!fir.ptr<i32>>>) -> (!fir.ref<!fir.box<!fir.ptr<i32>>>, !fir.ref<!fir.box<!fir.ptr<i32>>>)
534   !CHECK: %[[C10:.*]] = arith.constant 10 : i32
535   !CHECK: %[[A_BOX:.*]] = fir.load %[[VAL_1_DECL]]#0 : !fir.ref<!fir.box<!fir.ptr<i32>>>
536   !CHECK: %[[A_ADDR:.*]] = fir.box_addr %[[A_BOX]] : (!fir.box<!fir.ptr<i32>>) -> !fir.ptr<i32>
537   !CHECK: hlfir.assign %[[C10]] to %[[A_ADDR]] : i32, !fir.ptr<i32>
538   a = 10
539   !CHECK: omp.terminator
540   !$omp end target data
541   !CHECK: }
542end subroutine omp_target_device_addr
543
544
545!===============================================================================
546! Target Data with unstructured code
547!===============================================================================
548!CHECK-LABEL: func.func @_QPsb
549subroutine sb
550   integer :: i = 1
551   integer :: j = 11
552!CHECK: omp.target_data map_entries(%{{.*}}, %{{.*}} : !fir.ref<i32>, !fir.ref<i32>)
553   !$omp target data map(tofrom: i, j)
554     j = j - 1
555!CHECK: %[[J_VAL:.*]] = arith.subi
556!CHECK: hlfir.assign %[[J_VAL]]
557!CHECK: cf.br ^[[BB:.*]]
558!CHECK: ^[[BB]]:
559     goto 20
56020   i = i + 1
561!CHECK: %[[I_VAL:.*]] = arith.addi
562!CHECK: hlfir.assign %[[I_VAL]]
563!CHECK: omp.terminator
564   !$omp end target data
565end subroutine
566
567!===============================================================================
568! Target with parallel loop
569!===============================================================================
570
571!CHECK-LABEL: func.func @_QPomp_target_parallel_do() {
572subroutine omp_target_parallel_do
573   !CHECK: %[[C1024:.*]] = arith.constant 1024 : index
574   !CHECK: %[[VAL_0:.*]] = fir.alloca !fir.array<1024xi32> {bindc_name = "a", uniq_name = "_QFomp_target_parallel_doEa"}
575   !CHECK: %[[VAL_0_DECL:.*]]:2 = hlfir.declare %[[VAL_0]](%{{.*}}) {uniq_name = "_QFomp_target_parallel_doEa"} : (!fir.ref<!fir.array<1024xi32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<1024xi32>>, !fir.ref<!fir.array<1024xi32>>)
576   integer :: a(1024)
577   !CHECK: %[[VAL_1:.*]] = fir.alloca i32 {bindc_name = "i", uniq_name = "_QFomp_target_parallel_doEi"}
578   !CHECK: %[[VAL_1_DECL:.*]]:2 = hlfir.declare %[[VAL_1]] {uniq_name = "_QFomp_target_parallel_doEi"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
579   integer :: i
580   !CHECK: %[[C1:.*]] = arith.constant 1 : index
581   !CHECK: %[[C0:.*]] = arith.constant 0 : index
582   !CHECK: %[[SUB:.*]] = arith.subi %[[C1024]], %[[C1]] : index
583   !CHECK: %[[BOUNDS:.*]] = omp.map.bounds   lower_bound(%[[C0]] : index) upper_bound(%[[SUB]] : index) extent(%[[C1024]] : index) stride(%[[C1]] : index) start_idx(%[[C1]] : index)
584   !CHECK: %[[MAP:.*]] = omp.map.info var_ptr(%[[VAL_0_DECL]]#1 : !fir.ref<!fir.array<1024xi32>>, !fir.array<1024xi32>)   map_clauses(tofrom) capture(ByRef) bounds(%[[BOUNDS]]) -> !fir.ref<!fir.array<1024xi32>> {name = "a"}
585   !CHECK: omp.target   map_entries(%[[MAP]] -> %[[ARG_0:.*]], %{{.*}} -> %{{.*}} : !fir.ref<!fir.array<1024xi32>>, !fir.ref<i32>) {
586      !CHECK: %[[VAL_0_DECL:.*]]:2 = hlfir.declare %[[ARG_0]](%{{.*}}) {uniq_name = "_QFomp_target_parallel_doEa"} : (!fir.ref<!fir.array<1024xi32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<1024xi32>>, !fir.ref<!fir.array<1024xi32>>)
587      !CHECK: omp.parallel
588      !$omp target parallel do map(tofrom: a)
589         !CHECK: %[[I_PVT_ALLOCA:.*]] = fir.alloca i32 {bindc_name = "i", pinned, {{.*}}}
590         !CHECK: %[[I_PVT_DECL:.*]]:2 = hlfir.declare %[[I_PVT_ALLOCA]] {uniq_name = "_QFomp_target_parallel_doEi"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
591         !CHECK: omp.wsloop {
592         !CHECK-NEXT: omp.loop_nest (%[[I_VAL:.*]]) : i32
593         do i = 1, 1024
594           !CHECK:   fir.store %[[I_VAL]] to %[[I_PVT_DECL]]#1 : !fir.ref<i32>
595           !CHECK:   %[[C10:.*]] = arith.constant 10 : i32
596           !CHECK:   %[[I_PVT_VAL:.*]] = fir.load %[[I_PVT_DECL]]#0 : !fir.ref<i32>
597           !CHECK:   %[[I_VAL:.*]] = fir.convert %[[I_PVT_VAL]] : (i32) -> i64
598           !CHECK:   %[[A_I:.*]] = hlfir.designate %[[VAL_0_DECL]]#0 (%[[I_VAL]])  : (!fir.ref<!fir.array<1024xi32>>, i64) -> !fir.ref<i32>
599           !CHECK:   hlfir.assign %[[C10]] to %[[A_I]] : i32, !fir.ref<i32>
600            a(i) = 10
601         end do
602         !CHECK: omp.yield
603         !CHECK: }
604         !CHECK: }
605      !CHECK: omp.terminator
606      !CHECK: }
607   !CHECK: omp.terminator
608   !CHECK: }
609   !$omp end target parallel do
610end subroutine omp_target_parallel_do
611
612!===============================================================================
613! Target with unstructured code
614!===============================================================================
615
616!CHECK-LABEL:   func.func @_QPtarget_unstructured() {
617subroutine target_unstructured
618   !CHECK: %[[VAL_1:.*]]:2 = hlfir.declare %{{.*}} {uniq_name = "_QFtarget_unstructuredEi"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
619   integer :: i = 1
620   !CHECK: %[[VAL_3:.*]]:2 = hlfir.declare %{{.*}} {uniq_name = "_QFtarget_unstructuredEj"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
621   integer :: j = 11
622   !CHECK: %[[VAL_4:.*]] = omp.map.info var_ptr(%[[VAL_1]]#1 : !fir.ref<i32>, i32) map_clauses(implicit, exit_release_or_enter_alloc) capture(ByCopy) -> !fir.ref<i32> {name = "i"}
623   !CHECK: %[[VAL_5:.*]] = omp.map.info var_ptr(%[[VAL_3]]#1 : !fir.ref<i32>, i32) map_clauses(implicit, exit_release_or_enter_alloc) capture(ByCopy) -> !fir.ref<i32> {name = "j"}
624   !CHECK: omp.target map_entries(%[[VAL_4]] -> %[[VAL_6:.*]], %[[VAL_5]] -> %[[VAL_7:.*]] : !fir.ref<i32>, !fir.ref<i32>) {
625   !$omp target
626      !CHECK: %[[VAL_8:.*]]:2 = hlfir.declare %[[VAL_6]] {uniq_name = "_QFtarget_unstructuredEi"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
627      !CHECK: %[[VAL_9:.*]]:2 = hlfir.declare %[[VAL_7]] {uniq_name = "_QFtarget_unstructuredEj"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
628      !CHECK: ^bb1:
629      do while (i <= j)
630         !CHECK: ^bb2:
631         i = i + 1
632      end do
633      !CHECK: ^bb3:
634      !CHECK: omp.terminator
635   !$omp end target
636   !CHECK: }
637end subroutine target_unstructured
638