Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Lower / OpenMP / simd.f90
blob47596cccdbc121643ea40da0e82c88234d4942b4
1 ! Tests for 2.9.3.1 Simd
3 ! RUN: bbc -fopenmp -emit-fir %s -o - | FileCheck %s
5 !CHECK-LABEL: func @_QPsimdloop()
6 subroutine simdloop
7 integer :: i
8 !$OMP SIMD
9 ! CHECK: %[[LB:.*]] = arith.constant 1 : i32
10 ! CHECK-NEXT: %[[UB:.*]] = arith.constant 9 : i32
11 ! CHECK-NEXT: %[[STEP:.*]] = arith.constant 1 : i32
12 ! CHECK-NEXT: omp.simdloop for (%[[I:.*]]) : i32 = (%[[LB]]) to (%[[UB]]) inclusive step (%[[STEP]]) {
13 do i=1, 9
14 ! CHECK: fir.store %[[I]] to %[[LOCAL:.*]] : !fir.ref<i32>
15 ! CHECK: %[[LD:.*]] = fir.load %[[LOCAL]] : !fir.ref<i32>
16 ! CHECK: fir.call @_FortranAioOutputInteger32({{.*}}, %[[LD]]) {{.*}}: (!fir.ref<i8>, i32) -> i1
17 print*, i
18 end do
19 !$OMP END SIMD
20 end subroutine
22 !CHECK-LABEL: func @_QPsimdloop_with_if_clause
23 subroutine simdloop_with_if_clause(n, threshold)
24 integer :: i, n, threshold
25 !$OMP SIMD IF( n .GE. threshold )
26 ! CHECK: %[[LB:.*]] = arith.constant 1 : i32
27 ! CHECK: %[[UB:.*]] = fir.load %arg0
28 ! CHECK: %[[STEP:.*]] = arith.constant 1 : i32
29 ! CHECK: %[[COND:.*]] = arith.cmpi sge
30 ! CHECK: omp.simdloop if(%[[COND:.*]]) for (%[[I:.*]]) : i32 = (%[[LB]]) to (%[[UB]]) inclusive step (%[[STEP]]) {
31 do i = 1, n
32 ! CHECK: fir.store %[[I]] to %[[LOCAL:.*]] : !fir.ref<i32>
33 ! CHECK: %[[LD:.*]] = fir.load %[[LOCAL]] : !fir.ref<i32>
34 ! CHECK: fir.call @_FortranAioOutputInteger32({{.*}}, %[[LD]]) {{.*}}: (!fir.ref<i8>, i32) -> i1
35 print*, i
36 end do
37 !$OMP END SIMD
38 end subroutine
40 !CHECK-LABEL: func @_QPsimdloop_with_simdlen_clause
41 subroutine simdloop_with_simdlen_clause(n, threshold)
42 integer :: i, n, threshold
43 !$OMP SIMD SIMDLEN(2)
44 ! CHECK: %[[LB:.*]] = arith.constant 1 : i32
45 ! CHECK: %[[UB:.*]] = fir.load %arg0
46 ! CHECK: %[[STEP:.*]] = arith.constant 1 : i32
47 ! CHECK: omp.simdloop simdlen(2) for (%[[I:.*]]) : i32 = (%[[LB]]) to (%[[UB]]) inclusive step (%[[STEP]]) {
48 do i = 1, n
49 ! CHECK: fir.store %[[I]] to %[[LOCAL:.*]] : !fir.ref<i32>
50 ! CHECK: %[[LD:.*]] = fir.load %[[LOCAL]] : !fir.ref<i32>
51 ! CHECK: fir.call @_FortranAioOutputInteger32({{.*}}, %[[LD]]) {{.*}}: (!fir.ref<i8>, i32) -> i1
52 print*, i
53 end do
54 !$OMP END SIMD
55 end subroutine
57 !CHECK-LABEL: func @_QPsimdloop_with_simdlen_clause_from_param
58 subroutine simdloop_with_simdlen_clause_from_param(n, threshold)
59 integer :: i, n, threshold
60 integer, parameter :: simdlen = 2;
61 !$OMP SIMD SIMDLEN(simdlen)
62 ! CHECK: %[[LB:.*]] = arith.constant 1 : i32
63 ! CHECK: %[[UB:.*]] = fir.load %arg0
64 ! CHECK: %[[STEP:.*]] = arith.constant 1 : i32
65 ! CHECK: omp.simdloop simdlen(2) for (%[[I:.*]]) : i32 = (%[[LB]]) to (%[[UB]]) inclusive step (%[[STEP]]) {
66 do i = 1, n
67 ! CHECK: fir.store %[[I]] to %[[LOCAL:.*]] : !fir.ref<i32>
68 ! CHECK: %[[LD:.*]] = fir.load %[[LOCAL]] : !fir.ref<i32>
69 ! CHECK: fir.call @_FortranAioOutputInteger32({{.*}}, %[[LD]]) {{.*}}: (!fir.ref<i8>, i32) -> i1
70 print*, i
71 end do
72 !$OMP END SIMD
73 end subroutine
75 !CHECK-LABEL: func @_QPsimdloop_with_simdlen_clause_from_expr_from_param
76 subroutine simdloop_with_simdlen_clause_from_expr_from_param(n, threshold)
77 integer :: i, n, threshold
78 integer, parameter :: simdlen = 2;
79 !$OMP SIMD SIMDLEN(simdlen*2 + 2)
80 ! CHECK: %[[LB:.*]] = arith.constant 1 : i32
81 ! CHECK: %[[UB:.*]] = fir.load %arg0
82 ! CHECK: %[[STEP:.*]] = arith.constant 1 : i32
83 ! CHECK: omp.simdloop simdlen(6) for (%[[I:.*]]) : i32 = (%[[LB]]) to (%[[UB]]) inclusive step (%[[STEP]]) {
84 do i = 1, n
85 ! CHECK: fir.store %[[I]] to %[[LOCAL:.*]] : !fir.ref<i32>
86 ! CHECK: %[[LD:.*]] = fir.load %[[LOCAL]] : !fir.ref<i32>
87 ! CHECK: fir.call @_FortranAioOutputInteger32({{.*}}, %[[LD]]) {{.*}}: (!fir.ref<i8>, i32) -> i1
88 print*, i
89 end do
90 !$OMP END SIMD
91 end subroutine
93 !CHECK-LABEL: func @_QPsimdloop_with_safelen_clause
94 subroutine simdloop_with_safelen_clause(n, threshold)
95 integer :: i, n, threshold
96 !$OMP SIMD SAFELEN(2)
97 ! CHECK: %[[LB:.*]] = arith.constant 1 : i32
98 ! CHECK: %[[UB:.*]] = fir.load %arg0
99 ! CHECK: %[[STEP:.*]] = arith.constant 1 : i32
100 ! CHECK: omp.simdloop safelen(2) for (%[[I:.*]]) : i32 = (%[[LB]]) to (%[[UB]]) inclusive step (%[[STEP]]) {
101 do i = 1, n
102 ! CHECK: fir.store %[[I]] to %[[LOCAL:.*]] : !fir.ref<i32>
103 ! CHECK: %[[LD:.*]] = fir.load %[[LOCAL]] : !fir.ref<i32>
104 ! CHECK: fir.call @_FortranAioOutputInteger32({{.*}}, %[[LD]]) {{.*}}: (!fir.ref<i8>, i32) -> i1
105 print*, i
106 end do
107 !$OMP END SIMD
108 end subroutine
110 !CHECK-LABEL: func @_QPsimdloop_with_safelen_clause_from_expr_from_param
111 subroutine simdloop_with_safelen_clause_from_expr_from_param(n, threshold)
112 integer :: i, n, threshold
113 integer, parameter :: safelen = 2;
114 !$OMP SIMD SAFELEN(safelen*2 + 2)
115 ! CHECK: %[[LB:.*]] = arith.constant 1 : i32
116 ! CHECK: %[[UB:.*]] = fir.load %arg0
117 ! CHECK: %[[STEP:.*]] = arith.constant 1 : i32
118 ! CHECK: omp.simdloop safelen(6) for (%[[I:.*]]) : i32 = (%[[LB]]) to (%[[UB]]) inclusive step (%[[STEP]]) {
119 do i = 1, n
120 ! CHECK: fir.store %[[I]] to %[[LOCAL:.*]] : !fir.ref<i32>
121 ! CHECK: %[[LD:.*]] = fir.load %[[LOCAL]] : !fir.ref<i32>
122 ! CHECK: fir.call @_FortranAioOutputInteger32({{.*}}, %[[LD]]) {{.*}}: (!fir.ref<i8>, i32) -> i1
123 print*, i
124 end do
125 !$OMP END SIMD
126 end subroutine
128 !CHECK-LABEL: func @_QPsimdloop_with_simdlen_safelen_clause
129 subroutine simdloop_with_simdlen_safelen_clause(n, threshold)
130 integer :: i, n, threshold
131 !$OMP SIMD SIMDLEN(1) SAFELEN(2)
132 ! CHECK: %[[LB:.*]] = arith.constant 1 : i32
133 ! CHECK: %[[UB:.*]] = fir.load %arg0
134 ! CHECK: %[[STEP:.*]] = arith.constant 1 : i32
135 ! CHECK: omp.simdloop simdlen(1) safelen(2) for (%[[I:.*]]) : i32 = (%[[LB]]) to (%[[UB]]) inclusive step (%[[STEP]]) {
136 do i = 1, n
137 ! CHECK: fir.store %[[I]] to %[[LOCAL:.*]] : !fir.ref<i32>
138 ! CHECK: %[[LD:.*]] = fir.load %[[LOCAL]] : !fir.ref<i32>
139 ! CHECK: fir.call @_FortranAioOutputInteger32({{.*}}, %[[LD]]) {{.*}}: (!fir.ref<i8>, i32) -> i1
140 print*, i
141 end do
142 !$OMP END SIMD
143 end subroutine
145 !CHECK-LABEL: func @_QPsimdloop_with_collapse_clause
146 subroutine simdloop_with_collapse_clause(n)
147 integer :: i, j, n
148 integer :: A(n,n)
149 ! CHECK: %[[LOWER_I:.*]] = arith.constant 1 : i32
150 ! CHECK: %[[UPPER_I:.*]] = fir.load %[[PARAM_ARG:.*]] : !fir.ref<i32>
151 ! CHECK: %[[STEP_I:.*]] = arith.constant 1 : i32
152 ! CHECK: %[[LOWER_J:.*]] = arith.constant 1 : i32
153 ! CHECK: %[[UPPER_J:.*]] = fir.load %[[PARAM_ARG:.*]] : !fir.ref<i32>
154 ! CHECK: %[[STEP_J:.*]] = arith.constant 1 : i32
155 ! CHECK: omp.simdloop for (%[[ARG_0:.*]], %[[ARG_1:.*]]) : i32 = (
156 ! CHECK-SAME: %[[LOWER_I]], %[[LOWER_J]]) to (
157 ! CHECK-SAME: %[[UPPER_I]], %[[UPPER_J]]) inclusive step (
158 ! CHECK-SAME: %[[STEP_I]], %[[STEP_J]]) {
159 !$OMP SIMD COLLAPSE(2)
160 do i = 1, n
161 do j = 1, n
162 A(i,j) = i + j
163 end do
164 end do
165 !$OMP END SIMD
166 end subroutine