1 ! This test checks lowering of OpenACC data directive.
3 ! RUN: bbc -fopenacc -emit-fir %s -o - | FileCheck %s
6 real, dimension(10, 10) :: a
, b
, c
8 logical :: ifCondition
= .TRUE
.
10 !CHECK: [[A:%.*]] = fir.alloca !fir.array<10x10xf32> {{{.*}}uniq_name = "{{.*}}Ea"}
11 !CHECK: [[B:%.*]] = fir.alloca !fir.array<10x10xf32> {{{.*}}uniq_name = "{{.*}}Eb"}
12 !CHECK: [[C:%.*]] = fir.alloca !fir.array<10x10xf32> {{{.*}}uniq_name = "{{.*}}Ec"}
13 !CHECK: [[D:%.*]] = fir.alloca !fir.box<!fir.ptr<f32>> {bindc_name = "d", uniq_name = "{{.*}}Ed"}
14 !CHECK: [[E:%.*]] = fir.alloca !fir.box<!fir.ptr<f32>> {bindc_name = "e", uniq_name = "{{.*}}Ee"}
16 !$acc data if(.TRUE.) copy(a)
19 !CHECK: [[IF1:%.*]] = arith.constant true
20 !CHECK: acc.data if([[IF1]]) copy([[A]] : !fir.ref<!fir.array<10x10xf32>>) {
21 !CHECK: acc.terminator
24 !$acc data copy(a) if(ifCondition)
27 !CHECK: [[IFCOND:%.*]] = fir.load %{{.*}} : !fir.ref<!fir.logical<4>>
28 !CHECK: [[IF2:%.*]] = fir.convert [[IFCOND]] : (!fir.logical<4>) -> i1
29 !CHECK: acc.data if([[IF2]]) copy([[A]] : !fir.ref<!fir.array<10x10xf32>>) {
30 !CHECK: acc.terminator
33 !$acc data copy(a, b, c)
36 !CHECK: acc.data copy([[A]], [[B]], [[C]] : !fir.ref<!fir.array<10x10xf32>>, !fir.ref<!fir.array<10x10xf32>>, !fir.ref<!fir.array<10x10xf32>>) {
37 !CHECK: acc.terminator
40 !$acc data copy(a) copy(b) copy(c)
43 !CHECK: acc.data copy([[A]], [[B]], [[C]] : !fir.ref<!fir.array<10x10xf32>>, !fir.ref<!fir.array<10x10xf32>>, !fir.ref<!fir.array<10x10xf32>>) {
44 !CHECK: acc.terminator
47 !$acc data copyin(a) copyin(readonly: b, c)
50 !CHECK: acc.data copyin([[A]] : !fir.ref<!fir.array<10x10xf32>>) copyin_readonly([[B]], [[C]] : !fir.ref<!fir.array<10x10xf32>>, !fir.ref<!fir.array<10x10xf32>>) {
51 !CHECK: acc.terminator
54 !$acc data copyout(a) copyout(zero: b) copyout(c)
57 !CHECK: acc.data copyout([[A]], [[C]] : !fir.ref<!fir.array<10x10xf32>>, !fir.ref<!fir.array<10x10xf32>>) copyout_zero([[B]] : !fir.ref<!fir.array<10x10xf32>>) {
58 !CHECK: acc.terminator
61 !$acc data create(a, b) create(zero: c)
64 !CHECK: acc.data create([[A]], [[B]] : !fir.ref<!fir.array<10x10xf32>>, !fir.ref<!fir.array<10x10xf32>>) create_zero([[C]] : !fir.ref<!fir.array<10x10xf32>>) {
65 !CHECK: acc.terminator
68 !$acc data no_create(a, b) create(zero: c)
71 !CHECK: acc.data create_zero([[C]] : !fir.ref<!fir.array<10x10xf32>>) no_create([[A]], [[B]] : !fir.ref<!fir.array<10x10xf32>>, !fir.ref<!fir.array<10x10xf32>>) {
72 !CHECK: acc.terminator
75 !$acc data present(a, b, c)
78 !CHECK: acc.data present([[A]], [[B]], [[C]] : !fir.ref<!fir.array<10x10xf32>>, !fir.ref<!fir.array<10x10xf32>>, !fir.ref<!fir.array<10x10xf32>>) {
79 !CHECK: acc.terminator
82 !$acc data deviceptr(b, c)
85 !CHECK: acc.data deviceptr([[B]], [[C]] : !fir.ref<!fir.array<10x10xf32>>, !fir.ref<!fir.array<10x10xf32>>) {
86 !CHECK: acc.terminator
89 !$acc data attach(d, e)
92 !CHECK: acc.data attach([[D]], [[E]] : !fir.ref<!fir.box<!fir.ptr<f32>>>, !fir.ref<!fir.box<!fir.ptr<f32>>>) {
93 !CHECK: acc.terminator
96 end subroutine acc_data