[LLVM] Fix Maintainers.md formatting (NFC)
[llvm-project.git] / flang / test / Lower / OpenACC / acc-reduction.f90
blob88c60a22b0fe8b94f141d6d1d2d288ab1e316ee8
1 ! This test checks lowering of OpenACC reduction clause.
3 ! RUN: bbc -fopenacc -emit-hlfir %s -o - | FileCheck %s
5 ! CHECK-LABEL: acc.reduction.recipe @reduction_max_box_UxUxf32 : !fir.box<!fir.array<?x?xf32>> reduction_operator <max> init {
6 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.box<!fir.array<?x?xf32>>):
7 ! CHECK: %[[CST:.*]] = arith.constant -1.401300e-45 : f32
8 ! CHECK: %[[DIMS0:.*]]:3 = fir.box_dims %[[ARG0]], %c0{{.*}} : (!fir.box<!fir.array<?x?xf32>>, index) -> (index, index, index)
9 ! CHECK: %[[DIMS1:.*]]:3 = fir.box_dims %[[ARG0]], %c1 : (!fir.box<!fir.array<?x?xf32>>, index) -> (index, index, index)
10 ! CHECK: %[[SHAPE:.*]] = fir.shape %[[DIMS0]]#1, %[[DIMS1]]#1 : (index, index) -> !fir.shape<2>
11 ! CHECK: %[[TEMP:.*]] = fir.allocmem !fir.array<?x?xf32>, %[[DIMS0]]#1, %[[DIMS1]]#1 {bindc_name = ".tmp", uniq_name = ""}
12 ! CHECK: %[[DECL:.*]]:2 = hlfir.declare %[[TEMP]](%[[SHAPE]]) {uniq_name = ".tmp"} : (!fir.heap<!fir.array<?x?xf32>>, !fir.shape<2>) -> (!fir.box<!fir.array<?x?xf32>>, !fir.heap<!fir.array<?x?xf32>>)
13 ! CHECK: hlfir.assign %[[CST]] to %[[DECL]]#0 : f32, !fir.box<!fir.array<?x?xf32>>
14 ! CHECK: acc.yield %[[DECL]]#0 : !fir.box<!fir.array<?x?xf32>>
15 ! CHECK: } combiner {
16 ! CHECK: ^bb0(%[[V1:.*]]: !fir.box<!fir.array<?x?xf32>>, %[[V2:.*]]: !fir.box<!fir.array<?x?xf32>>, %[[LB0:.*]]: index, %[[UB0:.*]]: index, %[[STEP0:.*]]: index, %[[LB1:.*]]: index, %[[UB1:.*]]: index, %[[STEP1:.*]]: index):
18 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}}, %{{.*}} : (index, index) -> !fir.shape<2>
19 ! CHECK: %[[DES_V1:.*]] = hlfir.designate %[[V1]] (%[[LB0]]:%[[UB0]]:%[[STEP0]], %[[LB1]]:%[[UB1]]:%[[STEP1]]) shape %[[SHAPE]] : (!fir.box<!fir.array<?x?xf32>>, index, index, index, index, index, index, !fir.shape<2>) -> !fir.box<!fir.array<?x?xf32>>
20 ! CHECK: %[[DES_V2:.*]] = hlfir.designate %[[V2]] (%[[LB0]]:%[[UB0]]:%[[STEP0]], %[[LB1]]:%[[UB1]]:%[[STEP1]]) shape %[[SHAPE]] : (!fir.box<!fir.array<?x?xf32>>, index, index, index, index, index, index, !fir.shape<2>) -> !fir.box<!fir.array<?x?xf32>>
21 ! CHECK: %[[ELEMENTAL:.*]] = hlfir.elemental %[[SHAPE]] unordered : (!fir.shape<2>) -> !hlfir.expr<?x?xf32> {
22 ! CHECK: ^bb0(%[[ARG0:.*]]: index, %[[ARG1:.*]]: index):
23 ! CHECK: %[[D1:.*]] = hlfir.designate %[[DES_V1]] (%[[ARG0]], %[[ARG1]]) : (!fir.box<!fir.array<?x?xf32>>, index, index) -> !fir.ref<f32>
24 ! CHECK: %[[D2:.*]] = hlfir.designate %[[DES_V2]] (%[[ARG0]], %[[ARG1]]) : (!fir.box<!fir.array<?x?xf32>>, index, index) -> !fir.ref<f32>
25 ! CHECK: %[[LOAD1:.*]] = fir.load %[[D1]] : !fir.ref<f32>
26 ! CHECK: %[[LOAD2:.*]] = fir.load %[[D2]] : !fir.ref<f32>
27 ! CHECK: %[[CMP:.*]] = arith.cmpf ogt, %[[LOAD1]], %[[LOAD2]] {{.*}} : f32
28 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMP]], %[[LOAD1]], %[[LOAD2]] : f32
29 ! CHECK: hlfir.yield_element %[[SELECT]] : f32
30 ! CHECK: }
31 ! CHECK: hlfir.assign %[[ELEMENTAL]] to %[[V1]] : !hlfir.expr<?x?xf32>, !fir.box<!fir.array<?x?xf32>>
32 ! CHECK: acc.yield %[[V1]] : !fir.box<!fir.array<?x?xf32>>
33 ! CHECK: }
35 ! CHECK-LABEL: acc.reduction.recipe @reduction_max_box_ptr_Uxf32 : !fir.box<!fir.ptr<!fir.array<?xf32>>> reduction_operator <max> init {
36 ! CHECK: ^bb0(%{{.*}}: !fir.box<!fir.ptr<!fir.array<?xf32>>>):
37 ! CHECK: } combiner {
38 ! CHECK: ^bb0(%{{.*}}: !fir.box<!fir.ptr<!fir.array<?xf32>>>, %{{.*}}: !fir.box<!fir.ptr<!fir.array<?xf32>>>, %{{.*}}: index, %{{.*}}: index, %{{.*}}: index):
39 ! CHECK: }
41 ! CHECK-LABEL: acc.reduction.recipe @reduction_max_box_heap_Uxf32 : !fir.box<!fir.heap<!fir.array<?xf32>>> reduction_operator <max> init {
42 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.box<!fir.heap<!fir.array<?xf32>>>):
43 ! CHECK: %[[CST:.*]] = arith.constant -1.401300e-45 : f32
44 ! CHECK: %[[C0:.*]] = arith.constant 0 : index
45 ! CHECK: %[[BOX_DIMS:.*]]:3 = fir.box_dims %[[ARG0]], %[[C0]] : (!fir.box<!fir.heap<!fir.array<?xf32>>>, index) -> (index, index, index)
46 ! CHECK: %[[SHAPE:.*]] = fir.shape %[[BOX_DIMS]]#1 : (index) -> !fir.shape<1>
47 ! CHECK: %[[TEMP:.*]] = fir.allocmem !fir.array<?xf32>, %[[BOX_DIMS]]#1 {bindc_name = ".tmp", uniq_name = ""}
48 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %2(%1) {uniq_name = ".tmp"} : (!fir.heap<!fir.array<?xf32>>, !fir.shape<1>) -> (!fir.box<!fir.array<?xf32>>, !fir.heap<!fir.array<?xf32>>)
49 ! CHECK: hlfir.assign %[[CST]] to %[[DECLARE]]#0 : f32, !fir.box<!fir.array<?xf32>>
50 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.box<!fir.array<?xf32>>
51 ! CHECK: } combiner {
52 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.box<!fir.heap<!fir.array<?xf32>>>, %[[ARG1:.*]]: !fir.box<!fir.heap<!fir.array<?xf32>>>, %[[ARG2:.*]]: index, %[[ARG3:.*]]: index, %[[ARG4:.*]]: index):
53 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}} : (index) -> !fir.shape<1>
54 ! CHECK: %[[DES_V1:.*]] = hlfir.designate %[[ARG0]] (%[[ARG2]]:%[[ARG3]]:%[[ARG4]]) shape %[[SHAPE]] : (!fir.box<!fir.heap<!fir.array<?xf32>>>, index, index, index, !fir.shape<1>) -> !fir.box<!fir.heap<!fir.array<?xf32>>>
55 ! CHECK: %[[DES_V2:.*]] = hlfir.designate %[[ARG1]] (%[[ARG2]]:%[[ARG3]]:%[[ARG4]]) shape %[[SHAPE]] : (!fir.box<!fir.heap<!fir.array<?xf32>>>, index, index, index, !fir.shape<1>) -> !fir.box<!fir.heap<!fir.array<?xf32>>>
56 ! CHECK: %[[ELEMENTAL:.*]] = hlfir.elemental %[[SHAPE]] unordered : (!fir.shape<1>) -> !hlfir.expr<?xf32> {
57 ! CHECK: ^bb0(%[[IV:.*]]: index):
58 ! CHECK: %[[V1:.*]] = hlfir.designate %[[DES_V1]] (%[[IV]]) : (!fir.box<!fir.heap<!fir.array<?xf32>>>, index) -> !fir.ref<f32>
59 ! CHECK: %[[V2:.*]] = hlfir.designate %[[DES_V2]] (%[[IV]]) : (!fir.box<!fir.heap<!fir.array<?xf32>>>, index) -> !fir.ref<f32>
60 ! CHECK: %[[LOAD_V1:.*]] = fir.load %[[V1]] : !fir.ref<f32>
61 ! CHECK: %[[LOAD_V2:.*]] = fir.load %[[V2]] : !fir.ref<f32>
62 ! CHECK: %[[CMP:.*]] = arith.cmpf ogt, %[[LOAD_V1]], %[[LOAD_V2]] {{.*}} : f32
63 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMP]], %[[LOAD_V1]], %[[LOAD_V2]] : f32
64 ! CHECK: hlfir.yield_element %[[SELECT]] : f32
65 ! CHECK: }
66 ! CHECK: hlfir.assign %[[ELEMENTAL]] to %[[ARG0]] : !hlfir.expr<?xf32>, !fir.box<!fir.heap<!fir.array<?xf32>>>
67 ! CHECK: acc.yield %[[ARG0]] : !fir.box<!fir.heap<!fir.array<?xf32>>>
68 ! CHECK: }
70 ! CHECK-LABEL: acc.reduction.recipe @reduction_add_section_lb1.ub3_box_Uxi32 : !fir.box<!fir.array<?xi32>> reduction_operator <add> init {
71 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.box<!fir.array<?xi32>>):
72 ! CHECK: %[[BOX_DIMS:.*]]:3 = fir.box_dims %[[ARG0]], %c0{{.*}} : (!fir.box<!fir.array<?xi32>>, index) -> (index, index, index)
73 ! CHECK: %[[SHAPE:.*]] = fir.shape %[[BOX_DIMS]]#1 : (index) -> !fir.shape<1>
74 ! CHECK: %[[TEMP:.*]] = fir.allocmem !fir.array<?xi32>, %0#1 {bindc_name = ".tmp", uniq_name = ""}
75 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[TEMP]](%[[SHAPE]]) {uniq_name = ".tmp"} : (!fir.heap<!fir.array<?xi32>>, !fir.shape<1>) -> (!fir.box<!fir.array<?xi32>>, !fir.heap<!fir.array<?xi32>>)
76 ! CHECK: hlfir.assign %c0{{.*}} to %[[DECLARE]]#0 : i32, !fir.box<!fir.array<?xi32>>
77 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.box<!fir.array<?xi32>>
78 ! CHECK: } combiner {
79 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.box<!fir.array<?xi32>>, %[[ARG1:.*]]: !fir.box<!fir.array<?xi32>>):
80 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}} : (index) -> !fir.shape<1>
81 ! CHECK: %[[DES1:.*]] = hlfir.designate %[[ARG0]] shape %[[SHAPE]] : (!fir.box<!fir.array<?xi32>>, !fir.shape<1>) -> !fir.box<!fir.array<?xi32>>
82 ! CHECK: %[[DES2:.*]] = hlfir.designate %[[ARG1]] shape %[[SHAPE]] : (!fir.box<!fir.array<?xi32>>, !fir.shape<1>) -> !fir.box<!fir.array<?xi32>>
83 ! CHECK: %[[ELEMENTAL:.*]] = hlfir.elemental %[[SHAPE]] unordered : (!fir.shape<1>) -> !hlfir.expr<?xi32> {
84 ! CHECK: ^bb0(%[[IV:.*]]: index):
85 ! CHECK: %[[DES_V1:.*]] = hlfir.designate %[[DES1]] (%[[IV]]) : (!fir.box<!fir.array<?xi32>>, index) -> !fir.ref<i32>
86 ! CHECK: %[[DES_V2:.*]] = hlfir.designate %[[DES2]] (%[[IV]]) : (!fir.box<!fir.array<?xi32>>, index) -> !fir.ref<i32>
87 ! CHECK: %[[LOAD_V1:.*]] = fir.load %[[DES_V1]] : !fir.ref<i32>
88 ! CHECK: %[[LOAD_V2:.*]] = fir.load %[[DES_V2]] : !fir.ref<i32>
89 ! CHECK: %[[COMBINED:.*]] = arith.addi %[[LOAD_V1]], %[[LOAD_V2]] : i32
90 ! CHECK: hlfir.yield_element %[[COMBINED]] : i32
91 ! CHECK: }
92 ! CHECK: hlfir.assign %[[ELEMENTAL]] to %[[ARG0]] : !hlfir.expr<?xi32>, !fir.box<!fir.array<?xi32>>
93 ! CHECK: acc.yield %[[ARG0]] : !fir.box<!fir.array<?xi32>>
94 ! CHECK: }
96 ! CHECK-LABEL: acc.reduction.recipe @reduction_max_box_Uxf32 : !fir.box<!fir.array<?xf32>> reduction_operator <max> init {
97 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.box<!fir.array<?xf32>>):
98 ! CHECK: %[[INIT_VALUE:.*]] = arith.constant -1.401300e-45 : f32
99 ! CHECK: %[[C0:.*]] = arith.constant 0 : index
100 ! CHECK: %[[BOX_DIMS:.*]]:3 = fir.box_dims %[[ARG0]], %[[C0]] : (!fir.box<!fir.array<?xf32>>, index) -> (index, index, index)
101 ! CHECK: %[[SHAPE:.*]] = fir.shape %[[BOX_DIMS]]#1 : (index) -> !fir.shape<1>
102 ! CHECK: %[[TEMP:.*]] = fir.allocmem !fir.array<?xf32>, %0#1 {bindc_name = ".tmp", uniq_name = ""}
103 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[TEMP]](%[[SHAPE]]) {uniq_name = ".tmp"} : (!fir.heap<!fir.array<?xf32>>, !fir.shape<1>) -> (!fir.box<!fir.array<?xf32>>, !fir.heap<!fir.array<?xf32>>)
104 ! CHECK: hlfir.assign %[[INIT_VALUE]] to %[[DECLARE]]#0 : f32, !fir.box<!fir.array<?xf32>>
105 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.box<!fir.array<?xf32>>
106 ! CHECK: } combiner {
107 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.box<!fir.array<?xf32>>, %[[ARG1:.*]]: !fir.box<!fir.array<?xf32>>
108 ! CHECK: %[[LEFT:.*]] = hlfir.designate %[[ARG0]] (%{{.*}}:%{{.*}}:%{{.*}}) shape %{{.*}} : (!fir.box<!fir.array<?xf32>>, index, index, index, !fir.shape<1>) -> !fir.box<!fir.array<?xf32>>
109 ! CHECK: %[[RIGHT:.*]] = hlfir.designate %[[ARG1]] (%{{.*}}:%{{.*}}:%{{.*}}) shape %{{.*}} : (!fir.box<!fir.array<?xf32>>, index, index, index, !fir.shape<1>) -> !fir.box<!fir.array<?xf32>>
110 ! CHECK: %[[ELEMENTAL:.*]] = hlfir.elemental %{{.*}} unordered : (!fir.shape<1>) -> !hlfir.expr<?xf32> {
111 ! CHECK: ^bb0(%{{.*}}: index):
112 ! CHECK: %[[DES_V1:.*]] = hlfir.designate %[[LEFT]] (%{{.*}}) : (!fir.box<!fir.array<?xf32>>, index) -> !fir.ref<f32>
113 ! CHECK: %[[DES_V2:.*]] = hlfir.designate %[[RIGHT]] (%{{.*}}) : (!fir.box<!fir.array<?xf32>>, index) -> !fir.ref<f32>
114 ! CHECK: %[[LOAD_V1:.*]] = fir.load %[[DES_V1]] : !fir.ref<f32>
115 ! CHECK: %[[LOAD_V2:.*]] = fir.load %[[DES_V2]] : !fir.ref<f32>
116 ! CHECK: %[[CMPF:.*]] = arith.cmpf ogt, %[[LOAD_V1]], %[[LOAD_V2]] {{.*}} : f32
117 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMPF]], %[[LOAD_V1]], %[[LOAD_V2]] : f32
118 ! CHECK: hlfir.yield_element %[[SELECT]] : f32
119 ! CHECK: }
120 ! CHECK: hlfir.assign %[[ELEMENTAL]] to %[[ARG0]] : !hlfir.expr<?xf32>, !fir.box<!fir.array<?xf32>>
121 ! CHECK: acc.yield %[[ARG0]] : !fir.box<!fir.array<?xf32>>
122 ! CHECK: }
124 ! CHECK-LABEL: acc.reduction.recipe @reduction_add_box_Uxi32 : !fir.box<!fir.array<?xi32>> reduction_operator <add> init {
125 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.box<!fir.array<?xi32>>):
126 ! CHECK: %[[INIT_VALUE:.*]] = arith.constant 0 : i32
127 ! CHECK: %[[C0:.*]] = arith.constant 0 : index
128 ! CHECK: %[[BOX_DIMS:.*]]:3 = fir.box_dims %[[ARG0]], %[[C0]] : (!fir.box<!fir.array<?xi32>>, index) -> (index, index, index)
129 ! CHECK: %[[SHAPE:.*]] = fir.shape %[[BOX_DIMS]]#1 : (index) -> !fir.shape<1>
130 ! CHECK: %[[TEMP:.*]] = fir.allocmem !fir.array<?xi32>, %[[BOX_DIMS]]#1 {bindc_name = ".tmp", uniq_name = ""}
131 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[TEMP]](%[[SHAPE]]) {uniq_name = ".tmp"} : (!fir.heap<!fir.array<?xi32>>, !fir.shape<1>) -> (!fir.box<!fir.array<?xi32>>, !fir.heap<!fir.array<?xi32>>)
132 ! CHECK: hlfir.assign %[[INIT_VALUE]] to %[[DECLARE]]#0 : i32, !fir.box<!fir.array<?xi32>>
133 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.box<!fir.array<?xi32>>
134 ! CHECK: } combiner {
135 ! CHECK: ^bb0(%[[V1:.*]]: !fir.box<!fir.array<?xi32>>, %[[V2:.*]]: !fir.box<!fir.array<?xi32>>
136 ! CHECK: %[[LEFT:.*]] = hlfir.designate %[[ARG0]] (%{{.*}}:%{{.*}}:%{{.*}}) shape %{{.*}} : (!fir.box<!fir.array<?xi32>>, index, index, index, !fir.shape<1>) -> !fir.box<!fir.array<?xi32>>
137 ! CHECK: %[[RIGHT:.*]] = hlfir.designate %[[ARG1]] (%{{.*}}:%{{.*}}:%{{.*}}) shape %{{.*}} : (!fir.box<!fir.array<?xi32>>, index, index, index, !fir.shape<1>) -> !fir.box<!fir.array<?xi32>>
138 ! CHECK: %[[ELEMENTAL:.*]] = hlfir.elemental %{{.*}} unordered : (!fir.shape<1>) -> !hlfir.expr<?xi32> {
139 ! CHECK: ^bb0(%{{.*}}: index):
140 ! CHECK: %[[DES_V1:.*]] = hlfir.designate %[[LEFT]] (%{{.*}}) : (!fir.box<!fir.array<?xi32>>, index) -> !fir.ref<i32>
141 ! CHECK: %[[DES_V2:.*]] = hlfir.designate %[[RIGHT]] (%{{.*}}) : (!fir.box<!fir.array<?xi32>>, index) -> !fir.ref<i32>
142 ! CHECK: %[[LOAD_V1:.*]] = fir.load %[[DES_V1]] : !fir.ref<i32>
143 ! CHECK: %[[LOAD_V2:.*]] = fir.load %[[DES_V2]] : !fir.ref<i32>
144 ! CHECK: %[[COMBINED:.*]] = arith.addi %[[LOAD_V1]], %[[LOAD_V2]] : i32
145 ! CHECK: hlfir.yield_element %[[COMBINED]] : i32
146 ! CHECK: }
147 ! CHECK: hlfir.assign %[[ELEMENTAL]] to %[[V1]] : !hlfir.expr<?xi32>, !fir.box<!fir.array<?xi32>>
148 ! CHECK: acc.yield %arg0 : !fir.box<!fir.array<?xi32>>
149 ! CHECK: }
151 ! CHECK-LABEL: acc.reduction.recipe @reduction_mul_ref_z32 : !fir.ref<complex<f32>> reduction_operator <mul> init {
152 ! CHECK: ^bb0(%{{.*}}: !fir.ref<complex<f32>>):
153 ! CHECK: %[[REAL:.*]] = arith.constant 1.000000e+00 : f32
154 ! CHECK: %[[IMAG:.*]] = arith.constant 0.000000e+00 : f32
155 ! CHECK: %[[UNDEF:.*]] = fir.undefined complex<f32>
156 ! CHECK: %[[UNDEF1:.*]] = fir.insert_value %[[UNDEF]], %[[REAL]], [0 : index] : (complex<f32>, f32) -> complex<f32>
157 ! CHECK: %[[UNDEF2:.*]] = fir.insert_value %[[UNDEF1]], %[[IMAG]], [1 : index] : (complex<f32>, f32) -> complex<f32>
158 ! CHECK: %[[ALLOCA:.*]] = fir.alloca complex<f32>
159 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref<complex<f32>>) -> (!fir.ref<complex<f32>>, !fir.ref<complex<f32>>)
160 ! CHECK: fir.store %[[UNDEF2]] to %[[DECLARE]]#0 : !fir.ref<complex<f32>>
161 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<complex<f32>>
162 ! CHECK: } combiner {
163 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<complex<f32>>, %[[ARG1:.*]]: !fir.ref<complex<f32>>):
164 ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref<complex<f32>>
165 ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref<complex<f32>>
166 ! CHECK: %[[COMBINED:.*]] = fir.mulc %[[LOAD0]], %[[LOAD1]] {fastmath = #arith.fastmath<contract>} : complex<f32>
167 ! CHECK: fir.store %[[COMBINED]] to %[[ARG0]] : !fir.ref<complex<f32>>
168 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<complex<f32>>
169 ! CHECK: }
171 ! CHECK-LABEL: acc.reduction.recipe @reduction_add_ref_z32 : !fir.ref<complex<f32>> reduction_operator <add> init {
172 ! CHECK: ^bb0(%{{.*}}: !fir.ref<complex<f32>>):
173 ! CHECK: %[[REAL:.*]] = arith.constant 0.000000e+00 : f32
174 ! CHECK: %[[IMAG:.*]] = arith.constant 0.000000e+00 : f32
175 ! CHECK: %[[UNDEF:.*]] = fir.undefined complex<f32>
176 ! CHECK: %[[UNDEF1:.*]] = fir.insert_value %[[UNDEF]], %[[REAL]], [0 : index] : (complex<f32>, f32) -> complex<f32>
177 ! CHECK: %[[UNDEF2:.*]] = fir.insert_value %[[UNDEF1]], %[[IMAG]], [1 : index] : (complex<f32>, f32) -> complex<f32>
178 ! CHECK: %[[ALLOCA:.*]] = fir.alloca complex<f32>
179 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref<complex<f32>>) -> (!fir.ref<complex<f32>>, !fir.ref<complex<f32>>)
180 ! CHECK: fir.store %[[UNDEF2]] to %[[DECLARE]]#0 : !fir.ref<complex<f32>>
181 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<complex<f32>>
182 ! CHECK: } combiner {
183 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<complex<f32>>, %[[ARG1:.*]]: !fir.ref<complex<f32>>):
184 ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref<complex<f32>>
185 ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref<complex<f32>>
186 ! CHECK: %[[COMBINED:.*]] = fir.addc %[[LOAD0]], %[[LOAD1]] {fastmath = #arith.fastmath<contract>} : complex<f32>
187 ! CHECK: fir.store %[[COMBINED]] to %[[ARG0]] : !fir.ref<complex<f32>>
188 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<complex<f32>>
189 ! CHECK: }
191 ! CHECK-LABEL: acc.reduction.recipe @reduction_neqv_ref_l32 : !fir.ref<!fir.logical<4>> reduction_operator <neqv> init {
192 ! CHECK: ^bb0(%{{.*}}: !fir.ref<!fir.logical<4>>):
193 ! CHECK: %[[CST:.*]] = arith.constant false
194 ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.logical<4>
195 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref<!fir.logical<4>>) -> (!fir.ref<!fir.logical<4>>, !fir.ref<!fir.logical<4>>)
196 ! CHECK: %[[CONVERT:.*]] = fir.convert %[[CST]] : (i1) -> !fir.logical<4>
197 ! CHECK: fir.store %[[CONVERT]] to %[[DECLARE]]#0 : !fir.ref<!fir.logical<4>>
198 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<!fir.logical<4>>
199 ! CHECK: } combiner {
200 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<!fir.logical<4>>, %[[ARG1:.*]]: !fir.ref<!fir.logical<4>>):
201 ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref<!fir.logical<4>>
202 ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref<!fir.logical<4>>
203 ! CHECK: %[[CONV0:.*]] = fir.convert %[[LOAD0]] : (!fir.logical<4>) -> i1
204 ! CHECK: %[[CONV1:.*]] = fir.convert %[[LOAD1]] : (!fir.logical<4>) -> i1
205 ! CHECK: %[[CMP:.*]] = arith.cmpi ne, %[[CONV0]], %[[CONV1]] : i1
206 ! CHECK: %[[CMP_CONV:.*]] = fir.convert %[[CMP]] : (i1) -> !fir.logical<4>
207 ! CHECK: fir.store %[[CMP_CONV]] to %[[ARG0]] : !fir.ref<!fir.logical<4>>
208 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<!fir.logical<4>>
209 ! CHECK: }
211 ! CHECK-LABEL: acc.reduction.recipe @reduction_eqv_ref_l32 : !fir.ref<!fir.logical<4>> reduction_operator <eqv> init {
212 ! CHECK: ^bb0(%{{.*}}: !fir.ref<!fir.logical<4>>):
213 ! CHECK: %[[CST:.*]] = arith.constant true
214 ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.logical<4>
215 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref<!fir.logical<4>>) -> (!fir.ref<!fir.logical<4>>, !fir.ref<!fir.logical<4>>)
216 ! CHECK: %[[CONVERT:.*]] = fir.convert %[[CST]] : (i1) -> !fir.logical<4>
217 ! CHECK: fir.store %[[CONVERT]] to %[[DECLARE]]#0 : !fir.ref<!fir.logical<4>>
218 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<!fir.logical<4>>
219 ! CHECK: } combiner {
220 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<!fir.logical<4>>, %[[ARG1:.*]]: !fir.ref<!fir.logical<4>>):
221 ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref<!fir.logical<4>>
222 ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref<!fir.logical<4>>
223 ! CHECK: %[[CONV0:.*]] = fir.convert %[[LOAD0]] : (!fir.logical<4>) -> i1
224 ! CHECK: %[[CONV1:.*]] = fir.convert %[[LOAD1]] : (!fir.logical<4>) -> i1
225 ! CHECK: %[[CMP:.*]] = arith.cmpi eq, %[[CONV0]], %[[CONV1]] : i1
226 ! CHECK: %[[CMP_CONV:.*]] = fir.convert %[[CMP]] : (i1) -> !fir.logical<4>
227 ! CHECK: fir.store %[[CMP_CONV]] to %[[ARG0]] : !fir.ref<!fir.logical<4>>
228 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<!fir.logical<4>>
229 ! CHECK: }
231 ! CHECK-LABEL: acc.reduction.recipe @reduction_lor_ref_l32 : !fir.ref<!fir.logical<4>> reduction_operator <lor> init {
232 ! CHECK: ^bb0(%{{.*}}: !fir.ref<!fir.logical<4>>):
233 ! CHECK: %[[CST:.*]] = arith.constant false
234 ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.logical<4>
235 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref<!fir.logical<4>>) -> (!fir.ref<!fir.logical<4>>, !fir.ref<!fir.logical<4>>)
236 ! CHECK: %[[CONVERT:.*]] = fir.convert %[[CST]] : (i1) -> !fir.logical<4>
237 ! CHECK: fir.store %[[CONVERT]] to %[[DECLARE]]#0 : !fir.ref<!fir.logical<4>>
238 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<!fir.logical<4>>
239 ! CHECK: } combiner {
240 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<!fir.logical<4>>, %[[ARG1:.*]]: !fir.ref<!fir.logical<4>>):
241 ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref<!fir.logical<4>>
242 ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref<!fir.logical<4>>
243 ! CHECK: %[[CONV0:.*]] = fir.convert %[[LOAD0]] : (!fir.logical<4>) -> i1
244 ! CHECK: %[[CONV1:.*]] = fir.convert %[[LOAD1]] : (!fir.logical<4>) -> i1
245 ! CHECK: %[[CMP:.*]] = arith.ori %[[CONV0]], %[[CONV1]] : i1
246 ! CHECK: %[[CMP_CONV:.*]] = fir.convert %[[CMP]] : (i1) -> !fir.logical<4>
247 ! CHECK: fir.store %[[CMP_CONV]] to %[[ARG0]] : !fir.ref<!fir.logical<4>>
248 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<!fir.logical<4>>
249 ! CHECK: }
251 ! CHECK-LABEL: acc.reduction.recipe @reduction_land_ref_l32 : !fir.ref<!fir.logical<4>> reduction_operator <land> init {
252 ! CHECK: ^bb0(%{{.*}}: !fir.ref<!fir.logical<4>>):
253 ! CHECK: %[[CST:.*]] = arith.constant true
254 ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.logical<4>
255 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref<!fir.logical<4>>) -> (!fir.ref<!fir.logical<4>>, !fir.ref<!fir.logical<4>>)
256 ! CHECK: %[[CONVERT:.*]] = fir.convert %[[CST]] : (i1) -> !fir.logical<4>
257 ! CHECK: fir.store %[[CONVERT]] to %[[DECLARE]]#0 : !fir.ref<!fir.logical<4>>
258 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<!fir.logical<4>>
259 ! CHECK: } combiner {
260 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<!fir.logical<4>>, %[[ARG1:.*]]: !fir.ref<!fir.logical<4>>):
261 ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref<!fir.logical<4>>
262 ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref<!fir.logical<4>>
263 ! CHECK: %[[CONV0:.*]] = fir.convert %[[LOAD0]] : (!fir.logical<4>) -> i1
264 ! CHECK: %[[CONV1:.*]] = fir.convert %[[LOAD1]] : (!fir.logical<4>) -> i1
265 ! CHECK: %[[CMP:.*]] = arith.andi %[[CONV0]], %[[CONV1]] : i1
266 ! CHECK: %[[CMP_CONV:.*]] = fir.convert %[[CMP]] : (i1) -> !fir.logical<4>
267 ! CHECK: fir.store %[[CMP_CONV]] to %[[ARG0]] : !fir.ref<!fir.logical<4>>
268 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<!fir.logical<4>>
269 ! CHECK: }
271 ! CHECK-LABEL: acc.reduction.recipe @reduction_xor_ref_i32 : !fir.ref<i32> reduction_operator <xor> init {
272 ! CHECK: ^bb0(%{{.*}}: !fir.ref<i32>):
273 ! CHECK: %[[CST:.*]] = arith.constant 0 : i32
274 ! CHECK: %[[ALLOCA:.*]] = fir.alloca i32
275 ! CHECK: %[[DECLARE]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
276 ! CHECK: fir.store %[[CST]] to %[[DECLARE]]#0 : !fir.ref<i32>
277 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<i32>
278 ! CHECK: } combiner {
279 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<i32>, %[[ARG1:.*]]: !fir.ref<i32>):
280 ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref<i32>
281 ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref<i32>
282 ! CHECK: %[[COMBINED:.*]] = arith.xori %[[LOAD0]], %[[LOAD1]] : i32
283 ! CHECK: fir.store %[[COMBINED]] to %[[ARG0]] : !fir.ref<i32>
284 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<i32>
285 ! CHECK: }
287 ! CHECK-LABEL: acc.reduction.recipe @reduction_ior_ref_i32 : !fir.ref<i32> reduction_operator <ior> init {
288 ! CHECK: ^bb0(%{{.*}}: !fir.ref<i32>):
289 ! CHECK: %[[CST:.*]] = arith.constant 0 : i32
290 ! CHECK: %[[ALLOCA:.*]] = fir.alloca i32
291 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
292 ! CHECK: fir.store %[[CST]] to %[[DECLARE:.*]]#0 : !fir.ref<i32>
293 ! CHECK: acc.yield %[[DECLARE:.*]]#0 : !fir.ref<i32>
294 ! CHECK: } combiner {
295 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<i32>, %[[ARG1:.*]]: !fir.ref<i32>):
296 ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref<i32>
297 ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref<i32>
298 ! CHECK: %[[COMBINED:.*]] = arith.ori %[[LOAD0]], %[[LOAD1]] : i32
299 ! CHECK: fir.store %[[COMBINED]] to %[[ARG0]] : !fir.ref<i32>
300 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<i32>
301 ! CHECK: }
303 ! CHECK-LABEL: acc.reduction.recipe @reduction_iand_ref_i32 : !fir.ref<i32> reduction_operator <iand> init {
304 ! CHECK: ^bb0(%{{.*}}: !fir.ref<i32>):
305 ! CHECK: %[[CST:.*]] = arith.constant -1 : i32
306 ! CHECK: %[[ALLOCA:.*]] = fir.alloca i32
307 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
308 ! CHECK: fir.store %[[CST]] to %[[DECLARE]]#0 : !fir.ref<i32>
309 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<i32>
310 ! CHECK: } combiner {
311 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<i32>, %[[ARG1:.*]]: !fir.ref<i32>):
312 ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref<i32>
313 ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref<i32>
314 ! CHECK: %[[COMBINED:.*]] = arith.andi %[[LOAD0]], %[[LOAD1]] : i32
315 ! CHECK: fir.store %[[COMBINED]] to %[[ARG0]] : !fir.ref<i32>
316 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<i32>
317 ! CHECK: }
319 ! CHECK-LABEL: acc.reduction.recipe @reduction_max_section_ext100_ref_100xf32 : !fir.ref<!fir.array<100xf32>> reduction_operator <max> init {
320 ! CHECK: ^bb0(%{{.*}}: !fir.ref<!fir.array<100xf32>>):
321 ! CHECK: %[[INIT:.*]] = arith.constant -1.401300e-45 : f32
322 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}} : (index) -> !fir.shape<1>
323 ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.array<100xf32>
324 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]](%[[SHAPE]]) {uniq_name = "acc.reduction.init"} : (!fir.ref<!fir.array<100xf32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<100xf32>>, !fir.ref<!fir.array<100xf32>>)
325 ! CHECK: %[[LB:.*]] = arith.constant 0 : index
326 ! CHECK: %[[UB:.*]] = arith.constant 99 : index
327 ! CHECK: %[[STEP:.*]] = arith.constant 1 : index
328 ! CHECK: fir.do_loop %[[IV:.*]] = %[[LB]] to %[[UB]] step %[[STEP]] {
329 ! CHECK: %[[COORD:.*]] = fir.coordinate_of %[[DECLARE]]#0, %[[IV]] : (!fir.ref<!fir.array<100xf32>>, index) -> !fir.ref<f32>
330 ! CHECK: fir.store %[[INIT]] to %[[COORD]] : !fir.ref<f32>
331 ! CHECK: }
332 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<!fir.array<100xf32>>
333 ! CHECK: } combiner {
334 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<!fir.array<100xf32>>, %[[ARG1:.*]]: !fir.ref<!fir.array<100xf32>>):
335 ! CHECK: %[[LB0:.*]] = arith.constant 0 : index
336 ! CHECK: %[[UB0:.*]] = arith.constant 99 : index
337 ! CHECK: %[[STEP0:.*]] = arith.constant 1 : index
338 ! CHECK: fir.do_loop %[[IV0:.*]] = %[[LB0]] to %[[UB0]] step %[[STEP0]] {
339 ! CHECK: %[[COORD1:.*]] = fir.coordinate_of %[[ARG0]], %[[IV0]] : (!fir.ref<!fir.array<100xf32>>, index) -> !fir.ref<f32>
340 ! CHECK: %[[COORD2:.*]] = fir.coordinate_of %[[ARG1]], %[[IV0]] : (!fir.ref<!fir.array<100xf32>>, index) -> !fir.ref<f32>
341 ! CHECK: %[[LOAD1:.*]] = fir.load %[[COORD1]] : !fir.ref<f32>
342 ! CHECK: %[[LOAD2:.*]] = fir.load %[[COORD2]] : !fir.ref<f32>
343 ! CHECK: %[[CMP:.*]] = arith.cmpf ogt, %[[LOAD1]], %[[LOAD2]] {{.*}} : f32
344 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMP]], %[[LOAD1]], %[[LOAD2]] : f32
345 ! CHECK: fir.store %[[SELECT]] to %[[COORD1]] : !fir.ref<f32>
346 ! CHECK: }
347 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<!fir.array<100xf32>>
348 ! CHECK: }
350 ! CHECK-LABEL: acc.reduction.recipe @reduction_max_ref_f32 : !fir.ref<f32> reduction_operator <max> init {
351 ! CHECK: ^bb0(%{{.*}}: !fir.ref<f32>):
352 ! CHECK: %[[INIT:.*]] = arith.constant -1.401300e-45 : f32
353 ! CHECK: %[[ALLOCA:.*]] = fir.alloca f32
354 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %0 {uniq_name = "acc.reduction.init"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
355 ! CHECK: fir.store %[[INIT]] to %[[DECLARE]]#0 : !fir.ref<f32>
356 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<f32>
357 ! CHECK: } combiner {
358 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<f32>, %[[ARG1:.*]]: !fir.ref<f32>):
359 ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref<f32>
360 ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref<f32>
361 ! CHECK: %[[CMP:.*]] = arith.cmpf ogt, %[[LOAD0]], %[[LOAD1]] {{.*}} : f32
362 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMP]], %[[LOAD0]], %[[LOAD1]] : f32
363 ! CHECK: fir.store %[[SELECT]] to %[[ARG0]] : !fir.ref<f32>
364 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<f32>
365 ! CHECK: }
367 ! CHECK-LABEL: acc.reduction.recipe @reduction_max_section_ext100xext10_ref_100x10xi32 : !fir.ref<!fir.array<100x10xi32>> reduction_operator <max> init {
368 ! CHECK: ^bb0(%arg0: !fir.ref<!fir.array<100x10xi32>>):
369 ! CHECK: %[[INIT:.*]] = arith.constant -2147483648 : i32
370 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}}, %{{.*}} : (index, index) -> !fir.shape<2>
371 ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.array<100x10xi32>
372 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]](%[[SHAPE]]) {uniq_name = "acc.reduction.init"} : (!fir.ref<!fir.array<100x10xi32>>, !fir.shape<2>) -> (!fir.ref<!fir.array<100x10xi32>>, !fir.ref<!fir.array<100x10xi32>>)
373 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<!fir.array<100x10xi32>>
374 ! CHECK: } combiner {
375 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<!fir.array<100x10xi32>>, %[[ARG1:.*]]: !fir.ref<!fir.array<100x10xi32>>):
376 ! CHECK: %[[LB0:.*]] = arith.constant 0 : index
377 ! CHECK: %[[UB0:.*]] = arith.constant 9 : index
378 ! CHECK: %[[STEP0:.*]] = arith.constant 1 : index
379 ! CHECK: fir.do_loop %[[IV0:.*]] = %[[LB0]] to %[[UB0]] step %[[STEP0]] {
380 ! CHECK: %[[LB1:.*]] = arith.constant 0 : index
381 ! CHECK: %[[UB1:.*]] = arith.constant 99 : index
382 ! CHECK: %[[STEP1:.*]] = arith.constant 1 : index
383 ! CHECK: fir.do_loop %[[IV1:.*]] = %[[LB1]] to %[[UB1]] step %[[STEP1]] {
384 ! CHECK: %[[COORD1:.*]] = fir.coordinate_of %[[ARG0:.*]], %[[IV0]], %[[IV1]] : (!fir.ref<!fir.array<100x10xi32>>, index, index) -> !fir.ref<i32>
385 ! CHECK: %[[COORD2:.*]] = fir.coordinate_of %[[ARG1:.*]], %[[IV0]], %[[IV1]] : (!fir.ref<!fir.array<100x10xi32>>, index, index) -> !fir.ref<i32>
386 ! CHECK: %[[LOAD1:.*]] = fir.load %[[COORD1]] : !fir.ref<i32>
387 ! CHECK: %[[LOAD2:.*]] = fir.load %[[COORD2]] : !fir.ref<i32>
388 ! CHECK: %[[CMP:.*]] = arith.cmpi sgt, %[[LOAD1]], %[[LOAD2]] : i32
389 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMP]], %[[LOAD1]], %[[LOAD2]] : i32
390 ! CHECK: fir.store %[[SELECT]] to %[[COORD1]] : !fir.ref<i32>
391 ! CHECK: }
392 ! CHECK: }
393 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<!fir.array<100x10xi32>>
394 ! CHECK: }
396 ! CHECK-LABEL: acc.reduction.recipe @reduction_max_ref_i32 : !fir.ref<i32> reduction_operator <max> init {
397 ! CHECK: ^bb0(%arg0: !fir.ref<i32>):
398 ! CHECK: %[[INIT:.*]] = arith.constant -2147483648 : i32
399 ! CHECK: %[[ALLOCA:.*]] = fir.alloca i32
400 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
401 ! CHECK: fir.store %[[INIT]] to %[[DECLARE]]#0 : !fir.ref<i32>
402 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<i32>
403 ! CHECK: } combiner {
404 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<i32>, %[[ARG1:.*]]: !fir.ref<i32>):
405 ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref<i32>
406 ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref<i32>
407 ! CHECK: %[[CMP:.*]] = arith.cmpi sgt, %[[LOAD0]], %[[LOAD1]] : i32
408 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMP]], %[[LOAD0]], %[[LOAD1]] : i32
409 ! CHECK: fir.store %[[SELECT]] to %[[ARG0]] : !fir.ref<i32>
410 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<i32>
411 ! CHECK: }
413 ! CHECK-LABEL: acc.reduction.recipe @reduction_min_section_ext100xext10_ref_100x10xf32 : !fir.ref<!fir.array<100x10xf32>> reduction_operator <min> init {
414 ! CHECK: ^bb0(%{{.*}}: !fir.ref<!fir.array<100x10xf32>>):
415 ! CHECK: %[[INIT:.*]] = arith.constant 3.40282347E+38 : f32
416 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}}, %{{.*}} : (index, index) -> !fir.shape<2>
417 ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.array<100x10xf32>
418 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]](%[[SHAPE]]) {uniq_name = "acc.reduction.init"} : (!fir.ref<!fir.array<100x10xf32>>, !fir.shape<2>) -> (!fir.ref<!fir.array<100x10xf32>>, !fir.ref<!fir.array<100x10xf32>>)
419 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<!fir.array<100x10xf32>>
420 ! CHECK: } combiner {
421 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<!fir.array<100x10xf32>>, %[[ARG1:.*]]: !fir.ref<!fir.array<100x10xf32>>):
422 ! CHECK: %[[LB0:.*]] = arith.constant 0 : index
423 ! CHECK: %[[UB0:.*]] = arith.constant 9 : index
424 ! CHECK: %[[STEP0:.*]] = arith.constant 1 : index
425 ! CHECK: fir.do_loop %[[IV0:.*]] = %[[LB0]] to %[[UB0]] step %[[STEP0]] {
426 ! CHECK: %[[LB1:.*]] = arith.constant 0 : index
427 ! CHECK: %[[UB1:.*]] = arith.constant 99 : index
428 ! CHECK: %[[STEP1:.*]] = arith.constant 1 : index
429 ! CHECK: fir.do_loop %[[IV1:.*]] = %[[LB1]] to %[[UB1]] step %[[STEP1]] {
430 ! CHECK: %[[COORD1:.*]] = fir.coordinate_of %[[ARG0]], %[[IV0]], %[[IV1]] : (!fir.ref<!fir.array<100x10xf32>>, index, index) -> !fir.ref<f32>
431 ! CHECK: %[[COORD2:.*]] = fir.coordinate_of %[[ARG1]], %[[IV0]], %[[IV1]] : (!fir.ref<!fir.array<100x10xf32>>, index, index) -> !fir.ref<f32>
432 ! CHECK: %[[LOAD1:.*]] = fir.load %[[COORD1]] : !fir.ref<f32>
433 ! CHECK: %[[LOAD2:.*]] = fir.load %[[COORD2]] : !fir.ref<f32>
434 ! CHECK: %[[CMP:.*]] = arith.cmpf olt, %[[LOAD1]], %[[LOAD2]] {{.*}} : f32
435 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMP]], %[[LOAD1]], %[[LOAD2]] : f32
436 ! CHECK: fir.store %[[SELECT]] to %[[COORD1]] : !fir.ref<f32>
437 ! CHECK: }
438 ! CHECK: }
439 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<!fir.array<100x10xf32>>
440 ! CHECK: }
442 ! CHECK-LABEL: acc.reduction.recipe @reduction_min_ref_f32 : !fir.ref<f32> reduction_operator <min> init {
443 ! CHECK: ^bb0(%{{.*}}: !fir.ref<f32>):
444 ! CHECK: %[[INIT:.*]] = arith.constant 3.40282347E+38 : f32
445 ! CHECK: %[[ALLOCA:.*]] = fir.alloca f32
446 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
447 ! CHECK: fir.store %[[INIT]] to %[[DECLARE]]#0 : !fir.ref<f32>
448 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<f32>
449 ! CHECK: } combiner {
450 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<f32>, %[[ARG1:.*]]: !fir.ref<f32>):
451 ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref<f32>
452 ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref<f32>
453 ! CHECK: %[[CMP:.*]] = arith.cmpf olt, %[[LOAD0]], %[[LOAD1]] {{.*}} : f32
454 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMP]], %[[LOAD0]], %[[LOAD1]] : f32
455 ! CHECK: fir.store %[[SELECT]] to %[[ARG0]] : !fir.ref<f32>
456 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<f32>
457 ! CHECK: }
459 ! CHECK-LABEL: acc.reduction.recipe @reduction_min_section_ext100_ref_100xi32 : !fir.ref<!fir.array<100xi32>> reduction_operator <min> init {
460 ! CHECK: ^bb0(%{{.*}}: !fir.ref<!fir.array<100xi32>>):
461 ! CHECK: %[[INIT:.*]] = arith.constant 2147483647 : i32
462 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}} : (index) -> !fir.shape<1>
463 ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.array<100xi32>
464 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]](%[[SHAPE]]) {uniq_name = "acc.reduction.init"} : (!fir.ref<!fir.array<100xi32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<100xi32>>, !fir.ref<!fir.array<100xi32>>)
465 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<!fir.array<100xi32>>
466 ! CHECK: } combiner {
467 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<!fir.array<100xi32>>, %[[ARG1:.*]]: !fir.ref<!fir.array<100xi32>>):
468 ! CHECK: %[[LB0:.*]] = arith.constant 0 : index
469 ! CHECK: %[[UB0:.*]] = arith.constant 99 : index
470 ! CHECK: %[[STEP0:.*]] = arith.constant 1 : index
471 ! CHECK: fir.do_loop %[[IV0:.*]] = %[[LB0]] to %[[UB0]] step %[[STEP0]] {
472 ! CHECK: %[[COORD1:.*]] = fir.coordinate_of %[[ARG0]], %[[IV0]] : (!fir.ref<!fir.array<100xi32>>, index) -> !fir.ref<i32>
473 ! CHECK: %[[COORD2:.*]] = fir.coordinate_of %[[ARG1]], %[[IV0]] : (!fir.ref<!fir.array<100xi32>>, index) -> !fir.ref<i32>
474 ! CHECK: %[[LOAD1:.*]] = fir.load %[[COORD1]] : !fir.ref<i32>
475 ! CHECK: %[[LOAD2:.*]] = fir.load %[[COORD2]] : !fir.ref<i32>
476 ! CHECK: %[[CMP:.*]] = arith.cmpi slt, %[[LOAD1]], %[[LOAD2]] : i32
477 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMP]], %[[LOAD1]], %[[LOAD2]] : i32
478 ! CHECK: fir.store %[[SELECT]] to %[[COORD1]] : !fir.ref<i32>
479 ! CHECK: }
480 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<!fir.array<100xi32>>
481 ! CHECK: }
483 ! CHECK-LABEL: acc.reduction.recipe @reduction_min_ref_i32 : !fir.ref<i32> reduction_operator <min> init {
484 ! CHECK: ^bb0(%{{.*}}: !fir.ref<i32>):
485 ! CHECK: %[[INIT:.*]] = arith.constant 2147483647 : i32
486 ! CHECK: %[[ALLOCA:.*]] = fir.alloca i32
487 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
488 ! CHECK: fir.store %[[INIT]] to %[[DECLARE]]#0 : !fir.ref<i32>
489 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<i32>
490 ! CHECK: } combiner {
491 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<i32>, %[[ARG1:.*]]: !fir.ref<i32>):
492 ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref<i32>
493 ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref<i32>
494 ! CHECK: %[[CMP:.*]] = arith.cmpi slt, %[[LOAD0]], %[[LOAD1]] : i32
495 ! CHECK: %[[SELECT:.*]] = arith.select %[[CMP]], %[[LOAD0]], %[[LOAD1]] : i32
496 ! CHECK: fir.store %[[SELECT]] to %[[ARG0]] : !fir.ref<i32>
497 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<i32>
498 ! CHECK: }
500 ! CHECK-LABEL: acc.reduction.recipe @reduction_mul_ref_f32 : !fir.ref<f32> reduction_operator <mul> init {
501 ! CHECK: ^bb0(%{{.*}}: !fir.ref<f32>):
502 ! CHECK: %[[INIT:.*]] = arith.constant 1.000000e+00 : f32
503 ! CHECK: %[[ALLOCA:.*]] = fir.alloca f32
504 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
505 ! CHECK: fir.store %[[INIT]] to %[[DECLARE]]#0 : !fir.ref<f32>
506 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<f32>
507 ! CHECK: } combiner {
508 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<f32>, %[[ARG1:.*]]: !fir.ref<f32>):
509 ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref<f32>
510 ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref<f32>
511 ! CHECK: %[[COMBINED:.*]] = arith.mulf %[[LOAD0]], %[[LOAD1]] fastmath<contract> : f32
512 ! CHECK: fir.store %[[COMBINED]] to %[[ARG0]] : !fir.ref<f32>
513 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<f32>
514 ! CHECK: }
516 ! CHECK-LABEL: acc.reduction.recipe @reduction_mul_section_ext100_ref_100xi32 : !fir.ref<!fir.array<100xi32>> reduction_operator <mul> init {
517 ! CHECK: ^bb0(%{{.*}}: !fir.ref<!fir.array<100xi32>>):
518 ! CHECK: %[[INIT:.*]] = arith.constant 1 : i32
519 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}} : (index) -> !fir.shape<1>
520 ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.array<100xi32>
521 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]](%[[SHAPE]]) {uniq_name = "acc.reduction.init"} : (!fir.ref<!fir.array<100xi32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<100xi32>>, !fir.ref<!fir.array<100xi32>>)
522 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<!fir.array<100xi32>>
523 ! CHECK: } combiner {
524 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<!fir.array<100xi32>>, %[[ARG1:.*]]: !fir.ref<!fir.array<100xi32>>):
525 ! CHECK: %[[LB:.*]] = arith.constant 0 : index
526 ! CHECK: %[[UB:.*]] = arith.constant 99 : index
527 ! CHECK: %[[STEP:.*]] = arith.constant 1 : index
528 ! CHECK: fir.do_loop %[[IV:.*]] = %[[LB]] to %[[UB]] step %[[STEP]] {
529 ! CHECK: %[[COORD1:.*]] = fir.coordinate_of %[[ARG0]], %[[IV]] : (!fir.ref<!fir.array<100xi32>>, index) -> !fir.ref<i32>
530 ! CHECK: %[[COORD2:.*]] = fir.coordinate_of %[[ARG1]], %[[IV]] : (!fir.ref<!fir.array<100xi32>>, index) -> !fir.ref<i32>
531 ! CHECK: %[[LOAD1:.*]] = fir.load %[[COORD1]] : !fir.ref<i32>
532 ! CHECK: %[[LOAD2:.*]] = fir.load %[[COORD2]] : !fir.ref<i32>
533 ! CHECK: %[[COMBINED:.*]] = arith.muli %[[LOAD1]], %[[LOAD2]] : i32
534 ! CHECK: fir.store %[[COMBINED]] to %[[COORD1]] : !fir.ref<i32>
535 ! CHECK: }
536 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<!fir.array<100xi32>>
537 ! CHECK: }
539 ! CHECK-LABEL: acc.reduction.recipe @reduction_mul_ref_i32 : !fir.ref<i32> reduction_operator <mul> init {
540 ! CHECK: ^bb0(%{{.*}}: !fir.ref<i32>):
541 ! CHECK: %[[INIT:.*]] = arith.constant 1 : i32
542 ! CHECK: %[[ALLOCA:.*]] = fir.alloca i32
543 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
544 ! CHECK: fir.store %[[INIT]] to %[[DECLARE]]#0 : !fir.ref<i32>
545 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<i32>
546 ! CHECK: } combiner {
547 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<i32>, %[[ARG1:.*]]: !fir.ref<i32>):
548 ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref<i32>
549 ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref<i32>
550 ! CHECK: %[[COMBINED:.*]] = arith.muli %[[LOAD0]], %[[LOAD1]] : i32
551 ! CHECK: fir.store %[[COMBINED]] to %[[ARG0]] : !fir.ref<i32>
552 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<i32>
553 ! CHECK: }
555 ! CHECK-LABEL: acc.reduction.recipe @reduction_add_section_ext100_ref_100xf32 : !fir.ref<!fir.array<100xf32>> reduction_operator <add> init {
556 ! CHECK: ^bb0(%{{.*}}: !fir.ref<!fir.array<100xf32>>):
557 ! CHECK: %[[INIT:.*]] = arith.constant 0.000000e+00 : f32
558 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}} : (index) -> !fir.shape<1>
559 ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.array<100xf32>
560 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]](%[[SHAPE]]) {uniq_name = "acc.reduction.init"} : (!fir.ref<!fir.array<100xf32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<100xf32>>, !fir.ref<!fir.array<100xf32>>)
561 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<!fir.array<100xf32>>
562 ! CHECK: } combiner {
563 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<!fir.array<100xf32>>, %[[ARG1:.*]]: !fir.ref<!fir.array<100xf32>>):
564 ! CHECK: %[[LB:.*]] = arith.constant 0 : index
565 ! CHECK: %[[UB:.*]] = arith.constant 99 : index
566 ! CHECK: %[[STEP:.*]] = arith.constant 1 : index
567 ! CHECK: fir.do_loop %[[IV:.*]] = %[[LB]] to %[[UB]] step %[[STEP]] {
568 ! CHECK: %[[COORD1:.*]] = fir.coordinate_of %[[ARG0]], %[[IV]] : (!fir.ref<!fir.array<100xf32>>, index) -> !fir.ref<f32>
569 ! CHECK: %[[COORD2:.*]] = fir.coordinate_of %[[ARG1]], %[[IV]] : (!fir.ref<!fir.array<100xf32>>, index) -> !fir.ref<f32>
570 ! CHECK: %[[LOAD1:.*]] = fir.load %[[COORD1]] : !fir.ref<f32>
571 ! CHECK: %[[LOAD2:.*]] = fir.load %[[COORD2]] : !fir.ref<f32>
572 ! CHECK: %[[COMBINED:.*]] = arith.addf %[[LOAD1]], %[[LOAD2]] fastmath<contract> : f32
573 ! CHECK: fir.store %[[COMBINED]] to %[[COORD1]] : !fir.ref<f32>
574 ! CHECK: }
575 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<!fir.array<100xf32>>
576 ! CHECK: }
578 ! CHECK-LABEL: acc.reduction.recipe @reduction_add_ref_f32 : !fir.ref<f32> reduction_operator <add> init {
579 ! CHECK: ^bb0(%{{.*}}: !fir.ref<f32>):
580 ! CHECK: %[[INIT:.*]] = arith.constant 0.000000e+00 : f32
581 ! CHECK: %[[ALLOCA:.*]] = fir.alloca f32
582 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
583 ! CHECK: fir.store %[[INIT]] to %[[DECLARE]]#0 : !fir.ref<f32>
584 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<f32>
585 ! CHECK: } combiner {
586 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<f32>, %[[ARG1:.*]]: !fir.ref<f32>):
587 ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref<f32>
588 ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref<f32>
589 ! CHECK: %[[COMBINED:.*]] = arith.addf %[[LOAD0]], %[[LOAD1]] fastmath<contract> : f32
590 ! CHECK: fir.store %[[COMBINED]] to %[[ARG0]] : !fir.ref<f32>
591 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<f32>
592 ! CHECK: }
594 ! CHECK-LABEL: acc.reduction.recipe @reduction_add_section_ext100xext10xext2_ref_100x10x2xi32 : !fir.ref<!fir.array<100x10x2xi32>> reduction_operator <add> init {
595 ! CHECK: ^bb0(%{{.*}}: !fir.ref<!fir.array<100x10x2xi32>>):
596 ! CHECK: %[[INIT:.*]] = arith.constant 0 : i32
597 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}}, %{{.*}}, %{{.*}} : (index, index, index) -> !fir.shape<3>
598 ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.array<100x10x2xi32>
599 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]](%[[SHAPE]]) {uniq_name = "acc.reduction.init"} : (!fir.ref<!fir.array<100x10x2xi32>>, !fir.shape<3>) -> (!fir.ref<!fir.array<100x10x2xi32>>, !fir.ref<!fir.array<100x10x2xi32>>)
600 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<!fir.array<100x10x2xi32>>
601 ! CHECK: } combiner {
602 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<!fir.array<100x10x2xi32>>, %[[ARG1:.*]]: !fir.ref<!fir.array<100x10x2xi32>>):
603 ! CHECK: %[[LB0:.*]] = arith.constant 0 : index
604 ! CHECK: %[[UB0:.*]] = arith.constant 1 : index
605 ! CHECK: %[[STEP0:.*]] = arith.constant 1 : index
606 ! CHECK: fir.do_loop %[[IV0:.*]] = %[[LB0]] to %[[UB0]] step %[[STEP0]] {
607 ! CHECK: %[[LB1:.*]] = arith.constant 0 : index
608 ! CHECK: %[[UB1:.*]] = arith.constant 9 : index
609 ! CHECK: %[[STEP1:.*]] = arith.constant 1 : index
610 ! CHECK: fir.do_loop %[[IV1:.*]] = %[[LB1]] to %[[UB1]] step %[[STEP1]] {
611 ! CHECK: %[[LB2:.*]] = arith.constant 0 : index
612 ! CHECK: %[[UB2:.*]] = arith.constant 99 : index
613 ! CHECK: %[[STEP2:.*]] = arith.constant 1 : index
614 ! CHECK: fir.do_loop %[[IV2:.*]] = %[[LB2]] to %[[UB2]] step %[[STEP2]] {
615 ! CHECK: %[[COORD1:.*]] = fir.coordinate_of %[[ARG0]], %[[IV0]], %[[IV1]], %[[IV2]] : (!fir.ref<!fir.array<100x10x2xi32>>, index, index, index) -> !fir.ref<i32>
616 ! CHECK: %[[COORD2:.*]] = fir.coordinate_of %[[ARG1]], %[[IV0]], %[[IV1]], %[[IV2]] : (!fir.ref<!fir.array<100x10x2xi32>>, index, index, index) -> !fir.ref<i32>
617 ! CHECK: %[[LOAD1:.*]] = fir.load %[[COORD1]] : !fir.ref<i32>
618 ! CHECK: %[[LOAD2:.*]] = fir.load %[[COORD2]] : !fir.ref<i32>
619 ! CHECK: %[[COMBINED:.*]] = arith.addi %[[LOAD1]], %[[LOAD2]] : i32
620 ! CHECK: fir.store %[[COMBINED]] to %[[COORD1]] : !fir.ref<i32>
621 ! CHECK: }
622 ! CHECK: }
623 ! CHECK: }
624 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<!fir.array<100x10x2xi32>>
625 ! CHECK: }
627 ! CHECK-LABEL: acc.reduction.recipe @reduction_add_section_ext100xext10_ref_100x10xi32 : !fir.ref<!fir.array<100x10xi32>> reduction_operator <add> init {
628 ! CHECK: ^bb0(%{{.*}}: !fir.ref<!fir.array<100x10xi32>>):
629 ! CHECK: %[[INIT:.*]] = arith.constant 0 : i32
630 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}}, %{{.*}} : (index, index) -> !fir.shape<2>
631 ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.array<100x10xi32>
632 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]](%[[SHAPE]]) {uniq_name = "acc.reduction.init"} : (!fir.ref<!fir.array<100x10xi32>>, !fir.shape<2>) -> (!fir.ref<!fir.array<100x10xi32>>, !fir.ref<!fir.array<100x10xi32>>)
633 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<!fir.array<100x10xi32>>
634 ! CHECK: } combiner {
635 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<!fir.array<100x10xi32>>, %[[ARG1:.*]]: !fir.ref<!fir.array<100x10xi32>>):
636 ! CHECK: %[[LB0:.*]] = arith.constant 0 : index
637 ! CHECK: %[[UB0:.*]] = arith.constant 9 : index
638 ! CHECK: %[[STEP0:.*]] = arith.constant 1 : index
639 ! CHECK: fir.do_loop %[[IV0:.*]] = %[[LB0]] to %[[UB0]] step %[[STEP0]] {
640 ! CHECK: %[[LB1:.*]] = arith.constant 0 : index
641 ! CHECK: %[[UB1:.*]] = arith.constant 99 : index
642 ! CHECK: %[[STEP1:.*]] = arith.constant 1 : index
643 ! CHECK: fir.do_loop %[[IV1:.*]] = %[[LB1]] to %[[UB1]] step %[[STEP1]] {
644 ! CHECK: %[[COORD1:.*]] = fir.coordinate_of %[[ARG0]], %[[IV0]], %[[IV1]] : (!fir.ref<!fir.array<100x10xi32>>, index, index) -> !fir.ref<i32>
645 ! CHECK: %[[COORD2:.*]] = fir.coordinate_of %[[ARG1]], %[[IV0]], %[[IV1]] : (!fir.ref<!fir.array<100x10xi32>>, index, index) -> !fir.ref<i32>
646 ! CHECK: %[[LOAD1]] = fir.load %[[COORD1]] : !fir.ref<i32>
647 ! CHECK: %[[LOAD2]] = fir.load %[[COORD2]] : !fir.ref<i32>
648 ! CHECK: %[[COMBINED:.*]] = arith.addi %[[LOAD1]], %[[LOAD2]] : i32
649 ! CHECK: fir.store %[[COMBINED]] to %[[COORD1]] : !fir.ref<i32>
650 ! CHECK: }
651 ! CHECK: }
652 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<!fir.array<100x10xi32>>
653 ! CHECK: }
655 ! CHECK-LABEL: acc.reduction.recipe @reduction_add_section_ext100_ref_100xi32 : !fir.ref<!fir.array<100xi32>> reduction_operator <add> init {
656 ! CHECK: ^bb0(%{{.*}}: !fir.ref<!fir.array<100xi32>>):
657 ! CHECK: %[[INIT:.*]] = arith.constant 0 : i32
658 ! CHECK: %[[SHAPE:.*]] = fir.shape %{{.*}} : (index) -> !fir.shape<1>
659 ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.array<100xi32>
660 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]](%[[SHAPE]]) {uniq_name = "acc.reduction.init"} : (!fir.ref<!fir.array<100xi32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<100xi32>>, !fir.ref<!fir.array<100xi32>>)
661 ! HFLIR: acc.yield %[[DECLARE]]#0 : !fir.ref<!fir.array<100xi32>>
662 ! CHECK: } combiner {
663 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<!fir.array<100xi32>>, %[[ARG1:.*]]: !fir.ref<!fir.array<100xi32>>):
664 ! CHECK: %[[LB:.*]] = arith.constant 0 : index
665 ! CHECK: %[[UB:.*]] = arith.constant 99 : index
666 ! CHECK: %[[STEP:.*]] = arith.constant 1 : index
667 ! CHECK: fir.do_loop %[[IV:.*]] = %[[LB]] to %[[UB]] step %[[STEP]] {
668 ! CHECK: %[[COORD1:.*]] = fir.coordinate_of %[[ARG0]], %[[IV]] : (!fir.ref<!fir.array<100xi32>>, index) -> !fir.ref<i32>
669 ! CHECK: %[[COORD2:.*]] = fir.coordinate_of %[[ARG1]], %[[IV]] : (!fir.ref<!fir.array<100xi32>>, index) -> !fir.ref<i32>
670 ! CHECK: %[[LOAD1:.*]] = fir.load %[[COORD1]] : !fir.ref<i32>
671 ! CHECK: %[[LOAD2:.*]] = fir.load %[[COORD2]] : !fir.ref<i32>
672 ! CHECK: %[[COMBINED:.*]] = arith.addi %[[LOAD1]], %[[LOAD2]] : i32
673 ! CHECK: fir.store %[[COMBINED]] to %[[COORD1]] : !fir.ref<i32>
674 ! CHECK: }
675 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<!fir.array<100xi32>>
676 ! CHECK: }
678 ! CHECK-LABEL: acc.reduction.recipe @reduction_add_ref_i32 : !fir.ref<i32> reduction_operator <add> init {
679 ! CHECK: ^bb0(%{{.*}}: !fir.ref<i32>):
680 ! CHECK: %[[INIT:.*]] = arith.constant 0 : i32
681 ! CHECK: %[[ALLOCA:.*]] = fir.alloca i32
682 ! CHECK: %[[DECLARE:.*]]:2 = hlfir.declare %[[ALLOCA]] {uniq_name = "acc.reduction.init"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
683 ! CHECK: fir.store %[[INIT]] to %[[DECLARE]]#0 : !fir.ref<i32>
684 ! CHECK: acc.yield %[[DECLARE]]#0 : !fir.ref<i32>
685 ! CHECK: } combiner {
686 ! CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<i32>, %[[ARG1:.*]]: !fir.ref<i32>):
687 ! CHECK: %[[LOAD0:.*]] = fir.load %[[ARG0]] : !fir.ref<i32>
688 ! CHECK: %[[LOAD1:.*]] = fir.load %[[ARG1]] : !fir.ref<i32>
689 ! CHECK: %[[COMBINED:.*]] = arith.addi %[[LOAD0]], %[[LOAD1]] : i32
690 ! CHECK: fir.store %[[COMBINED]] to %[[ARG0]] : !fir.ref<i32>
691 ! CHECK: acc.yield %[[ARG0]] : !fir.ref<i32>
692 ! CHECK: }
694 subroutine acc_reduction_add_int(a, b)
695 integer :: a(100)
696 integer :: i, b
698 !$acc loop reduction(+:b)
699 do i = 1, 100
700 b = b + a(i)
701 end do
702 end subroutine
704 ! CHECK-LABEL: func.func @_QPacc_reduction_add_int(
705 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<100xi32>> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref<i32> {fir.bindc_name = "b"})
706 ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]]
707 ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#0 : !fir.ref<i32>) -> !fir.ref<i32> {name = "b"}
708 ! CHECK: acc.loop {{.*}} reduction(@reduction_add_ref_i32 -> %[[RED_B]] : !fir.ref<i32>)
710 subroutine acc_reduction_add_int_array_1d(a, b)
711 integer :: a(100)
712 integer :: i, b(100)
714 !$acc loop reduction(+:b)
715 do i = 1, 100
716 b(i) = b(i) + a(i)
717 end do
718 end subroutine
720 ! CHECK-LABEL: func.func @_QPacc_reduction_add_int_array_1d(
721 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<100xi32>> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref<!fir.array<100xi32>> {fir.bindc_name = "b"})
722 ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]]
723 ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#0 : !fir.ref<!fir.array<100xi32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<100xi32>> {name = "b"}
724 ! CHECK: acc.loop {{.*}} reduction(@reduction_add_section_ext100_ref_100xi32 -> %[[RED_B]] : !fir.ref<!fir.array<100xi32>>)
726 subroutine acc_reduction_add_int_array_2d(a, b)
727 integer :: a(100, 10), b(100, 10)
728 integer :: i, j
730 !$acc loop collapse(2) reduction(+:b)
731 do i = 1, 100
732 do j = 1, 10
733 b(i, j) = b(i, j) + a(i, j)
734 end do
735 end do
736 end subroutine
738 ! CHECK-LABEL: func.func @_QPacc_reduction_add_int_array_2d(
739 ! CHECK-SAME: %[[ARG0:.*]]: !fir.ref<!fir.array<100x10xi32>> {fir.bindc_name = "a"}, %[[ARG1:.*]]: !fir.ref<!fir.array<100x10xi32>> {fir.bindc_name = "b"}) {
740 ! CHECK: %[[DECLARG1:.*]]:2 = hlfir.declare %[[ARG1]]
741 ! CHECK: %[[RED_ARG1:.*]] = acc.reduction varPtr(%[[DECLARG1]]#0 : !fir.ref<!fir.array<100x10xi32>>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref<!fir.array<100x10xi32>> {name = "b"}
742 ! CHECK: acc.loop {{.*}} reduction(@reduction_add_section_ext100xext10_ref_100x10xi32 -> %[[RED_ARG1]] : !fir.ref<!fir.array<100x10xi32>>)
743 ! CHECK: } attributes {collapse = [2]{{.*}}
745 subroutine acc_reduction_add_int_array_3d(a, b)
746 integer :: a(100, 10, 2), b(100, 10, 2)
747 integer :: i, j, k
749 !$acc loop collapse(3) reduction(+:b)
750 do i = 1, 100
751 do j = 1, 10
752 do k = 1, 2
753 b(i, j, k) = b(i, j, k) + a(i, j, k)
754 end do
755 end do
756 end do
757 end subroutine
759 ! CHECK-LABEL: func.func @_QPacc_reduction_add_int_array_3d(
760 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<100x10x2xi32>> {fir.bindc_name = "a"}, %[[ARG1:.*]]: !fir.ref<!fir.array<100x10x2xi32>> {fir.bindc_name = "b"})
761 ! CHECK: %[[DECLARG1:.*]]:2 = hlfir.declare %[[ARG1]]
762 ! CHECK: %[[RED_ARG1:.*]] = acc.reduction varPtr(%[[DECLARG1]]#0 : !fir.ref<!fir.array<100x10x2xi32>>) bounds(%{{.*}}, %{{.*}}, %{{.*}}) -> !fir.ref<!fir.array<100x10x2xi32>> {name = "b"}
763 ! CHECK: acc.loop {{.*}} reduction(@reduction_add_section_ext100xext10xext2_ref_100x10x2xi32 -> %[[RED_ARG1]] : !fir.ref<!fir.array<100x10x2xi32>>)
764 ! CHECK: } attributes {collapse = [3]{{.*}}
766 subroutine acc_reduction_add_float(a, b)
767 real :: a(100), b
768 integer :: i
770 !$acc loop reduction(+:b)
771 do i = 1, 100
772 b = b + a(i)
773 end do
774 end subroutine
776 ! CHECK-LABEL: func.func @_QPacc_reduction_add_float(
777 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<100xf32>> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref<f32> {fir.bindc_name = "b"})
778 ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]]
779 ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#0 : !fir.ref<f32>) -> !fir.ref<f32> {name = "b"}
780 ! CHECK: acc.loop {{.*}} reduction(@reduction_add_ref_f32 -> %[[RED_B]] : !fir.ref<f32>)
782 subroutine acc_reduction_add_float_array_1d(a, b)
783 real :: a(100), b(100)
784 integer :: i
786 !$acc loop reduction(+:b)
787 do i = 1, 100
788 b(i) = b(i) + a(i)
789 end do
790 end subroutine
792 ! CHECK-LABEL: func.func @_QPacc_reduction_add_float_array_1d(
793 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<100xf32>> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref<!fir.array<100xf32>> {fir.bindc_name = "b"})
794 ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]]
795 ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#0 : !fir.ref<!fir.array<100xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<100xf32>> {name = "b"}
796 ! CHECK: acc.loop {{.*}} reduction(@reduction_add_section_ext100_ref_100xf32 -> %[[RED_B]] : !fir.ref<!fir.array<100xf32>>)
798 subroutine acc_reduction_mul_int(a, b)
799 integer :: a(100)
800 integer :: i, b
802 !$acc loop reduction(*:b)
803 do i = 1, 100
804 b = b * a(i)
805 end do
806 end subroutine
808 ! CHECK-LABEL: func.func @_QPacc_reduction_mul_int(
809 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<100xi32>> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref<i32> {fir.bindc_name = "b"})
810 ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]]
811 ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#0 : !fir.ref<i32>) -> !fir.ref<i32> {name = "b"}
812 ! CHECK: acc.loop {{.*}} reduction(@reduction_mul_ref_i32 -> %[[RED_B]] : !fir.ref<i32>)
814 subroutine acc_reduction_mul_int_array_1d(a, b)
815 integer :: a(100)
816 integer :: i, b(100)
818 !$acc loop reduction(*:b)
819 do i = 1, 100
820 b(i) = b(i) * a(i)
821 end do
822 end subroutine
824 ! CHECK-LABEL: func.func @_QPacc_reduction_mul_int_array_1d(
825 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<100xi32>> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref<!fir.array<100xi32>> {fir.bindc_name = "b"})
826 ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]]
827 ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#0 : !fir.ref<!fir.array<100xi32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<100xi32>> {name = "b"}
828 ! CHECK: acc.loop {{.*}} reduction(@reduction_mul_section_ext100_ref_100xi32 -> %[[RED_B]] : !fir.ref<!fir.array<100xi32>>)
830 subroutine acc_reduction_mul_float(a, b)
831 real :: a(100), b
832 integer :: i
834 !$acc loop reduction(*:b)
835 do i = 1, 100
836 b = b * a(i)
837 end do
838 end subroutine
840 ! CHECK-LABEL: func.func @_QPacc_reduction_mul_float(
841 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<100xf32>> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref<f32> {fir.bindc_name = "b"})
842 ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]]
843 ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#0 : !fir.ref<f32>) -> !fir.ref<f32> {name = "b"}
844 ! CHECK: acc.loop {{.*}} reduction(@reduction_mul_ref_f32 -> %[[RED_B]] : !fir.ref<f32>)
846 subroutine acc_reduction_mul_float_array_1d(a, b)
847 real :: a(100), b(100)
848 integer :: i
850 !$acc loop reduction(*:b)
851 do i = 1, 100
852 b(i) = b(i) * a(i)
853 end do
854 end subroutine
856 ! CHECK-LABEL: func.func @_QPacc_reduction_mul_float_array_1d(
857 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<100xf32>> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref<!fir.array<100xf32>> {fir.bindc_name = "b"})
858 ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]]
859 ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#0 : !fir.ref<!fir.array<100xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<100xf32>> {name = "b"}
860 ! CHECK: acc.loop {{.*}} reduction(@reduction_mul_section_ext100_ref_100xf32 -> %[[RED_B]] : !fir.ref<!fir.array<100xf32>>)
862 subroutine acc_reduction_min_int(a, b)
863 integer :: a(100)
864 integer :: i, b
866 !$acc loop reduction(min:b)
867 do i = 1, 100
868 b = min(b, a(i))
869 end do
870 end subroutine
872 ! CHECK-LABEL: func.func @_QPacc_reduction_min_int(
873 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<100xi32>> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref<i32> {fir.bindc_name = "b"})
874 ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]]
875 ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#0 : !fir.ref<i32>) -> !fir.ref<i32> {name = "b"}
876 ! CHECK: acc.loop {{.*}} reduction(@reduction_min_ref_i32 -> %[[RED_B]] : !fir.ref<i32>)
878 subroutine acc_reduction_min_int_array_1d(a, b)
879 integer :: a(100), b(100)
880 integer :: i
882 !$acc loop reduction(min:b)
883 do i = 1, 100
884 b(i) = min(b(i), a(i))
885 end do
886 end subroutine
888 ! CHECK-LABEL: func.func @_QPacc_reduction_min_int_array_1d(
889 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<100xi32>> {fir.bindc_name = "a"}, %[[ARG1:.*]]: !fir.ref<!fir.array<100xi32>> {fir.bindc_name = "b"})
890 ! CHECK: %[[DECLARG1:.*]]:2 = hlfir.declare %[[ARG1]]
891 ! CHECK: %[[RED_ARG1:.*]] = acc.reduction varPtr(%[[DECLARG1]]#0 : !fir.ref<!fir.array<100xi32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<100xi32>> {name = "b"}
892 ! CHECK: acc.loop {{.*}} reduction(@reduction_min_section_ext100_ref_100xi32 -> %[[RED_ARG1]] : !fir.ref<!fir.array<100xi32>>)
894 subroutine acc_reduction_min_float(a, b)
895 real :: a(100), b
896 integer :: i
898 !$acc loop reduction(min:b)
899 do i = 1, 100
900 b = min(b, a(i))
901 end do
902 end subroutine
904 ! CHECK-LABEL: func.func @_QPacc_reduction_min_float(
905 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<100xf32>> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref<f32> {fir.bindc_name = "b"})
906 ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]]
907 ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#0 : !fir.ref<f32>) -> !fir.ref<f32> {name = "b"}
908 ! CHECK: acc.loop {{.*}} reduction(@reduction_min_ref_f32 -> %[[RED_B]] : !fir.ref<f32>)
910 subroutine acc_reduction_min_float_array2d(a, b)
911 real :: a(100, 10), b(100, 10)
912 integer :: i, j
914 !$acc loop reduction(min:b) collapse(2)
915 do i = 1, 100
916 do j = 1, 10
917 b(i, j) = min(b(i, j), a(i, j))
918 end do
919 end do
920 end subroutine
922 ! CHECK-LABEL: func.func @_QPacc_reduction_min_float_array2d(
923 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<100x10xf32>> {fir.bindc_name = "a"}, %[[ARG1:.*]]: !fir.ref<!fir.array<100x10xf32>> {fir.bindc_name = "b"})
924 ! CHECK: %[[DECLARG1:.*]]:2 = hlfir.declare %[[ARG1]]
925 ! CHECK: %[[RED_ARG1:.*]] = acc.reduction varPtr(%[[DECLARG1]]#0 : !fir.ref<!fir.array<100x10xf32>>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref<!fir.array<100x10xf32>> {name = "b"}
926 ! CHECK: acc.loop {{.*}} reduction(@reduction_min_section_ext100xext10_ref_100x10xf32 -> %[[RED_ARG1]] : !fir.ref<!fir.array<100x10xf32>>)
927 ! CHECK: attributes {collapse = [2]{{.*}}
929 subroutine acc_reduction_max_int(a, b)
930 integer :: a(100)
931 integer :: i, b
933 !$acc loop reduction(max:b)
934 do i = 1, 100
935 b = max(b, a(i))
936 end do
937 end subroutine
939 ! CHECK-LABEL: func.func @_QPacc_reduction_max_int(
940 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<100xi32>> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref<i32> {fir.bindc_name = "b"})
941 ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]]
942 ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#0 : !fir.ref<i32>) -> !fir.ref<i32> {name = "b"}
943 ! CHECK: acc.loop {{.*}} reduction(@reduction_max_ref_i32 -> %[[RED_B]] : !fir.ref<i32>)
945 subroutine acc_reduction_max_int_array2d(a, b)
946 integer :: a(100, 10), b(100, 10)
947 integer :: i, j
949 !$acc loop reduction(max:b) collapse(2)
950 do i = 1, 100
951 do j = 1, 10
952 b(i, j) = max(b(i, j), a(i, j))
953 end do
954 end do
955 end subroutine
957 ! CHECK-LABEL: func.func @_QPacc_reduction_max_int_array2d(
958 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<100x10xi32>> {fir.bindc_name = "a"}, %[[ARG1:.*]]: !fir.ref<!fir.array<100x10xi32>> {fir.bindc_name = "b"})
959 ! CHECK: %[[DECLARG1:.*]]:2 = hlfir.declare %[[ARG1]]
960 ! CHECK: %[[RED_ARG1:.*]] = acc.reduction varPtr(%[[DECLARG1]]#0 : !fir.ref<!fir.array<100x10xi32>>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref<!fir.array<100x10xi32>> {name = "b"}
961 ! CHECK: acc.loop {{.*}} reduction(@reduction_max_section_ext100xext10_ref_100x10xi32 -> %[[RED_ARG1]] : !fir.ref<!fir.array<100x10xi32>>)
963 subroutine acc_reduction_max_float(a, b)
964 real :: a(100), b
965 integer :: i
967 !$acc loop reduction(max:b)
968 do i = 1, 100
969 b = max(b, a(i))
970 end do
971 end subroutine
973 ! CHECK-LABEL: func.func @_QPacc_reduction_max_float(
974 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<100xf32>> {fir.bindc_name = "a"}, %[[B:.*]]: !fir.ref<f32> {fir.bindc_name = "b"})
975 ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]]
976 ! CHECK: %[[RED_B:.*]] = acc.reduction varPtr(%[[DECLB]]#0 : !fir.ref<f32>) -> !fir.ref<f32> {name = "b"}
977 ! CHECK: acc.loop {{.*}} reduction(@reduction_max_ref_f32 -> %[[RED_B]] : !fir.ref<f32>)
979 subroutine acc_reduction_max_float_array1d(a, b)
980 real :: a(100), b(100)
981 integer :: i
983 !$acc loop reduction(max:b)
984 do i = 1, 100
985 b(i) = max(b(i), a(i))
986 end do
987 end subroutine
989 ! CHECK-LABEL: func.func @_QPacc_reduction_max_float_array1d(
990 ! CHECK-SAME: %{{.*}}: !fir.ref<!fir.array<100xf32>> {fir.bindc_name = "a"}, %[[ARG1:.*]]: !fir.ref<!fir.array<100xf32>> {fir.bindc_name = "b"})
991 ! CHECK: %[[DECLARG1:.*]]:2 = hlfir.declare %[[ARG1]]
992 ! CHECK: %[[RED_ARG1:.*]] = acc.reduction varPtr(%[[DECLARG1]]#0 : !fir.ref<!fir.array<100xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<100xf32>> {name = "b"}
993 ! CHECK: acc.loop {{.*}} reduction(@reduction_max_section_ext100_ref_100xf32 -> %[[RED_ARG1]] : !fir.ref<!fir.array<100xf32>>)
995 subroutine acc_reduction_iand()
996 integer :: i
997 !$acc parallel reduction(iand:i)
998 !$acc end parallel
999 end subroutine
1001 ! CHECK-LABEL: func.func @_QPacc_reduction_iand()
1002 ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%{{.*}} : !fir.ref<i32>) -> !fir.ref<i32> {name = "i"}
1003 ! CHECK: acc.parallel reduction(@reduction_iand_ref_i32 -> %[[RED]] : !fir.ref<i32>)
1005 subroutine acc_reduction_ior()
1006 integer :: i
1007 !$acc parallel reduction(ior:i)
1008 !$acc end parallel
1009 end subroutine
1011 ! CHECK-LABEL: func.func @_QPacc_reduction_ior()
1012 ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%{{.*}} : !fir.ref<i32>) -> !fir.ref<i32> {name = "i"}
1013 ! CHECK: acc.parallel reduction(@reduction_ior_ref_i32 -> %[[RED]] : !fir.ref<i32>)
1015 subroutine acc_reduction_ieor()
1016 integer :: i
1017 !$acc parallel reduction(ieor:i)
1018 !$acc end parallel
1019 end subroutine
1021 ! CHECK-LABEL: func.func @_QPacc_reduction_ieor()
1022 ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%{{.*}} : !fir.ref<i32>) -> !fir.ref<i32> {name = "i"}
1023 ! CHECK: acc.parallel reduction(@reduction_xor_ref_i32 -> %[[RED]] : !fir.ref<i32>)
1025 subroutine acc_reduction_and()
1026 logical :: l
1027 !$acc parallel reduction(.and.:l)
1028 !$acc end parallel
1029 end subroutine
1031 ! CHECK-LABEL: func.func @_QPacc_reduction_and()
1032 ! CHECK: %[[L:.*]] = fir.alloca !fir.logical<4> {bindc_name = "l", uniq_name = "_QFacc_reduction_andEl"}
1033 ! CHECK: %[[DECLL:.*]]:2 = hlfir.declare %[[L]]
1034 ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%[[DECLL]]#0 : !fir.ref<!fir.logical<4>>) -> !fir.ref<!fir.logical<4>> {name = "l"}
1035 ! CHECK: acc.parallel reduction(@reduction_land_ref_l32 -> %[[RED]] : !fir.ref<!fir.logical<4>>)
1037 subroutine acc_reduction_or()
1038 logical :: l
1039 !$acc parallel reduction(.or.:l)
1040 !$acc end parallel
1041 end subroutine
1043 ! CHECK-LABEL: func.func @_QPacc_reduction_or()
1044 ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%{{.*}} : !fir.ref<!fir.logical<4>>) -> !fir.ref<!fir.logical<4>> {name = "l"}
1045 ! CHECK: acc.parallel reduction(@reduction_lor_ref_l32 -> %[[RED]] : !fir.ref<!fir.logical<4>>)
1047 subroutine acc_reduction_eqv()
1048 logical :: l
1049 !$acc parallel reduction(.eqv.:l)
1050 !$acc end parallel
1051 end subroutine
1053 ! CHECK-LABEL: func.func @_QPacc_reduction_eqv()
1054 ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%{{.*}} : !fir.ref<!fir.logical<4>>) -> !fir.ref<!fir.logical<4>> {name = "l"}
1055 ! CHECK: acc.parallel reduction(@reduction_eqv_ref_l32 -> %[[RED]] : !fir.ref<!fir.logical<4>>)
1057 subroutine acc_reduction_neqv()
1058 logical :: l
1059 !$acc parallel reduction(.neqv.:l)
1060 !$acc end parallel
1061 end subroutine
1063 ! CHECK-LABEL: func.func @_QPacc_reduction_neqv()
1064 ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%{{.*}} : !fir.ref<!fir.logical<4>>) -> !fir.ref<!fir.logical<4>> {name = "l"}
1065 ! CHECK: acc.parallel reduction(@reduction_neqv_ref_l32 -> %[[RED]] : !fir.ref<!fir.logical<4>>)
1067 subroutine acc_reduction_add_cmplx()
1068 complex :: c
1069 !$acc parallel reduction(+:c)
1070 !$acc end parallel
1071 end subroutine
1073 ! CHECK-LABEL: func.func @_QPacc_reduction_add_cmplx()
1074 ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%{{.*}} : !fir.ref<complex<f32>>) -> !fir.ref<complex<f32>> {name = "c"}
1075 ! CHECK: acc.parallel reduction(@reduction_add_ref_z32 -> %[[RED]] : !fir.ref<complex<f32>>)
1077 subroutine acc_reduction_mul_cmplx()
1078 complex :: c
1079 !$acc parallel reduction(*:c)
1080 !$acc end parallel
1081 end subroutine
1083 ! CHECK-LABEL: func.func @_QPacc_reduction_mul_cmplx()
1084 ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%{{.*}} : !fir.ref<complex<f32>>) -> !fir.ref<complex<f32>> {name = "c"}
1085 ! CHECK: acc.parallel reduction(@reduction_mul_ref_z32 -> %[[RED]] : !fir.ref<complex<f32>>)
1087 subroutine acc_reduction_add_alloc()
1088 integer, allocatable :: i
1089 allocate(i)
1090 !$acc parallel reduction(+:i)
1091 !$acc end parallel
1092 end subroutine
1094 ! CHECK-LABEL: func.func @_QPacc_reduction_add_alloc()
1095 ! CHECK: %[[ALLOCA:.*]] = fir.alloca !fir.box<!fir.heap<i32>> {bindc_name = "i", uniq_name = "_QFacc_reduction_add_allocEi"}
1096 ! CHECK: %[[DECL:.*]]:2 = hlfir.declare %[[ALLOCA]]
1097 ! CHECK: %[[LOAD:.*]] = fir.load %[[DECL]]#0 : !fir.ref<!fir.box<!fir.heap<i32>>>
1098 ! CHECK: %[[BOX_ADDR:.*]] = fir.box_addr %[[LOAD]] : (!fir.box<!fir.heap<i32>>) -> !fir.heap<i32>
1099 ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%[[BOX_ADDR]] : !fir.heap<i32>) -> !fir.heap<i32> {name = "i"}
1100 ! CHECK: acc.parallel reduction(@reduction_add_heap_i32 -> %[[RED]] : !fir.heap<i32>)
1102 subroutine acc_reduction_add_pointer(i)
1103 integer, pointer :: i
1104 !$acc parallel reduction(+:i)
1105 !$acc end parallel
1106 end subroutine
1108 ! CHECK-LABEL: func.func @_QPacc_reduction_add_pointer(
1109 ! CHECK-SAME: %[[ARG0:.*]]: !fir.ref<!fir.box<!fir.ptr<i32>>> {fir.bindc_name = "i"})
1110 ! CHECK: %[[DECLARG0:.*]]:2 = hlfir.declare %[[ARG0]]
1111 ! CHECK: %[[LOAD:.*]] = fir.load %[[DECLARG0]]#0 : !fir.ref<!fir.box<!fir.ptr<i32>>>
1112 ! CHECK: %[[BOX_ADDR:.*]] = fir.box_addr %[[LOAD]] : (!fir.box<!fir.ptr<i32>>) -> !fir.ptr<i32>
1113 ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%[[BOX_ADDR]] : !fir.ptr<i32>) -> !fir.ptr<i32> {name = "i"}
1114 ! CHECK: acc.parallel reduction(@reduction_add_ptr_i32 -> %[[RED]] : !fir.ptr<i32>)
1116 subroutine acc_reduction_add_static_slice(a)
1117 integer :: a(100)
1118 !$acc parallel reduction(+:a(11:20))
1119 !$acc end parallel
1120 end subroutine
1122 ! CHECK-LABEL: func.func @_QPacc_reduction_add_static_slice(
1123 ! CHECK-SAME: %[[ARG0:.*]]: !fir.ref<!fir.array<100xi32>> {fir.bindc_name = "a"})
1124 ! CHECK: %[[C100:.*]] = arith.constant 100 : index
1125 ! CHECK: %[[DECLARG0:.*]]:2 = hlfir.declare %[[ARG0]]
1126 ! CHECK: %[[C1:.*]] = arith.constant 1 : index
1127 ! CHECK: %[[LB:.*]] = arith.constant 10 : index
1128 ! CHECK: %[[UB:.*]] = arith.constant 19 : index
1129 ! CHECK: %[[BOUND:.*]] = acc.bounds lowerbound(%[[LB]] : index) upperbound(%[[UB]] : index) extent(%[[C100]] : index) stride(%[[C1]] : index) startIdx(%[[C1]] : index)
1130 ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%[[DECLARG0]]#0 : !fir.ref<!fir.array<100xi32>>) bounds(%[[BOUND]]) -> !fir.ref<!fir.array<100xi32>> {name = "a(11:20)"}
1131 ! CHECK: acc.parallel reduction(@reduction_add_section_lb10.ub19_ref_100xi32 -> %[[RED]] : !fir.ref<!fir.array<100xi32>>)
1133 subroutine acc_reduction_add_dynamic_extent_add(a)
1134 integer :: a(:)
1135 !$acc parallel reduction(+:a)
1136 !$acc end parallel
1137 end subroutine
1139 ! CHECK-LABEL: func.func @_QPacc_reduction_add_dynamic_extent_add(
1140 ! CHECK-SAME: %[[ARG0:.*]]: !fir.box<!fir.array<?xi32>> {fir.bindc_name = "a"})
1141 ! CHECK: %[[DECLARG0:.*]]:2 = hlfir.declare %[[ARG0]]
1142 ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%{{.*}} : !fir.ref<!fir.array<?xi32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<?xi32>> {name = "a"}
1143 ! CHECK: acc.parallel reduction(@reduction_add_box_Uxi32 -> %[[RED:.*]] : !fir.ref<!fir.array<?xi32>>)
1145 subroutine acc_reduction_add_assumed_shape_max(a)
1146 real :: a(:)
1147 !$acc parallel reduction(max:a)
1148 !$acc end parallel
1149 end subroutine
1151 ! CHECK-LABEL: func.func @_QPacc_reduction_add_assumed_shape_max(
1152 ! CHECK-SAME: %[[ARG0:.*]]: !fir.box<!fir.array<?xf32>> {fir.bindc_name = "a"})
1153 ! CHECK: %[[DECLARG0:.*]]:2 = hlfir.declare %[[ARG0]]
1154 ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%{{.*}} : !fir.ref<!fir.array<?xf32>>) bounds(%{{.*}}) -> !fir.ref<!fir.array<?xf32>> {name = "a"}
1155 ! CHECK: acc.parallel reduction(@reduction_max_box_Uxf32 -> %[[RED]] : !fir.ref<!fir.array<?xf32>>) {
1157 subroutine acc_reduction_add_dynamic_extent_add_with_section(a)
1158 integer :: a(:)
1159 !$acc parallel reduction(+:a(2:4))
1160 !$acc end parallel
1161 end subroutine
1163 ! CHECK-LABEL: func.func @_QPacc_reduction_add_dynamic_extent_add_with_section(
1164 ! CHECK-SAME: %[[ARG0:.*]]: !fir.box<!fir.array<?xi32>> {fir.bindc_name = "a"})
1165 ! CHECK: %[[DECL:.*]]:2 = hlfir.declare %[[ARG0]] dummy_scope %{{[0-9]+}} {uniq_name = "_QFacc_reduction_add_dynamic_extent_add_with_sectionEa"} : (!fir.box<!fir.array<?xi32>>, !fir.dscope) -> (!fir.box<!fir.array<?xi32>>, !fir.box<!fir.array<?xi32>>)
1166 ! CHECK: %[[BOUND:.*]] = acc.bounds lowerbound(%c1{{.*}} : index) upperbound(%c3{{.*}} : index) extent(%{{.*}}#1 : index) stride(%{{.*}}#2 : index) startIdx(%{{.*}} : index) {strideInBytes = true}
1167 ! CHECK: %[[BOX_ADDR:.*]] = fir.box_addr %[[DECL]]#0 : (!fir.box<!fir.array<?xi32>>) -> !fir.ref<!fir.array<?xi32>>
1168 ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%[[BOX_ADDR]] : !fir.ref<!fir.array<?xi32>>) bounds(%[[BOUND]]) -> !fir.ref<!fir.array<?xi32>> {name = "a(2:4)"}
1169 ! CHECK: acc.parallel reduction(@reduction_add_section_lb1.ub3_box_Uxi32 -> %[[RED]] : !fir.ref<!fir.array<?xi32>>)
1171 subroutine acc_reduction_add_allocatable(a)
1172 real, allocatable :: a(:)
1173 !$acc parallel reduction(max:a)
1174 !$acc end parallel
1175 end subroutine
1177 ! CHECK-LABEL: func.func @_QPacc_reduction_add_allocatable(
1178 ! CHECK-SAME: %[[ARG0:.*]]: !fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>> {fir.bindc_name = "a"})
1179 ! CHECK: %[[DECL:.*]]:2 = hlfir.declare %[[ARG0]] dummy_scope %{{[0-9]+}} {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QFacc_reduction_add_allocatableEa"} : (!fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>, !fir.dscope) -> (!fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>)
1180 ! CHECK: %[[BOX:.*]] = fir.load %[[DECL]]#0 : !fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>
1181 ! CHECK: %[[BOUND:.*]] = acc.bounds lowerbound(%c0{{.*}} : index) upperbound(%{{.*}} : index) extent(%{{.*}}#1 : index) stride(%{{.*}}#2 : index) startIdx(%{{.*}}#0 : index) {strideInBytes = true}
1182 ! CHECK: %[[BOX_ADDR:.*]] = fir.box_addr %[[BOX]] : (!fir.box<!fir.heap<!fir.array<?xf32>>>) -> !fir.heap<!fir.array<?xf32>>
1183 ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%[[BOX_ADDR]] : !fir.heap<!fir.array<?xf32>>) bounds(%{{[0-9]+}}) -> !fir.heap<!fir.array<?xf32>> {name = "a"}
1184 ! CHECK: acc.parallel reduction(@reduction_max_box_heap_Uxf32 -> %[[RED]] : !fir.heap<!fir.array<?xf32>>)
1186 subroutine acc_reduction_add_pointer_array(a)
1187 real, pointer :: a(:)
1188 !$acc parallel reduction(max:a)
1189 !$acc end parallel
1190 end subroutine
1192 ! CHECK-LABEL: func.func @_QPacc_reduction_add_pointer_array(
1193 ! CHECK-SAME: %[[ARG0:.*]]: !fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>> {fir.bindc_name = "a"})
1194 ! CHECK: %[[DECL:.*]]:2 = hlfir.declare %[[ARG0]] dummy_scope %{{[0-9]+}} {fortran_attrs = #fir.var_attrs<pointer>, uniq_name = "_QFacc_reduction_add_pointer_arrayEa"} : (!fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>>, !fir.dscope) -> (!fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>>, !fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>>)
1195 ! CHECK: %[[BOX:.*]] = fir.load %[[DECL]]#0 : !fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>>
1196 ! CHECK: %[[BOUND:.*]] = acc.bounds lowerbound(%c0{{.*}} : index) upperbound(%{{.*}} : index) extent(%{{.*}}#1 : index) stride(%{{.*}}#2 : index) startIdx(%{{.*}}#0 : index) {strideInBytes = true}
1197 ! CHECK: %[[BOX_ADDR:.*]] = fir.box_addr %[[BOX]] : (!fir.box<!fir.ptr<!fir.array<?xf32>>>) -> !fir.ptr<!fir.array<?xf32>>
1198 ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%[[BOX_ADDR]] : !fir.ptr<!fir.array<?xf32>>) bounds(%[[BOUND]]) -> !fir.ptr<!fir.array<?xf32>> {name = "a"}
1199 ! CHECK: acc.parallel reduction(@reduction_max_box_ptr_Uxf32 -> %[[RED]] : !fir.ptr<!fir.array<?xf32>>)
1201 subroutine acc_reduction_max_dynamic_extent_max(a, n)
1202 integer :: n
1203 real :: a(n, n)
1204 !$acc parallel reduction(max:a)
1205 !$acc end parallel
1206 end subroutine
1208 ! CHECK-LABEL: func.func @_QPacc_reduction_max_dynamic_extent_max(
1209 ! CHECK-SAME: %[[ARG0:.*]]: !fir.ref<!fir.array<?x?xf32>> {fir.bindc_name = "a"}, %{{.*}}: !fir.ref<i32> {fir.bindc_name = "n"})
1210 ! CHECK: %[[DECL_A:.*]]:2 = hlfir.declare %[[ARG0]](%{{.*}}) dummy_scope %{{[0-9]+}} {uniq_name = "_QFacc_reduction_max_dynamic_extent_maxEa"} : (!fir.ref<!fir.array<?x?xf32>>, !fir.shape<2>, !fir.dscope) -> (!fir.box<!fir.array<?x?xf32>>, !fir.ref<!fir.array<?x?xf32>>)
1211 ! CHECK: %[[ADDR:.*]] = fir.box_addr %[[DECL_A]]#0 : (!fir.box<!fir.array<?x?xf32>>) -> !fir.ref<!fir.array<?x?xf32>>
1212 ! CHECK: %[[RED:.*]] = acc.reduction varPtr(%[[ADDR]] : !fir.ref<!fir.array<?x?xf32>>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref<!fir.array<?x?xf32>> {name = "a"}
1213 ! CHECK: acc.parallel reduction(@reduction_max_box_UxUxf32 -> %[[RED]] : !fir.ref<!fir.array<?x?xf32>>)