1 ! This test checks lowering of OpenACC loop directive.
3 ! RUN: bbc -fopenacc -emit-fir %s -o - | FileCheck %s
8 integer, parameter :: n
= 10
9 real, dimension(n
) :: a
, b
10 real, dimension(n
, n
) :: c
, d
11 integer :: gangNum
= 8
12 integer :: gangStatic
= 8
13 integer :: vectorLength
= 128
14 integer, parameter :: tileSize
= 2
35 !CHECK-NEXT: } attributes {seq}
45 !CHECK-NEXT: } attributes {auto}
47 !$acc loop independent
55 !CHECK-NEXT: } attributes {independent}
62 !CHECK: acc.loop gang {
67 !$acc loop gang(num: 8)
72 !CHECK: [[GANGNUM1:%.*]] = arith.constant 8 : i32
73 !CHECK-NEXT: acc.loop gang(num=[[GANGNUM1]]: i32) {
78 !$acc loop gang(num: gangNum)
83 !CHECK: [[GANGNUM2:%.*]] = fir.load %{{.*}} : !fir.ref<i32>
84 !CHECK-NEXT: acc.loop gang(num=[[GANGNUM2]]: i32) {
89 !$acc loop gang(num: gangNum, static: gangStatic)
94 !CHECK: acc.loop gang(num=%{{.*}}: i32, static=%{{.*}}: i32) {
104 !CHECK: acc.loop vector {
109 !$acc loop vector(128)
114 !CHECK: [[CONSTANT128:%.*]] = arith.constant 128 : i32
115 !CHECK: acc.loop vector([[CONSTANT128]]: i32) {
120 !$acc loop vector(vectorLength)
125 !CHECK: [[VECTORLENGTH:%.*]] = fir.load %{{.*}} : !fir.ref<i32>
126 !CHECK: acc.loop vector([[VECTORLENGTH]]: i32) {
136 !CHECK: acc.loop worker {
141 !$acc loop worker(128)
146 !CHECK: [[WORKER128:%.*]] = arith.constant 128 : i32
147 !CHECK: acc.loop worker([[WORKER128]]: i32) {
152 !$acc loop private(c)
157 !CHECK: acc.loop private(%{{.*}}: !fir.ref<!fir.array<10x10xf32>>) {
162 !$acc loop private(c, d)
167 !CHECK: acc.loop private(%{{.*}}: !fir.ref<!fir.array<10x10xf32>>, %{{.*}}: !fir.ref<!fir.array<10x10xf32>>) {
172 !$acc loop private(c) private(d)
177 !CHECK: acc.loop private(%{{.*}}: !fir.ref<!fir.array<10x10xf32>>, %{{.*}}: !fir.ref<!fir.array<10x10xf32>>) {
186 !CHECK: [[TILESIZE:%.*]] = arith.constant 2 : i32
187 !CHECK: acc.loop tile([[TILESIZE]]: i32) {
196 !CHECK: [[TILESIZEM1:%.*]] = arith.constant -1 : i32
197 !CHECK: acc.loop tile([[TILESIZEM1]]: i32) {
202 !$acc loop tile(2, 2)
209 !CHECK: [[TILESIZE1:%.*]] = arith.constant 2 : i32
210 !CHECK: [[TILESIZE2:%.*]] = arith.constant 2 : i32
211 !CHECK: acc.loop tile([[TILESIZE1]]: i32, [[TILESIZE2]]: i32) {
216 !$acc loop tile(tileSize)
221 !CHECK: acc.loop tile(%{{.*}}: i32) {
226 !$acc loop tile(tileSize, tileSize)
233 !CHECK: acc.loop tile(%{{.*}}: i32, %{{.*}}: i32) {
238 !$acc loop collapse(2)
249 !CHECK-NEXT: } attributes {collapse = 2 : i64}