1 ! This test checks lowering of Openacc serial loop combined directive.
3 ! RUN: bbc -fopenacc -emit-hlfir %s -o - | FileCheck %s
5 ! CHECK-LABEL: acc.private.recipe @privatization_ref_10xf32 : !fir.ref<!fir.array<10xf32>> init {
6 ! CHECK: ^bb0(%{{.*}}: !fir.ref<!fir.array<10xf32>>):
7 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}} : (index) -> !fir.shape<1>
8 ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.array<10xf32>
9 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]](%[[SHAPE]]) {uniq_name = "acc.private.init"} : (!fir.ref<!fir.array<10xf32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<10xf32>>, !fir.ref<!fir.array<10xf32>>)
10 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<!fir.array<10xf32>>
13 ! CHECK-LABEL: acc.firstprivate.recipe @firstprivatization_section_ext10_ref_10xf32 : !fir.ref<!fir.array<10xf32>> init {
14 ! CHECK: ^bb0(%{{.*}}: !fir.ref<!fir.array<10xf32>>):
15 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}} : (index) -> !fir.shape<1>
16 ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.array<10xf32>
17 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]](%[[SHAPE]]) {uniq_name = "acc.private.init"} : (!fir.ref<!fir.array<10xf32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<10xf32>>, !fir.ref<!fir.array<10xf32>>)
18 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<!fir.array<10xf32>>
20 ! CHECK: ^bb0(%arg0: !fir.ref<!fir.array<10xf32>>, %arg1: !fir.ref<!fir.array<10xf32>>):
21 ! CHECK: acc.terminator
24 ! CHECK-LABEL: func.func @_QPacc_serial_loop()
26 subroutine acc_serial_loop
32 integer :: numGangs
= 1
33 integer :: numWorkers
= 10
34 integer :: vectorLength
= 128
35 logical :: ifCondition
= .TRUE
.
36 integer, parameter :: n
= 10
37 real, dimension(n
) :: a
, b
, c
38 real, dimension(n
, n
) :: d
, e
40 integer :: reduction_i
43 integer :: gangNum
= 8
44 integer :: gangStatic
= 8
45 integer :: vectorNum
= 128
46 integer, parameter :: tileSize
= 2
48 ! CHECK: %[[A:.*]] = fir.alloca !fir.array<10xf32> {{{.*}}uniq_name = "{{.*}}Ea"}
49 ! CHECK: %[[DECLA:.*]]:2 = hlfir.declare %[[A]]
50 ! CHECK: %[[B:.*]] = fir.alloca !fir.array<10xf32> {{{.*}}uniq_name = "{{.*}}Eb"}
51 ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]]
52 ! CHECK: %[[C:.*]] = fir.alloca !fir.array<10xf32> {{{.*}}uniq_name = "{{.*}}Ec"}
53 ! CHECK: %[[DECLC:.*]]:2 = hlfir.declare %[[C]]
54 ! CHECK: %[[F:.*]] = fir.alloca !fir.box<!fir.ptr<f32>> {bindc_name = "f", uniq_name = "{{.*}}Ef"}
55 ! CHECK: %[[DECLF:.*]]:2 = hlfir.declare %[[F]]
56 ! CHECK: %[[G:.*]] = fir.alloca !fir.box<!fir.ptr<f32>> {bindc_name = "g", uniq_name = "{{.*}}Eg"}
57 ! CHECK: %[[DECLG:.*]]:2 = hlfir.declare %[[G]]
58 ! CHECK: %[[IFCONDITION:.*]] = fir.address_of(@{{.*}}ifcondition) : !fir.ref<!fir.logical<4>>
59 ! CHECK: %[[DECLIFCONDITION:.*]]:2 = hlfir.declare %[[IFCONDITION]]
74 !$acc serial loop async
86 ! CHECK-NEXT: } attributes {asyncAttr}
88 !$acc serial loop async(1)
93 ! CHECK: [[ASYNC1:%.*]] = arith.constant 1 : i32
94 ! CHECK: acc.serial async([[ASYNC1]] : i32) {
102 !$acc serial loop async(async)
107 ! CHECK: [[ASYNC2:%.*]] = fir.load %{{.*}} : !fir.ref<i32>
108 ! CHECK: acc.serial async([[ASYNC2]] : i32) {
116 !$acc serial loop wait
121 ! CHECK: acc.serial {
127 ! CHECK-NEXT: } attributes {waitAttr}
129 !$acc serial loop wait(1)
134 ! CHECK: [[WAIT1:%.*]] = arith.constant 1 : i32
135 ! CHECK: acc.serial wait([[WAIT1]] : i32) {
143 !$acc serial loop wait(1, 2)
148 ! CHECK: [[WAIT2:%.*]] = arith.constant 1 : i32
149 ! CHECK: [[WAIT3:%.*]] = arith.constant 2 : i32
150 ! CHECK: acc.serial wait([[WAIT2]], [[WAIT3]] : i32, i32) {
158 !$acc serial loop wait(wait1, wait2)
163 ! CHECK: [[WAIT4:%.*]] = fir.load %{{.*}} : !fir.ref<i32>
164 ! CHECK: [[WAIT5:%.*]] = fir.load %{{.*}} : !fir.ref<i32>
165 ! CHECK: acc.serial wait([[WAIT4]], [[WAIT5]] : i32, i32) {
173 !$acc serial loop if(.TRUE.)
178 ! CHECK: [[IF1:%.*]] = arith.constant true
179 ! CHECK: acc.serial if([[IF1]]) {
187 !$acc serial loop if(ifCondition)
192 ! CHECK: [[IFCOND:%.*]] = fir.load %{{.*}} : !fir.ref<!fir.logical<4>>
193 ! CHECK: [[IF2:%.*]] = fir.convert [[IFCOND]] : (!fir.logical<4>) -> i1
194 ! CHECK: acc.serial if([[IF2]]) {
202 !$acc serial loop self(.TRUE.)
207 ! CHECK: [[SELF1:%.*]] = arith.constant true
208 ! CHECK: acc.serial self([[SELF1]]) {
216 !$acc serial loop self
221 ! CHECK: acc.serial {
227 ! CHECK-NEXT: } attributes {selfAttr}
229 !$acc serial loop self(ifCondition)
234 ! CHECK: %[[SELF2:.*]] = fir.convert %[[DECLIFCONDITION]]#1 : (!fir.ref<!fir.logical<4>>) -> i1
235 ! CHECK: acc.serial self(%[[SELF2]]) {
243 !$acc serial loop copy(a, b)
248 ! CHECK: %[[COPYIN_A:.*]] = acc.copyin varPtr(%[[DECLA]]#1 : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<10xf32>> {dataClause = #acc<data_clause acc_copy>, name = "a"}
249 ! CHECK: %[[COPYIN_B:.*]] = acc.copyin varPtr(%[[DECLB]]#1 : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<10xf32>> {dataClause = #acc<data_clause acc_copy>, name = "b"}
250 ! CHECK: acc.serial dataOperands(%[[COPYIN_A]], %[[COPYIN_B]] : !fir.ref<!fir.array<10xf32>>, !fir.ref<!fir.array<10xf32>>) {
257 ! CHECK: acc.copyout accPtr(%[[COPYIN_A]] : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) to varPtr(%[[DECLA]]#1 : !fir.ref<!fir.array<10xf32>>) {dataClause = #acc<data_clause acc_copy>, name = "a"}
258 ! CHECK: acc.copyout accPtr(%[[COPYIN_B]] : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) to varPtr(%[[DECLB]]#1 : !fir.ref<!fir.array<10xf32>>) {dataClause = #acc<data_clause acc_copy>, name = "b"}
260 !$acc serial loop copy(a) copy(b)
265 ! CHECK: %[[COPYIN_A:.*]] = acc.copyin varPtr(%[[DECLA]]#1 : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<10xf32>> {dataClause = #acc<data_clause acc_copy>, name = "a"}
266 ! CHECK: %[[COPYIN_B:.*]] = acc.copyin varPtr(%[[DECLB]]#1 : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<10xf32>> {dataClause = #acc<data_clause acc_copy>, name = "b"}
267 ! CHECK: acc.serial dataOperands(%[[COPYIN_A]], %[[COPYIN_B]] : !fir.ref<!fir.array<10xf32>>, !fir.ref<!fir.array<10xf32>>) {
274 ! CHECK: acc.copyout accPtr(%[[COPYIN_A]] : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) to varPtr(%[[DECLA]]#1 : !fir.ref<!fir.array<10xf32>>) {dataClause = #acc<data_clause acc_copy>, name = "a"}
275 ! CHECK: acc.copyout accPtr(%[[COPYIN_B]] : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) to varPtr(%[[DECLB]]#1 : !fir.ref<!fir.array<10xf32>>) {dataClause = #acc<data_clause acc_copy>, name = "b"}
277 !$acc serial loop copyin(a) copyin(readonly: b)
282 ! CHECK: %[[COPYIN_A:.*]] = acc.copyin varPtr(%[[DECLA]]#1 : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<10xf32>> {name = "a"}
283 ! CHECK: %[[COPYIN_B:.*]] = acc.copyin varPtr(%[[DECLB]]#1 : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<10xf32>> {dataClause = #acc<data_clause acc_copyin_readonly>, name = "b"}
284 ! CHECK: acc.serial dataOperands(%[[COPYIN_A]], %[[COPYIN_B]] : !fir.ref<!fir.array<10xf32>>, !fir.ref<!fir.array<10xf32>>) {
292 !$acc serial loop copyout(a) copyout(zero: b)
297 ! CHECK: %[[CREATE_A:.*]] = acc.create varPtr(%[[DECLA]]#1 : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<10xf32>> {dataClause = #acc<data_clause acc_copyout>, name = "a"}
298 ! CHECK: %[[CREATE_B:.*]] = acc.create varPtr(%[[DECLB]]#1 : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<10xf32>> {dataClause = #acc<data_clause acc_copyout>, name = "b"}
299 ! CHECK: acc.serial dataOperands(%[[CREATE_A]], %[[CREATE_B]] : !fir.ref<!fir.array<10xf32>>, !fir.ref<!fir.array<10xf32>>) {
306 ! CHECK: acc.copyout accPtr(%[[CREATE_A]] : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) to varPtr(%[[DECLA]]#1 : !fir.ref<!fir.array<10xf32>>) {name = "a"}
307 ! CHECK: acc.copyout accPtr(%[[CREATE_B]] : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) to varPtr(%[[DECLB]]#1 : !fir.ref<!fir.array<10xf32>>) {name = "b"}
309 !$acc serial loop create(b) create(zero: a)
314 ! CHECK: %[[CREATE_B:.*]] = acc.create varPtr(%[[DECLB]]#1 : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<10xf32>> {name = "b"}
315 ! CHECK: %[[CREATE_A:.*]] = acc.create varPtr(%[[DECLA]]#1 : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<10xf32>> {dataClause = #acc<data_clause acc_create_zero>, name = "a"}
316 ! CHECK: acc.serial dataOperands(%[[CREATE_B]], %[[CREATE_A]] : !fir.ref<!fir.array<10xf32>>, !fir.ref<!fir.array<10xf32>>) {
323 ! CHECK: acc.delete accPtr(%[[CREATE_B]] : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) {dataClause = #acc<data_clause acc_create>, name = "b"}
324 ! CHECK: acc.delete accPtr(%[[CREATE_A]] : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) {dataClause = #acc<data_clause acc_create_zero>, name = "a"}
326 !$acc serial loop no_create(a, b)
331 ! CHECK: %[[NOCREATE_A:.*]] = acc.nocreate varPtr(%[[DECLA]]#1 : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<10xf32>> {name = "a"}
332 ! CHECK: %[[NOCREATE_B:.*]] = acc.nocreate varPtr(%[[DECLB]]#1 : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<10xf32>> {name = "b"}
333 ! CHECK: acc.serial dataOperands(%[[NOCREATE_A]], %[[NOCREATE_B]] : !fir.ref<!fir.array<10xf32>>, !fir.ref<!fir.array<10xf32>>) {
341 !$acc serial loop present(a, b)
346 ! CHECK: %[[PRESENT_A:.*]] = acc.present varPtr(%[[DECLA]]#1 : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<10xf32>> {name = "a"}
347 ! CHECK: %[[PRESENT_B:.*]] = acc.present varPtr(%[[DECLB]]#1 : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<10xf32>> {name = "b"}
348 ! CHECK: acc.serial dataOperands(%[[PRESENT_A]], %[[PRESENT_B]] : !fir.ref<!fir.array<10xf32>>, !fir.ref<!fir.array<10xf32>>) {
356 !$acc serial loop deviceptr(a) deviceptr(b)
361 ! CHECK: %[[DEVICEPTR_A:.*]] = acc.deviceptr varPtr(%[[DECLA]]#1 : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<10xf32>> {name = "a"}
362 ! CHECK: %[[DEVICEPTR_B:.*]] = acc.deviceptr varPtr(%[[DECLB]]#1 : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<10xf32>> {name = "b"}
363 ! CHECK: acc.serial dataOperands(%[[DEVICEPTR_A]], %[[DEVICEPTR_B]] : !fir.ref<!fir.array<10xf32>>, !fir.ref<!fir.array<10xf32>>) {
371 !$acc serial loop attach(f, g)
376 ! CHECK: %[[BOX_F:.*]] = fir.load %[[DECLF]]#1 : !fir.ref<!fir.box<!fir.ptr<f32>>>
377 ! CHECK: %[[BOX_ADDR_F:.*]] = fir.box_addr %[[BOX_F]] : (!fir.box<!fir.ptr<f32>>) -> !fir.ptr<f32>
378 ! CHECK: %[[ATTACH_F:.*]] = acc.attach varPtr(%[[BOX_ADDR_F]] : !fir.ptr<f32>) -> !fir.ptr<f32> {name = "f"}
379 ! CHECK: %[[BOX_G:.*]] = fir.load %[[DECLG]]#1 : !fir.ref<!fir.box<!fir.ptr<f32>>>
380 ! CHECK: %[[BOX_ADDR_G:.*]] = fir.box_addr %[[BOX_G]] : (!fir.box<!fir.ptr<f32>>) -> !fir.ptr<f32>
381 ! CHECK: %[[ATTACH_G:.*]] = acc.attach varPtr(%[[BOX_ADDR_G]] : !fir.ptr<f32>) -> !fir.ptr<f32> {name = "g"}
382 ! CHECK: acc.serial dataOperands(%[[ATTACH_F]], %[[ATTACH_G]] : !fir.ptr<f32>, !fir.ptr<f32>) {
390 !$acc serial loop private(a) firstprivate(b)
395 ! CHECK: %[[ACC_FPRIVATE_B:.*]] = acc.firstprivate varPtr(%[[DECLB]]#1 : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<10xf32>> {name = "b"}
396 ! CHECK: acc.serial firstprivate(@firstprivatization_section_ext10_ref_10xf32 -> %[[ACC_FPRIVATE_B]] : !fir.ref<!fir.array<10xf32>>) {
397 ! CHECK: %[[ACC_PRIVATE_A:.*]] = acc.private varPtr(%[[DECLA]]#1 : !fir.ref<!fir.array<10xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<10xf32>> {name = "a"}
398 ! CHECK: acc.loop private(@privatization_ref_10xf32 -> %[[ACC_PRIVATE_A]] : !fir.ref<!fir.array<10xf32>>) {
405 !$acc serial loop seq
410 ! CHECK: acc.serial {
414 ! CHECK-NEXT: } attributes {seq}
418 !$acc serial loop auto
423 ! CHECK: acc.serial {
427 ! CHECK-NEXT: } attributes {auto}
431 !$acc serial loop independent
436 ! CHECK: acc.serial {
440 ! CHECK-NEXT: } attributes {independent}
444 !$acc serial loop gang
449 ! CHECK: acc.serial {
450 ! CHECK: acc.loop gang {
457 !$acc serial loop gang(num: 8)
462 ! CHECK: acc.serial {
463 ! CHECK: [[GANGNUM1:%.*]] = arith.constant 8 : i32
464 ! CHECK-NEXT: acc.loop gang(num=[[GANGNUM1]] : i32) {
471 !$acc serial loop gang(num: gangNum)
476 ! CHECK: acc.serial {
477 ! CHECK: [[GANGNUM2:%.*]] = fir.load %{{.*}} : !fir.ref<i32>
478 ! CHECK-NEXT: acc.loop gang(num=[[GANGNUM2]] : i32) {
485 !$acc serial loop gang(num: gangNum, static: gangStatic)
490 ! CHECK: acc.serial {
491 ! CHECK: acc.loop gang(num=%{{.*}} : i32, static=%{{.*}} : i32) {
498 !$acc serial loop vector
502 ! CHECK: acc.serial {
503 ! CHECK: acc.loop vector {
510 !$acc serial loop vector(128)
515 ! CHECK: acc.serial {
516 ! CHECK: [[CONSTANT128:%.*]] = arith.constant 128 : i32
517 ! CHECK: acc.loop vector([[CONSTANT128]] : i32) {
524 !$acc serial loop vector(vectorLength)
529 ! CHECK: acc.serial {
530 ! CHECK: [[VECTORLENGTH:%.*]] = fir.load %{{.*}} : !fir.ref<i32>
531 ! CHECK: acc.loop vector([[VECTORLENGTH]] : i32) {
538 !$acc serial loop worker
543 ! CHECK: acc.serial {
544 ! CHECK: acc.loop worker {
551 !$acc serial loop worker(128)
556 ! CHECK: acc.serial {
557 ! CHECK: [[WORKER128:%.*]] = arith.constant 128 : i32
558 ! CHECK: acc.loop worker([[WORKER128]] : i32) {
565 !$acc serial loop collapse(2)
572 ! CHECK: acc.serial {
577 ! CHECK-NEXT: } attributes {collapse = 2 : i64}
589 ! CHECK: acc.serial {
601 !$acc serial loop tile(2)
606 ! CHECK: acc.serial {
607 ! CHECK: [[TILESIZE:%.*]] = arith.constant 2 : i32
608 ! CHECK: acc.loop tile([[TILESIZE]] : i32) {
615 !$acc serial loop tile(*)
620 ! CHECK: acc.serial {
621 ! CHECK: [[TILESIZEM1:%.*]] = arith.constant -1 : i32
622 ! CHECK: acc.loop tile([[TILESIZEM1]] : i32) {
629 !$acc serial loop tile(2, 2)
636 ! CHECK: acc.serial {
637 ! CHECK: [[TILESIZE1:%.*]] = arith.constant 2 : i32
638 ! CHECK: [[TILESIZE2:%.*]] = arith.constant 2 : i32
639 ! CHECK: acc.loop tile([[TILESIZE1]], [[TILESIZE2]] : i32, i32) {
646 !$acc serial loop tile(tileSize)
651 ! CHECK: acc.serial {
652 ! CHECK: acc.loop tile(%{{.*}} : i32) {
659 !$acc serial loop tile(tileSize, tileSize)
666 ! CHECK: acc.serial {
667 ! CHECK: acc.loop tile(%{{.*}}, %{{.*}} : i32, i32) {
674 !$acc serial loop reduction(+:reduction_r) reduction(*:reduction_i)
676 reduction_r
= reduction_r
+ a(i
)
680 ! CHECK: %[[COPYINREDR:.*]] = acc.copyin varPtr(%{{.*}} : !fir.ref<f32>) -> !fir.ref<f32> {dataClause = #acc<data_clause acc_reduction>, implicit = true, name = "reduction_r"}
681 ! CHECK: %[[COPYINREDI:.*]] = acc.copyin varPtr(%{{.*}} : !fir.ref<i32>) -> !fir.ref<i32> {dataClause = #acc<data_clause acc_reduction>, implicit = true, name = "reduction_i"}
682 ! CHECK: acc.serial dataOperands(%[[COPYINREDR]], %[[COPYINREDI]] : !fir.ref<f32>, !fir.ref<i32>) {
683 ! CHECK: acc.loop reduction(@reduction_add_ref_f32 -> %{{.*}} : !fir.ref<f32>, @reduction_mul_ref_i32 -> %{{.*}} : !fir.ref<i32>) {
689 ! CHECK: acc.copyout accPtr(%[[COPYINREDR]] : !fir.ref<f32>) to varPtr(%{{.*}} : !fir.ref<f32>) {dataClause = #acc<data_clause acc_reduction>, implicit = true, name = "reduction_r"}
690 ! CHECK: acc.copyout accPtr(%[[COPYINREDI]] : !fir.ref<i32>) to varPtr(%{{.*}} : !fir.ref<i32>) {dataClause = #acc<data_clause acc_reduction>, implicit = true, name = "reduction_i"}
692 end subroutine acc_serial_loop