Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Lower / OpenMP / sections.f90
blob3bec578c6bd57046a136afbf3478b06a7276c80e
1 ! This test checks the lowering of OpenMP sections construct with several clauses present
3 ! RUN: %flang_fc1 -emit-fir -fopenmp %s -o - | FileCheck %s
5 !CHECK: func @_QQmain() attributes {fir.bindc_name = "sample"} {
6 !CHECK: %[[COUNT:.*]] = fir.address_of(@_QFEcount) : !fir.ref<i32>
7 !CHECK: %[[ETA:.*]] = fir.alloca f32 {bindc_name = "eta", uniq_name = "_QFEeta"}
8 !CHECK: %[[CONST_1:.*]] = arith.constant 1 : i32
9 !CHECK: omp.sections allocate(%[[CONST_1]] : i32 -> %0 : !fir.ref<i32>) {
10 !CHECK: omp.section {
11 !CHECK: %[[PRIVATE_ETA:.*]] = fir.alloca f32 {bindc_name = "eta", pinned, uniq_name = "_QFEeta"}
12 !CHECK: %[[PRIVATE_DOUBLE_COUNT:.*]] = fir.alloca i32 {bindc_name = "double_count", pinned, uniq_name = "_QFEdouble_count"}
13 !CHECK: %[[const:.*]] = arith.constant 5 : i32
14 !CHECK: fir.store %[[const]] to %[[COUNT]] : !fir.ref<i32>
15 !CHECK: %[[temp_count:.*]] = fir.load %[[COUNT]] : !fir.ref<i32>
16 !CHECK: %[[temp_double_count:.*]] = fir.load %[[PRIVATE_DOUBLE_COUNT]] : !fir.ref<i32>
17 !CHECK: %[[result:.*]] = arith.muli %[[temp_count]], %[[temp_double_count]] : i32
18 !CHECK: {{.*}} = fir.convert %[[result]] : (i32) -> f32
19 !CHECK: fir.store {{.*}} to %[[PRIVATE_ETA]] : !fir.ref<f32>
20 !CHECK: omp.terminator
21 !CHECK: }
22 !CHECK: omp.section {
23 !CHECK: %[[PRIVATE_ETA:.*]] = fir.alloca f32 {bindc_name = "eta", pinned, uniq_name = "_QFEeta"}
24 !CHECK: %[[PRIVATE_DOUBLE_COUNT:.*]] = fir.alloca i32 {bindc_name = "double_count", pinned, uniq_name = "_QFEdouble_count"}
25 !CHECK: %[[temp:.*]] = fir.load %[[PRIVATE_DOUBLE_COUNT]] : !fir.ref<i32>
26 !CHECK: %[[const:.*]] = arith.constant 1 : i32
27 !CHECK: %[[result:.*]] = arith.addi %[[temp]], %[[const]] : i32
28 !CHECK: fir.store %[[result]] to %[[PRIVATE_DOUBLE_COUNT]] : !fir.ref<i32>
29 !CHECK: omp.terminator
30 !CHECK: }
31 !CHECK: omp.section {
32 !CHECK: %[[PRIVATE_ETA:.*]] = fir.alloca f32 {bindc_name = "eta", pinned, uniq_name = "_QFEeta"}
33 !CHECK: %[[PRIVATE_DOUBLE_COUNT:.*]] = fir.alloca i32 {bindc_name = "double_count", pinned, uniq_name = "_QFEdouble_count"}
34 !CHECK: %[[temp:.*]] = fir.load %[[PRIVATE_ETA]] : !fir.ref<f32>
35 !CHECK: %[[const:.*]] = arith.constant 7.000000e+00 : f32
36 !CHECK: %[[result:.*]] = arith.subf %[[temp]], %[[const]] {{.*}}: f32
37 !CHECK: fir.store %[[result]] to %[[PRIVATE_ETA]] : !fir.ref<f32>
38 !CHECK: {{.*}} = fir.load %[[COUNT]] : !fir.ref<i32>
39 !CHECK: %[[temp_count:.*]] = fir.convert {{.*}} : (i32) -> f32
40 !CHECK: %[[temp_eta:.*]] = fir.load %[[PRIVATE_ETA]] : !fir.ref<f32>
41 !CHECK: {{.*}} = arith.mulf %[[temp_count]], %[[temp_eta]] {{.*}}: f32
42 !CHECK: %[[result:.*]] = fir.convert {{.*}} : (f32) -> i32
43 !CHECK: fir.store %[[result]] to %[[COUNT]] : !fir.ref<i32>
44 !CHECK: {{.*}} = fir.load %[[COUNT]] : !fir.ref<i32>
45 !CHECK: %[[temp_count:.*]] = fir.convert {{.*}} : (i32) -> f32
46 !CHECK: %[[temp_eta:.*]] = fir.load %[[PRIVATE_ETA]] : !fir.ref<f32>
47 !CHECK: {{.*}} = arith.subf %[[temp_count]], %[[temp_eta]] {{.*}}: f32
48 !CHECK: %[[result:.*]] = fir.convert {{.*}} : (f32) -> i32
49 !CHECK: fir.store %[[result]] to %[[PRIVATE_DOUBLE_COUNT]] : !fir.ref<i32>
50 !CHECK: omp.terminator
51 !CHECK: }
52 !CHECK: omp.terminator
53 !CHECK: }
54 !CHECK: omp.sections nowait {
55 !CHECK: omp.terminator
56 !CHECK: }
57 !CHECK: return
58 !CHECK: }
60 program sample
61 use omp_lib
62 integer :: count = 0, double_count = 1
63 !$omp sections private (eta, double_count) allocate(omp_high_bw_mem_alloc: count)
64 !$omp section
65 count = 1 + 4
66 eta = count * double_count
67 !$omp section
68 double_count = double_count + 1
69 !$omp section
70 eta = eta - 7
71 count = count * eta
72 double_count = count - eta
73 !$omp end sections
75 !$omp sections
76 !$omp end sections nowait
77 end program sample
79 !CHECK: func @_QPfirstprivate(%[[ARG:.*]]: !fir.ref<f32> {fir.bindc_name = "alpha"}) {
80 !CHECK: omp.sections {
81 !CHECK: omp.section {
82 !CHECK: %[[PRIVATE_ALPHA:.*]] = fir.alloca f32 {bindc_name = "alpha", pinned, uniq_name = "_QFfirstprivateEalpha"}
83 !CHECK: %[[temp:.*]] = fir.load %[[ARG]] : !fir.ref<f32>
84 !CHECK: fir.store %[[temp]] to %[[PRIVATE_ALPHA]] : !fir.ref<f32>
85 !CHECK: omp.terminator
86 !CHECK: }
87 !CHECK: omp.terminator
88 !CHECK: }
89 !CHECK: omp.sections {
90 !CHECK: omp.section {
91 !CHECK: %[[PRIVATE_VAR:.*]] = fir.load %[[ARG]] : !fir.ref<f32>
92 !CHECK: %[[CONSTANT:.*]] = arith.constant 5.000000e+00 : f32
93 !CHECK: %[[PRIVATE_VAR_2:.*]] = arith.mulf %[[PRIVATE_VAR]], %[[CONSTANT]] {{.*}}: f32
94 !CHECK: fir.store %[[PRIVATE_VAR_2]] to %[[ARG]] : !fir.ref<f32>
95 !CHECK: omp.terminator
96 !CHECK: }
97 !CHECK: omp.terminator
98 !CHECK: }
99 !CHECK: return
100 !CHECK: }
102 subroutine firstprivate(alpha)
103 real :: alpha
104 !$omp sections firstprivate(alpha)
105 !$omp end sections
107 !$omp sections
108 alpha = alpha * 5
109 !$omp end sections
110 end subroutine
112 subroutine lastprivate()
113 integer :: x
114 !CHECK: %[[X:.*]] = fir.alloca i32 {bindc_name = "x", uniq_name = "_QFlastprivateEx"}
115 !CHECK: omp.sections {
116 !$omp sections lastprivate(x)
117 !CHECK: omp.section {
118 !CHECK: %[[PRIVATE_X:.*]] = fir.alloca i32 {bindc_name = "x", pinned, uniq_name = "_QFlastprivateEx"}
119 !CHECK: %[[const:.*]] = arith.constant 10 : i32
120 !CHECK: %[[temp:.*]] = fir.load %[[PRIVATE_X]] : !fir.ref<i32>
121 !CHECK: %[[result:.*]] = arith.muli %c10_i32, %[[temp]] : i32
122 !CHECK: fir.store %[[result]] to %[[PRIVATE_X]] : !fir.ref<i32>
123 !CHECK: omp.terminator
124 !CHECK: }
125 !$omp section
126 x = x * 10
127 !CHECK: omp.section {
128 !CHECK: %[[PRIVATE_X:.*]] = fir.alloca i32 {bindc_name = "x", pinned, uniq_name = "_QFlastprivateEx"}
129 !CHECK: %[[true:.*]] = arith.constant true
130 !CHECK: %[[temp:.*]] = fir.load %[[PRIVATE_X]] : !fir.ref<i32>
131 !CHECK: %[[const:.*]] = arith.constant 1 : i32
132 !CHECK: %[[result:.*]] = arith.addi %[[temp]], %[[const]] : i32
133 !CHECK: fir.store %[[result]] to %[[PRIVATE_X]] : !fir.ref<i32>
134 !CHECK: scf.if %[[true]] {
135 !CHECK: %[[temp:.*]] = fir.load %[[PRIVATE_X]] : !fir.ref<i32>
136 !CHECK: fir.store %[[temp]] to %[[X]] : !fir.ref<i32>
137 !CHECK: }
138 !CHECK: omp.terminator
139 !CHECK: }
140 !$omp section
141 x = x + 1
142 !CHECK: omp.terminator
143 !CHECK: }
144 !$omp end sections
146 !CHECK: omp.sections {
147 !$omp sections firstprivate(x) lastprivate(x)
148 !CHECK: omp.section {
149 !CHECK: %[[PRIVATE_X:.*]] = fir.alloca i32 {bindc_name = "x", pinned, uniq_name = "_QFlastprivateEx"}
150 !CHECK: %[[temp:.*]] = fir.load %[[X]] : !fir.ref<i32>
151 !CHECK: fir.store %[[temp]] to %[[PRIVATE_X]] : !fir.ref<i32>
152 !CHECK: omp.barrier
153 !CHECK: %[[const:.*]] = arith.constant 10 : i32
154 !CHECK: %[[temp:.*]] = fir.load %[[PRIVATE_X]] : !fir.ref<i32>
155 !CHECK: %[[result:.*]] = arith.muli %c10_i32, %[[temp]] : i32
156 !CHECK: fir.store %[[result]] to %[[PRIVATE_X]] : !fir.ref<i32>
157 !CHECK: omp.terminator
158 !CHECK: }
159 !$omp section
160 x = x * 10
161 !CHECK: omp.section {
162 !CHECK: %[[PRIVATE_X:.*]] = fir.alloca i32 {bindc_name = "x", pinned, uniq_name = "_QFlastprivateEx"}
163 !CHECK: %[[temp:.*]] = fir.load %[[X]] : !fir.ref<i32>
164 !CHECK: fir.store %[[temp]] to %[[PRIVATE_X]] : !fir.ref<i32>
165 !CHECK: omp.barrier
166 !CHECK: %[[true:.*]] = arith.constant true
167 !CHECK: %[[temp:.*]] = fir.load %[[PRIVATE_X]] : !fir.ref<i32>
168 !CHECK: %[[const:.*]] = arith.constant 1 : i32
169 !CHECK: %[[result:.*]] = arith.addi %[[temp]], %[[const]] : i32
170 !CHECK: fir.store %[[result]] to %[[PRIVATE_X]] : !fir.ref<i32>
171 !CHECK: scf.if %true {
172 !CHECK: %[[temp:.*]] = fir.load %[[PRIVATE_X]] : !fir.ref<i32>
173 !CHECK: fir.store %[[temp]] to %[[X]] : !fir.ref<i32>
174 !CHECK: }
175 !CHECK: omp.terminator
176 !CHECK: }
177 !$omp section
178 x = x + 1
179 !CHECK: omp.terminator
180 !CHECK: }
181 !$omp end sections
183 !CHECK: omp.sections nowait {
184 !$omp sections firstprivate(x) lastprivate(x)
185 !CHECK: omp.section {
186 !CHECK: %[[PRIVATE_X:.*]] = fir.alloca i32 {bindc_name = "x", pinned, uniq_name = "_QFlastprivateEx"}
187 !CHECK: %[[temp:.*]] = fir.load %[[X]] : !fir.ref<i32>
188 !CHECK: fir.store %[[temp]] to %[[PRIVATE_X]] : !fir.ref<i32>
189 !CHECK: omp.barrier
190 !CHECK: %[[const:.*]] = arith.constant 10 : i32
191 !CHECK: %[[temp:.*]] = fir.load %[[PRIVATE_X]] : !fir.ref<i32>
192 !CHECK: %[[result:.*]] = arith.muli %c10_i32, %[[temp]] : i32
193 !CHECK: fir.store %[[result]] to %[[PRIVATE_X]] : !fir.ref<i32>
194 !CHECK: omp.terminator
195 !CHECK: }
196 !$omp section
197 x = x * 10
198 !CHECK: omp.section {
199 !CHECK: %[[PRIVATE_X:.*]] = fir.alloca i32 {bindc_name = "x", pinned, uniq_name = "_QFlastprivateEx"}
200 !CHECK: %[[temp:.*]] = fir.load %[[X]] : !fir.ref<i32>
201 !CHECK: fir.store %[[temp]] to %[[PRIVATE_X]] : !fir.ref<i32>
202 !CHECK: omp.barrier
203 !CHECK: %[[true:.*]] = arith.constant true
204 !CHECK: %[[temp:.*]] = fir.load %[[PRIVATE_X]] : !fir.ref<i32>
205 !CHECK: %[[const:.*]] = arith.constant 1 : i32
206 !CHECK: %[[result:.*]] = arith.addi %[[temp]], %[[const]] : i32
207 !CHECK: fir.store %[[result]] to %[[PRIVATE_X]] : !fir.ref<i32>
208 !CHECK: scf.if %true {
209 !CHECK: %[[temp:.*]] = fir.load %[[PRIVATE_X]] : !fir.ref<i32>
210 !CHECK: fir.store %[[temp]] to %[[X]] : !fir.ref<i32>
211 !CHECK: omp.barrier
212 !CHECK: }
213 !CHECK: omp.terminator
214 !CHECK: }
215 !$omp section
216 x = x + 1
217 !CHECK: omp.terminator
218 !CHECK: }
219 !$omp end sections nowait
220 end subroutine