Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Lower / OpenMP / wsloop-reduction-add.f90
blob69d133d50ffa0aecc8b3cadfe51fecc2f9b7de97
1 ! RUN: bbc -emit-fir -fopenmp %s -o - | FileCheck %s
2 ! RUN: %flang_fc1 -emit-fir -fopenmp %s -o - | FileCheck %s
4 !CHECK-LABEL: omp.reduction.declare
5 !CHECK-SAME: @[[RED_F64_NAME:.*]] : f64 init {
6 !CHECK: ^bb0(%{{.*}}: f64):
7 !CHECK: %[[C0_1:.*]] = arith.constant 0.000000e+00 : f64
8 !CHECK: omp.yield(%[[C0_1]] : f64)
9 !CHECK: } combiner {
10 !CHECK: ^bb0(%[[ARG0:.*]]: f64, %[[ARG1:.*]]: f64):
11 !CHECK: %[[RES:.*]] = arith.addf %[[ARG0]], %[[ARG1]] {{.*}}: f64
12 !CHECK: omp.yield(%[[RES]] : f64)
13 !CHECK: }
15 !CHECK-LABEL: omp.reduction.declare
16 !CHECK-SAME: @[[RED_I64_NAME:.*]] : i64 init {
17 !CHECK: ^bb0(%{{.*}}: i64):
18 !CHECK: %[[C0_1:.*]] = arith.constant 0 : i64
19 !CHECK: omp.yield(%[[C0_1]] : i64)
20 !CHECK: } combiner {
21 !CHECK: ^bb0(%[[ARG0:.*]]: i64, %[[ARG1:.*]]: i64):
22 !CHECK: %[[RES:.*]] = arith.addi %[[ARG0]], %[[ARG1]] : i64
23 !CHECK: omp.yield(%[[RES]] : i64)
24 !CHECK: }
26 !CHECK-LABEL: omp.reduction.declare
27 !CHECK-SAME: @[[RED_F32_NAME:.*]] : f32 init {
28 !CHECK: ^bb0(%{{.*}}: f32):
29 !CHECK: %[[C0_1:.*]] = arith.constant 0.000000e+00 : f32
30 !CHECK: omp.yield(%[[C0_1]] : f32)
31 !CHECK: } combiner {
32 !CHECK: ^bb0(%[[ARG0:.*]]: f32, %[[ARG1:.*]]: f32):
33 !CHECK: %[[RES:.*]] = arith.addf %[[ARG0]], %[[ARG1]] {{.*}}: f32
34 !CHECK: omp.yield(%[[RES]] : f32)
35 !CHECK: }
37 !CHECK-LABEL: omp.reduction.declare
38 !CHECK-SAME: @[[RED_I32_NAME:.*]] : i32 init {
39 !CHECK: ^bb0(%{{.*}}: i32):
40 !CHECK: %[[C0_1:.*]] = arith.constant 0 : i32
41 !CHECK: omp.yield(%[[C0_1]] : i32)
42 !CHECK: } combiner {
43 !CHECK: ^bb0(%[[ARG0:.*]]: i32, %[[ARG1:.*]]: i32):
44 !CHECK: %[[RES:.*]] = arith.addi %[[ARG0]], %[[ARG1]] : i32
45 !CHECK: omp.yield(%[[RES]] : i32)
46 !CHECK: }
48 !CHECK-LABEL: func.func @_QPsimple_int_reduction
49 !CHECK: %[[XREF:.*]] = fir.alloca i32 {bindc_name = "x", uniq_name = "_QFsimple_int_reductionEx"}
50 !CHECK: %[[C0_2:.*]] = arith.constant 0 : i32
51 !CHECK: fir.store %[[C0_2]] to %[[XREF]] : !fir.ref<i32>
52 !CHECK: omp.parallel
53 !CHECK: %[[I_PVT_REF:.*]] = fir.alloca i32 {adapt.valuebyref, pinned}
54 !CHECK: %[[C1_1:.*]] = arith.constant 1 : i32
55 !CHECK: %[[C100:.*]] = arith.constant 100 : i32
56 !CHECK: %[[C1_2:.*]] = arith.constant 1 : i32
57 !CHECK: omp.wsloop reduction(@[[RED_I32_NAME]] -> %[[XREF]] : !fir.ref<i32>) for (%[[IVAL:.*]]) : i32 = (%[[C1_1]]) to (%[[C100]]) inclusive step (%[[C1_2]])
58 !CHECK: fir.store %[[IVAL]] to %[[I_PVT_REF]] : !fir.ref<i32>
59 !CHECK: %[[I_PVT_VAL:.*]] = fir.load %[[I_PVT_REF]] : !fir.ref<i32>
60 !CHECK: omp.reduction %[[I_PVT_VAL]], %[[XREF]] : i32, !fir.ref<i32>
61 !CHECK: omp.yield
62 !CHECK: omp.terminator
63 !CHECK: return
64 subroutine simple_int_reduction
65 integer :: x
66 x = 0
67 !$omp parallel
68 !$omp do reduction(+:x)
69 do i=1, 100
70 x = x + i
71 end do
72 !$omp end do
73 !$omp end parallel
74 end subroutine
76 !CHECK-LABEL: func.func @_QPsimple_real_reduction
77 !CHECK: %[[XREF:.*]] = fir.alloca f32 {bindc_name = "x", uniq_name = "_QFsimple_real_reductionEx"}
78 !CHECK: %[[C0_2:.*]] = arith.constant 0.000000e+00 : f32
79 !CHECK: fir.store %[[C0_2]] to %[[XREF]] : !fir.ref<f32>
80 !CHECK: omp.parallel
81 !CHECK: %[[I_PVT_REF:.*]] = fir.alloca i32 {adapt.valuebyref, pinned}
82 !CHECK: %[[C1_1:.*]] = arith.constant 1 : i32
83 !CHECK: %[[C100:.*]] = arith.constant 100 : i32
84 !CHECK: %[[C1_2:.*]] = arith.constant 1 : i32
85 !CHECK: omp.wsloop reduction(@[[RED_F32_NAME]] -> %[[XREF]] : !fir.ref<f32>) for (%[[IVAL:.*]]) : i32 = (%[[C1_1]]) to (%[[C100]]) inclusive step (%[[C1_2]])
86 !CHECK: fir.store %[[IVAL]] to %[[I_PVT_REF]] : !fir.ref<i32>
87 !CHECK: %[[I_PVT_VAL_i32:.*]] = fir.load %[[I_PVT_REF]] : !fir.ref<i32>
88 !CHECK: %[[I_PVT_VAL_f32:.*]] = fir.convert %[[I_PVT_VAL_i32]] : (i32) -> f32
89 !CHECK: omp.reduction %[[I_PVT_VAL_f32]], %[[XREF]] : f32, !fir.ref<f32>
90 !CHECK: omp.yield
91 !CHECK: omp.terminator
92 !CHECK: return
93 subroutine simple_real_reduction
94 real :: x
95 x = 0.0
96 !$omp parallel
97 !$omp do reduction(+:x)
98 do i=1, 100
99 x = x + i
100 end do
101 !$omp end do
102 !$omp end parallel
103 end subroutine
105 !CHECK-LABEL: func.func @_QPsimple_int_reduction_switch_order
106 !CHECK: %[[XREF:.*]] = fir.alloca i32 {bindc_name = "x", uniq_name = "_QFsimple_int_reduction_switch_orderEx"}
107 !CHECK: %[[C0_2:.*]] = arith.constant 0 : i32
108 !CHECK: fir.store %[[C0_2]] to %[[XREF]] : !fir.ref<i32>
109 !CHECK: omp.parallel
110 !CHECK: %[[I_PVT_REF:.*]] = fir.alloca i32 {adapt.valuebyref, pinned}
111 !CHECK: %[[C1_1:.*]] = arith.constant 1 : i32
112 !CHECK: %[[C100:.*]] = arith.constant 100 : i32
113 !CHECK: %[[C1_2:.*]] = arith.constant 1 : i32
114 !CHECK: omp.wsloop reduction(@[[RED_I32_NAME]] -> %[[XREF]] : !fir.ref<i32>) for (%[[IVAL:.*]]) : i32 = (%[[C1_1]]) to (%[[C100]]) inclusive step (%[[C1_2]])
115 !CHECK: fir.store %[[IVAL]] to %[[I_PVT_REF]] : !fir.ref<i32>
116 !CHECK: %[[I_PVT_VAL:.*]] = fir.load %[[I_PVT_REF]] : !fir.ref<i32>
117 !CHECK: omp.reduction %[[I_PVT_VAL]], %[[XREF]] : i32, !fir.ref<i32>
118 !CHECK: omp.yield
119 !CHECK: omp.terminator
120 !CHECK: return
121 subroutine simple_int_reduction_switch_order
122 integer :: x
123 x = 0
124 !$omp parallel
125 !$omp do reduction(+:x)
126 do i=1, 100
127 x = i + x
128 end do
129 !$omp end do
130 !$omp end parallel
131 end subroutine
133 !CHECK-LABEL: func.func @_QPsimple_real_reduction_switch_order
134 !CHECK: %[[XREF:.*]] = fir.alloca f32 {bindc_name = "x", uniq_name = "_QFsimple_real_reduction_switch_orderEx"}
135 !CHECK: %[[C0_2:.*]] = arith.constant 0.000000e+00 : f32
136 !CHECK: fir.store %[[C0_2]] to %[[XREF]] : !fir.ref<f32>
137 !CHECK: omp.parallel
138 !CHECK: %[[I_PVT_REF:.*]] = fir.alloca i32 {adapt.valuebyref, pinned}
139 !CHECK: %[[C1_1:.*]] = arith.constant 1 : i32
140 !CHECK: %[[C100:.*]] = arith.constant 100 : i32
141 !CHECK: %[[C1_2:.*]] = arith.constant 1 : i32
142 !CHECK: omp.wsloop reduction(@[[RED_F32_NAME]] -> %[[XREF]] : !fir.ref<f32>) for (%[[IVAL:.*]]) : i32 = (%[[C1_1]]) to (%[[C100]]) inclusive step (%[[C1_2]])
143 !CHECK: fir.store %[[IVAL]] to %[[I_PVT_REF]] : !fir.ref<i32>
144 !CHECK: %[[I_PVT_VAL_i32:.*]] = fir.load %[[I_PVT_REF]] : !fir.ref<i32>
145 !CHECK: %[[I_PVT_VAL_f32:.*]] = fir.convert %[[I_PVT_VAL_i32]] : (i32) -> f32
146 !CHECK: omp.reduction %[[I_PVT_VAL_f32]], %[[XREF]] : f32, !fir.ref<f32>
147 !CHECK: omp.yield
148 !CHECK: omp.terminator
149 !CHECK: return
150 subroutine simple_real_reduction_switch_order
151 real :: x
152 x = 0.0
153 !$omp parallel
154 !$omp do reduction(+:x)
155 do i=1, 100
156 x = i + x
157 end do
158 !$omp end do
159 !$omp end parallel
160 end subroutine
162 !CHECK-LABEL: func.func @_QPmultiple_int_reductions_same_type
163 !CHECK: %[[XREF:.*]] = fir.alloca i32 {bindc_name = "x", uniq_name = "_QFmultiple_int_reductions_same_typeEx"}
164 !CHECK: %[[YREF:.*]] = fir.alloca i32 {bindc_name = "y", uniq_name = "_QFmultiple_int_reductions_same_typeEy"}
165 !CHECK: %[[ZREF:.*]] = fir.alloca i32 {bindc_name = "z", uniq_name = "_QFmultiple_int_reductions_same_typeEz"}
166 !CHECK: omp.parallel
167 !CHECK: %[[I_PVT_REF:.*]] = fir.alloca i32 {adapt.valuebyref, pinned}
168 !CHECK: omp.wsloop reduction(@[[RED_I32_NAME]] -> %[[XREF]] : !fir.ref<i32>, @[[RED_I32_NAME]] -> %[[YREF]] : !fir.ref<i32>, @[[RED_I32_NAME]] -> %[[ZREF]] : !fir.ref<i32>) for (%[[IVAL]]) : i32
169 !CHECK: fir.store %[[IVAL]] to %[[I_PVT_REF]] : !fir.ref<i32>
170 !CHECK: %[[I_PVT_VAL1:.*]] = fir.load %[[I_PVT_REF]] : !fir.ref<i32>
171 !CHECK: omp.reduction %[[I_PVT_VAL1]], %[[XREF]] : i32, !fir.ref<i32>
172 !CHECK: %[[I_PVT_VAL2:.*]] = fir.load %[[I_PVT_REF]] : !fir.ref<i32>
173 !CHECK: omp.reduction %[[I_PVT_VAL2]], %[[YREF]] : i32, !fir.ref<i32>
174 !CHECK: %[[I_PVT_VAL3:.*]] = fir.load %[[I_PVT_REF]] : !fir.ref<i32>
175 !CHECK: omp.reduction %[[I_PVT_VAL3]], %[[ZREF]] : i32, !fir.ref<i32>
176 !CHECK: omp.yield
177 !CHECK: omp.terminator
178 !CHECK: return
179 subroutine multiple_int_reductions_same_type
180 integer :: x,y,z
181 x = 0
182 y = 0
183 z = 0
184 !$omp parallel
185 !$omp do reduction(+:x,y,z)
186 do i=1, 100
187 x = x + i
188 y = y + i
189 z = z + i
190 end do
191 !$omp end do
192 !$omp end parallel
193 end subroutine
195 !CHECK-LABEL: func.func @_QPmultiple_real_reductions_same_type
196 !CHECK: %[[XREF:.*]] = fir.alloca f32 {bindc_name = "x", uniq_name = "_QFmultiple_real_reductions_same_typeEx"}
197 !CHECK: %[[YREF:.*]] = fir.alloca f32 {bindc_name = "y", uniq_name = "_QFmultiple_real_reductions_same_typeEy"}
198 !CHECK: %[[ZREF:.*]] = fir.alloca f32 {bindc_name = "z", uniq_name = "_QFmultiple_real_reductions_same_typeEz"}
199 !CHECK: omp.parallel
200 !CHECK: %[[I_PVT_REF:.*]] = fir.alloca i32 {adapt.valuebyref, pinned}
201 !CHECK: omp.wsloop reduction(@[[RED_F32_NAME]] -> %[[XREF]] : !fir.ref<f32>, @[[RED_F32_NAME]] -> %[[YREF]] : !fir.ref<f32>, @[[RED_F32_NAME]] -> %[[ZREF]] : !fir.ref<f32>) for (%[[IVAL]]) : i32
202 !CHECK: fir.store %[[IVAL]] to %[[I_PVT_REF]] : !fir.ref<i32>
203 !CHECK: %[[I_PVT_VAL1_I32:.*]] = fir.load %[[I_PVT_REF]] : !fir.ref<i32>
204 !CHECK: %[[I_PVT_VAL1_F32:.*]] = fir.convert %[[I_PVT_VAL1_I32]] : (i32) -> f32
205 !CHECK: omp.reduction %[[I_PVT_VAL1_F32]], %[[XREF]] : f32, !fir.ref<f32>
206 !CHECK: %[[I_PVT_VAL2_I32:.*]] = fir.load %[[I_PVT_REF]] : !fir.ref<i32>
207 !CHECK: %[[I_PVT_VAL2_F32:.*]] = fir.convert %[[I_PVT_VAL2_I32]] : (i32) -> f32
208 !CHECK: omp.reduction %[[I_PVT_VAL2_F32]], %[[YREF]] : f32, !fir.ref<f32>
209 !CHECK: %[[I_PVT_VAL3_I32:.*]] = fir.load %[[I_PVT_REF]] : !fir.ref<i32>
210 !CHECK: %[[I_PVT_VAL3_F32:.*]] = fir.convert %[[I_PVT_VAL3_I32]] : (i32) -> f32
211 !CHECK: omp.reduction %[[I_PVT_VAL3_F32]], %[[ZREF]] : f32, !fir.ref<f32>
212 !CHECK: omp.yield
213 !CHECK: omp.terminator
214 !CHECK: return
215 subroutine multiple_real_reductions_same_type
216 real :: x,y,z
217 x = 0.0
218 y = 0.0
219 z = 0.0
220 !$omp parallel
221 !$omp do reduction(+:x,y,z)
222 do i=1, 100
223 x = x + i
224 y = y + i
225 z = z + i
226 end do
227 !$omp end do
228 !$omp end parallel
229 end subroutine
231 !CHECK-LABEL: func.func @_QPmultiple_reductions_different_type
232 !CHECK: %[[WREF:.*]] = fir.alloca f64 {bindc_name = "w", uniq_name = "_QFmultiple_reductions_different_typeEw"}
233 !CHECK: %[[XREF:.*]] = fir.alloca i32 {bindc_name = "x", uniq_name = "_QFmultiple_reductions_different_typeEx"}
234 !CHECK: %[[YREF:.*]] = fir.alloca i64 {bindc_name = "y", uniq_name = "_QFmultiple_reductions_different_typeEy"}
235 !CHECK: %[[ZREF:.*]] = fir.alloca f32 {bindc_name = "z", uniq_name = "_QFmultiple_reductions_different_typeEz"}
236 !CHECK: omp.parallel
237 !CHECK: %[[I_PVT_REF:.*]] = fir.alloca i32 {adapt.valuebyref, pinned}
238 !CHECK: omp.wsloop reduction(@[[RED_I32_NAME]] -> %[[XREF]] : !fir.ref<i32>, @[[RED_I64_NAME]] -> %[[YREF]] : !fir.ref<i64>, @[[RED_F32_NAME]] -> %[[ZREF]] : !fir.ref<f32>, @[[RED_F64_NAME]] -> %[[WREF]] : !fir.ref<f64>) for (%[[IVAL:.*]]) : i32
239 !CHECK: fir.store %[[IVAL]] to %[[I_PVT_REF]] : !fir.ref<i32>
240 !CHECK: %[[I_PVT_VAL1_I32:.*]] = fir.load %[[I_PVT_REF]] : !fir.ref<i32>
241 !CHECK: omp.reduction %[[I_PVT_VAL1_I32]], %[[XREF]] : i32, !fir.ref<i32>
242 !CHECK: %[[I_PVT_VAL2_I32:.*]] = fir.load %[[I_PVT_REF]] : !fir.ref<i32>
243 !CHECK: %[[I_PVT_VAL2_I64:.*]] = fir.convert %[[I_PVT_VAL2_I32]] : (i32) -> i64
244 !CHECK: omp.reduction %[[I_PVT_VAL2_I64]], %[[YREF]] : i64, !fir.ref<i64>
245 !CHECK: %[[I_PVT_VAL3_I32:.*]] = fir.load %[[I_PVT_REF]] : !fir.ref<i32>
246 !CHECK: %[[I_PVT_VAL3_F32:.*]] = fir.convert %[[I_PVT_VAL3_I32]] : (i32) -> f32
247 !CHECK: omp.reduction %[[I_PVT_VAL3_F32]], %[[ZREF]] : f32, !fir.ref<f32>
248 !CHECK: %[[I_PVT_VAL4_I32:.*]] = fir.load %[[I_PVT_REF]] : !fir.ref<i32>
249 !CHECK: %[[I_PVT_VAL4_F64:.*]] = fir.convert %[[I_PVT_VAL4_I32]] : (i32) -> f64
250 !CHECK: omp.reduction %[[I_PVT_VAL4_F64]], %[[WREF]] : f64, !fir.ref<f64>
251 !CHECK: omp.yield
252 !CHECK: omp.terminator
253 !CHECK: return
254 subroutine multiple_reductions_different_type
255 integer :: x
256 integer(kind=8) :: y
257 real :: z
258 real(kind=8) :: w
259 x = 0
260 y = 0
261 z = 0.0
262 w = 0.0
263 !$omp parallel
264 !$omp do reduction(+:x,y,z,w)
265 do i=1, 100
266 x = x + i
267 y = y + i
268 z = z + i
269 w = w + i
270 end do
271 !$omp end do
272 !$omp end parallel
273 end subroutine