1 ! Tests for 2.9.3.1 Simd
3 ! The "if" clause was added to the "simd" directive in OpenMP 5.0.
4 ! RUN: %flang_fc1 -flang-experimental-hlfir -emit-hlfir -fopenmp -fopenmp-version=50 %s -o - | FileCheck %s
5 ! RUN: bbc -hlfir -emit-hlfir -fopenmp -fopenmp-version=50 %s -o - | FileCheck %s
7 !CHECK: omp.declare_reduction @[[REDUCER:.*]] : i32
9 !CHECK-LABEL: func @_QPsimd()
13 ! CHECK: %[[LB:.*]] = arith.constant 1 : i32
14 ! CHECK-NEXT: %[[UB:.*]] = arith.constant 9 : i32
15 ! CHECK-NEXT: %[[STEP:.*]] = arith.constant 1 : i32
16 ! CHECK-NEXT: omp.simd {
17 ! CHECK-NEXT: omp.loop_nest (%[[I:.*]]) : i32 = (%[[LB]]) to (%[[UB]]) inclusive step (%[[STEP]]) {
19 ! CHECK: fir.store %[[I]] to %[[LOCAL:.*]]#1 : !fir.ref<i32>
20 ! CHECK: %[[LD:.*]] = fir.load %[[LOCAL]]#0 : !fir.ref<i32>
21 ! CHECK: fir.call @_FortranAioOutputInteger32({{.*}}, %[[LD]]) {{.*}}: (!fir.ref<i8>, i32) -> i1
27 !CHECK-LABEL: func @_QPsimd_with_if_clause
28 subroutine simd_with_if_clause(n
, threshold
)
29 ! CHECK: %[[ARG_N:.*]]:2 = hlfir.declare %{{.*}} dummy_scope %{{[0-9]+}} {uniq_name = "_QFsimd_with_if_clauseEn"} : (!fir.ref<i32>, !fir.dscope) -> (!fir.ref<i32>, !fir.ref<i32>)
30 integer :: i
, n
, threshold
31 !$OMP SIMD IF( n .GE. threshold )
32 ! CHECK: %[[COND:.*]] = arith.cmpi sge
33 ! CHECK: %[[LB:.*]] = arith.constant 1 : i32
34 ! CHECK: %[[UB:.*]] = fir.load %[[ARG_N]]#0
35 ! CHECK: %[[STEP:.*]] = arith.constant 1 : i32
36 ! CHECK: omp.simd if(%[[COND:.*]]) {
37 ! CHECK-NEXT: omp.loop_nest (%[[I:.*]]) : i32 = (%[[LB]]) to (%[[UB]]) inclusive step (%[[STEP]]) {
39 ! CHECK: fir.store %[[I]] to %[[LOCAL:.*]]#1 : !fir.ref<i32>
40 ! CHECK: %[[LD:.*]] = fir.load %[[LOCAL]]#0 : !fir.ref<i32>
41 ! CHECK: fir.call @_FortranAioOutputInteger32({{.*}}, %[[LD]]) {{.*}}: (!fir.ref<i8>, i32) -> i1
47 !CHECK-LABEL: func @_QPsimd_with_simdlen_clause
48 subroutine simd_with_simdlen_clause(n
, threshold
)
49 ! CHECK: %[[ARG_N:.*]]:2 = hlfir.declare %{{.*}} dummy_scope %{{[0-9]+}} {uniq_name = "_QFsimd_with_simdlen_clauseEn"} : (!fir.ref<i32>, !fir.dscope) -> (!fir.ref<i32>, !fir.ref<i32>)
50 integer :: i
, n
, threshold
52 ! CHECK: %[[LB:.*]] = arith.constant 1 : i32
53 ! CHECK: %[[UB:.*]] = fir.load %[[ARG_N]]#0
54 ! CHECK: %[[STEP:.*]] = arith.constant 1 : i32
55 ! CHECK: omp.simd simdlen(2) {
56 ! CHECK-NEXT: omp.loop_nest (%[[I:.*]]) : i32 = (%[[LB]]) to (%[[UB]]) inclusive step (%[[STEP]]) {
58 ! CHECK: fir.store %[[I]] to %[[LOCAL:.*]]#1 : !fir.ref<i32>
59 ! CHECK: %[[LD:.*]] = fir.load %[[LOCAL]]#0 : !fir.ref<i32>
60 ! CHECK: fir.call @_FortranAioOutputInteger32({{.*}}, %[[LD]]) {{.*}}: (!fir.ref<i8>, i32) -> i1
66 !CHECK-LABEL: func @_QPsimd_with_simdlen_clause_from_param
67 subroutine simd_with_simdlen_clause_from_param(n
, threshold
)
68 ! CHECK: %[[ARG_N:.*]]:2 = hlfir.declare %{{.*}} dummy_scope %{{[0-9]+}} {uniq_name = "_QFsimd_with_simdlen_clause_from_paramEn"} : (!fir.ref<i32>, !fir.dscope) -> (!fir.ref<i32>, !fir.ref<i32>)
69 integer :: i
, n
, threshold
70 integer, parameter :: simdlen
= 2;
71 !$OMP SIMD SIMDLEN(simdlen)
72 ! CHECK: %[[LB:.*]] = arith.constant 1 : i32
73 ! CHECK: %[[UB:.*]] = fir.load %[[ARG_N]]#0
74 ! CHECK: %[[STEP:.*]] = arith.constant 1 : i32
75 ! CHECK: omp.simd simdlen(2) {
76 ! CHECK-NEXT: omp.loop_nest (%[[I:.*]]) : i32 = (%[[LB]]) to (%[[UB]]) inclusive step (%[[STEP]]) {
78 ! CHECK: fir.store %[[I]] to %[[LOCAL:.*]]#1 : !fir.ref<i32>
79 ! CHECK: %[[LD:.*]] = fir.load %[[LOCAL]]#0 : !fir.ref<i32>
80 ! CHECK: fir.call @_FortranAioOutputInteger32({{.*}}, %[[LD]]) {{.*}}: (!fir.ref<i8>, i32) -> i1
86 !CHECK-LABEL: func @_QPsimd_with_simdlen_clause_from_expr_from_param
87 subroutine simd_with_simdlen_clause_from_expr_from_param(n
, threshold
)
88 ! CHECK: %[[ARG_N:.*]]:2 = hlfir.declare %{{.*}} dummy_scope %{{[0-9]+}} {uniq_name = "_QFsimd_with_simdlen_clause_from_expr_from_paramEn"} : (!fir.ref<i32>, !fir.dscope) -> (!fir.ref<i32>, !fir.ref<i32>)
89 integer :: i
, n
, threshold
90 integer, parameter :: simdlen
= 2;
91 !$OMP SIMD SIMDLEN(simdlen*2 + 2)
92 ! CHECK: %[[LB:.*]] = arith.constant 1 : i32
93 ! CHECK: %[[UB:.*]] = fir.load %[[ARG_N]]#0
94 ! CHECK: %[[STEP:.*]] = arith.constant 1 : i32
95 ! CHECK: omp.simd simdlen(6) {
96 ! CHECK-NEXT: omp.loop_nest (%[[I:.*]]) : i32 = (%[[LB]]) to (%[[UB]]) inclusive step (%[[STEP]]) {
98 ! CHECK: fir.store %[[I]] to %[[LOCAL:.*]]#1 : !fir.ref<i32>
99 ! CHECK: %[[LD:.*]] = fir.load %[[LOCAL]]#0 : !fir.ref<i32>
100 ! CHECK: fir.call @_FortranAioOutputInteger32({{.*}}, %[[LD]]) {{.*}}: (!fir.ref<i8>, i32) -> i1
106 !CHECK-LABEL: func @_QPsimd_with_safelen_clause
107 subroutine simd_with_safelen_clause(n
, threshold
)
108 ! CHECK: %[[ARG_N:.*]]:2 = hlfir.declare %{{.*}} dummy_scope %{{[0-9]+}} {uniq_name = "_QFsimd_with_safelen_clauseEn"} : (!fir.ref<i32>, !fir.dscope) -> (!fir.ref<i32>, !fir.ref<i32>)
109 integer :: i
, n
, threshold
110 !$OMP SIMD SAFELEN(2)
111 ! CHECK: %[[LB:.*]] = arith.constant 1 : i32
112 ! CHECK: %[[UB:.*]] = fir.load %[[ARG_N]]#0
113 ! CHECK: %[[STEP:.*]] = arith.constant 1 : i32
114 ! CHECK: omp.simd safelen(2) {
115 ! CHECK-NEXT: omp.loop_nest (%[[I:.*]]) : i32 = (%[[LB]]) to (%[[UB]]) inclusive step (%[[STEP]]) {
117 ! CHECK: fir.store %[[I]] to %[[LOCAL:.*]]#1 : !fir.ref<i32>
118 ! CHECK: %[[LD:.*]] = fir.load %[[LOCAL]]#0 : !fir.ref<i32>
119 ! CHECK: fir.call @_FortranAioOutputInteger32({{.*}}, %[[LD]]) {{.*}}: (!fir.ref<i8>, i32) -> i1
125 !CHECK-LABEL: func @_QPsimd_with_safelen_clause_from_expr_from_param
126 subroutine simd_with_safelen_clause_from_expr_from_param(n
, threshold
)
127 ! CHECK: %[[ARG_N:.*]]:2 = hlfir.declare %{{.*}} dummy_scope %{{[0-9]+}} {uniq_name = "_QFsimd_with_safelen_clause_from_expr_from_paramEn"} : (!fir.ref<i32>, !fir.dscope) -> (!fir.ref<i32>, !fir.ref<i32>)
128 integer :: i
, n
, threshold
129 integer, parameter :: safelen
= 2;
130 !$OMP SIMD SAFELEN(safelen*2 + 2)
131 ! CHECK: %[[LB:.*]] = arith.constant 1 : i32
132 ! CHECK: %[[UB:.*]] = fir.load %[[ARG_N]]#0
133 ! CHECK: %[[STEP:.*]] = arith.constant 1 : i32
134 ! CHECK: omp.simd safelen(6) {
135 ! CHECK-NEXT: omp.loop_nest (%[[I:.*]]) : i32 = (%[[LB]]) to (%[[UB]]) inclusive step (%[[STEP]]) {
137 ! CHECK: fir.store %[[I]] to %[[LOCAL:.*]]#1 : !fir.ref<i32>
138 ! CHECK: %[[LD:.*]] = fir.load %[[LOCAL]]#0 : !fir.ref<i32>
139 ! CHECK: fir.call @_FortranAioOutputInteger32({{.*}}, %[[LD]]) {{.*}}: (!fir.ref<i8>, i32) -> i1
145 !CHECK-LABEL: func @_QPsimd_with_simdlen_safelen_clause
146 subroutine simd_with_simdlen_safelen_clause(n
, threshold
)
147 ! CHECK: %[[ARG_N:.*]]:2 = hlfir.declare %{{.*}} dummy_scope %{{[0-9]+}} {uniq_name = "_QFsimd_with_simdlen_safelen_clauseEn"} : (!fir.ref<i32>, !fir.dscope) -> (!fir.ref<i32>, !fir.ref<i32>)
148 integer :: i
, n
, threshold
149 !$OMP SIMD SIMDLEN(1) SAFELEN(2)
150 ! CHECK: %[[LB:.*]] = arith.constant 1 : i32
151 ! CHECK: %[[UB:.*]] = fir.load %[[ARG_N]]#0
152 ! CHECK: %[[STEP:.*]] = arith.constant 1 : i32
153 ! CHECK: omp.simd safelen(2) simdlen(1) {
154 ! CHECK-NEXT: omp.loop_nest (%[[I:.*]]) : i32 = (%[[LB]]) to (%[[UB]]) inclusive step (%[[STEP]]) {
156 ! CHECK: fir.store %[[I]] to %[[LOCAL:.*]]#1 : !fir.ref<i32>
157 ! CHECK: %[[LD:.*]] = fir.load %[[LOCAL]]#0 : !fir.ref<i32>
158 ! CHECK: fir.call @_FortranAioOutputInteger32({{.*}}, %[[LD]]) {{.*}}: (!fir.ref<i8>, i32) -> i1
164 !CHECK-LABEL: func @_QPsimd_with_collapse_clause
165 subroutine simd_with_collapse_clause(n
)
168 ! CHECK: %[[LOWER_I:.*]] = arith.constant 1 : i32
169 ! CHECK: %[[UPPER_I:.*]] = fir.load %[[PARAM_ARG:.*]] : !fir.ref<i32>
170 ! CHECK: %[[STEP_I:.*]] = arith.constant 1 : i32
171 ! CHECK: %[[LOWER_J:.*]] = arith.constant 1 : i32
172 ! CHECK: %[[UPPER_J:.*]] = fir.load %[[PARAM_ARG:.*]] : !fir.ref<i32>
173 ! CHECK: %[[STEP_J:.*]] = arith.constant 1 : i32
175 ! CHECK-NEXT: omp.loop_nest (%[[ARG_0:.*]], %[[ARG_1:.*]]) : i32 = (
176 ! CHECK-SAME: %[[LOWER_I]], %[[LOWER_J]]) to (
177 ! CHECK-SAME: %[[UPPER_I]], %[[UPPER_J]]) inclusive step (
178 ! CHECK-SAME: %[[STEP_I]], %[[STEP_J]]) {
179 !$OMP SIMD COLLAPSE(2)
189 !CHECK: func.func @_QPsimdloop_aligned_cptr(%[[ARG_A:.*]]: !fir.ref
190 !CHECK-SAME: <!fir.type<_QM__fortran_builtinsT__builtin_c_ptr
191 !CHECK-SAME: {__address:i64}>> {fir.bindc_name = "a"}) {
192 !CHECK: %[[A_DECL:.*]]:2 = hlfir.declare %[[ARG_A]] dummy_scope %0
193 !CHECK-SAME: {uniq_name = "_QFsimdloop_aligned_cptrEa"} :
194 !CHECK-SAME: (!fir.ref<!fir.type<_QM__fortran_builtinsT__builtin_c_ptr{__address:i64}>>, !fir.dscope) ->
195 !CHECK-SAME: (!fir.ref<!fir.type<_QM__fortran_builtinsT__builtin_c_ptr{__address:i64}>>,
196 !CHECK-SAME: !fir.ref<!fir.type<_QM__fortran_builtinsT__builtin_c_ptr{__address:i64}>>)
197 subroutine simdloop_aligned_cptr( A
)
201 !CHECK: omp.simd aligned(%[[A_DECL]]#1 : !fir.ref
202 !CHECK-SAME: <!fir.type<_QM__fortran_builtinsT__builtin_c_ptr{__address:i64}>>
203 !CHECK-SAME: -> 256 : i64)
204 !$OMP SIMD ALIGNED(A:256)
211 !CHECK-LABEL: func @_QPsimdloop_aligned_allocatable
212 subroutine simdloop_aligned_allocatable()
214 integer, allocatable
:: A(:)
216 !CHECK: %[[A_PTR:.*]] = fir.alloca !fir.box<!fir.heap<!fir.array<?xi32>>> {bindc_name = "a",
217 !CHECK-SAME: uniq_name = "_QFsimdloop_aligned_allocatableEa"}
218 !CHECK: %[[A_DECL:.*]]:2 = hlfir.declare %[[A_PTR]] {fortran_attrs = #fir.var_attrs<allocatable>,
219 !CHECK-SAME: uniq_name = "_QFsimdloop_aligned_allocatableEa"} :
220 !CHECK-SAME: (!fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>) ->
221 !CHECK-SAME: (!fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>)
222 !CHECK: omp.simd aligned(%[[A_DECL]]#1 : !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>> -> 256 : i64)
223 !$OMP SIMD ALIGNED(A:256)
229 !CHECK-LABEL: func @_QPsimd_with_nontemporal_clause
230 subroutine simd_with_nontemporal_clause(n
)
231 !CHECK: %[[A_DECL:.*]]:2 = hlfir.declare %{{.*}} {uniq_name = "_QFsimd_with_nontemporal_clauseEa"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
232 !CHECK: %[[C_DECL:.*]]:2 = hlfir.declare %{{.*}} {uniq_name = "_QFsimd_with_nontemporal_clauseEc"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
235 !CHECK: %[[LB:.*]] = arith.constant 1 : i32
236 !CHECK: %[[UB:.*]] = fir.load %{{.*}}#0 : !fir.ref<i32>
237 !CHECK: %[[STEP:.*]] = arith.constant 1 : i32
238 !CHECK: omp.simd nontemporal(%[[A_DECL]]#1, %[[C_DECL]]#1 : !fir.ref<i32>, !fir.ref<i32>) {
239 !CHECK-NEXT: omp.loop_nest (%[[I:.*]]) : i32 = (%[[LB]]) to (%[[UB]]) inclusive step (%[[STEP]]) {
240 !$OMP SIMD NONTEMPORAL(A, C)
247 !CHECK-LABEL: func.func @_QPlastprivate_with_simd() {
248 subroutine lastprivate_with_simd
250 !CHECK: %[[VAR_SUM:.*]] = fir.alloca f32 {bindc_name = "sum", uniq_name = "_QFlastprivate_with_simdEsum"}
251 !CHECK: %[[VAR_SUM_DECLARE:.*]]:2 = hlfir.declare %[[VAR_SUM]] {{.*}}
252 !CHECK: %[[VAR_SUM_PINNED:.*]] = fir.alloca f32 {bindc_name = "sum", pinned, uniq_name = "_QFlastprivate_with_simdEsum"}
253 !CHECK: %[[VAR_SUM_PINNED_DECLARE:.*]]:2 = hlfir.declare %[[VAR_SUM_PINNED]] {{.*}}
261 !CHECK: omp.loop_nest (%[[ARG:.*]]) : i32 = ({{.*}} to ({{.*}}) inclusive step ({{.*}}) {
262 !CHECK: %[[ADD_RESULT:.*]] = arith.addi {{.*}}
263 !CHECK: %[[ADD_RESULT_CONVERT:.*]] = fir.convert %[[ADD_RESULT]] : (i32) -> f32
264 !CHECK: hlfir.assign %[[ADD_RESULT_CONVERT]] to %[[VAR_SUM_PINNED_DECLARE]]#0 : f32, !fir.ref<f32>
265 !CHECK: %[[SELECT_RESULT:.*]] = arith.select {{.*}}, {{.*}}, {{.*}} : i1
266 !CHECK: fir.if %[[SELECT_RESULT]] {
267 !CHECK: %[[LOADED_SUM:.*]] = fir.load %[[VAR_SUM_PINNED_DECLARE]]#0 : !fir.ref<f32>
268 !CHECK: hlfir.assign %[[LOADED_SUM]] to %[[VAR_SUM_DECLARE]]#0 : f32, !fir.ref<f32>
273 !$omp simd lastprivate(sum)
279 !CHECK-LABEL: func @_QPsimd_with_reduction_clause()
280 subroutine simd_with_reduction_clause
283 ! CHECK: %[[LB:.*]] = arith.constant 1 : i32
284 ! CHECK-NEXT: %[[UB:.*]] = arith.constant 9 : i32
285 ! CHECK-NEXT: %[[STEP:.*]] = arith.constant 1 : i32
286 ! CHECK-NEXT: omp.simd reduction(@[[REDUCER]] %[[X:.*]]#0 -> %[[X_RED:.*]] : !fir.ref<i32>) {
287 ! CHECK-NEXT: omp.loop_nest (%[[I:.*]]) : i32 = (%[[LB]]) to (%[[UB]]) inclusive step (%[[STEP]]) {
288 !$omp simd reduction(+:x)
290 ! CHECK: %[[X_DECL:.*]]:2 = hlfir.declare %[[X_RED]] {uniq_name = "_QFsimd_with_reduction_clauseEx"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
291 ! CHECK: fir.store %[[I]] to %[[LOCAL:.*]]#1 : !fir.ref<i32>
292 ! CHECK: %[[X_LD:.*]] = fir.load %[[X_DECL]]#0 : !fir.ref<i32>
293 ! CHECK: %[[I_LD:.*]] = fir.load %[[LOCAL]]#0 : !fir.ref<i32>
294 ! CHECK: %[[SUM:.*]] = arith.addi %[[X_LD]], %[[I_LD]] : i32
295 ! CHECK: hlfir.assign %[[SUM]] to %[[X_DECL]]#0 : i32, !fir.ref<i32>