[flang] Accept polymorphic component element in storage_size
[llvm-project.git] / flang / test / Lower / HLFIR / binary-ops.f90
blob8e5dced1396d009cb77e2b6ad62b2faeafbfa543
1 ! Test lowering of binary intrinsic operations to HLFIR
2 ! RUN: bbc -emit-fir -hlfir -o - %s 2>&1 | FileCheck %s
4 subroutine int_add(x, y, z)
5 integer :: x, y, z
6 x = y + z
7 end subroutine
8 ! CHECK-LABEL: func.func @_QPint_add(
9 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}}y"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
10 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare %{{.*}}z"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
11 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<i32>
12 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<i32>
13 ! CHECK: %[[VAL_8:.*]] = arith.addi %[[VAL_6]], %[[VAL_7]] : i32
15 subroutine real_add(x, y, z)
16 real :: x, y, z
17 x = y + z
18 end subroutine
19 ! CHECK-LABEL: func.func @_QPreal_add(
20 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}}y"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
21 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare %{{.*}}z"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
22 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<f32>
23 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<f32>
24 ! CHECK: %[[VAL_8:.*]] = arith.addf %[[VAL_6]], %[[VAL_7]] fastmath<contract> : f32
26 subroutine complex_add(x, y, z)
27 complex :: x, y, z
28 x = y + z
29 end subroutine
30 ! CHECK-LABEL: func.func @_QPcomplex_add(
31 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}}y"} : (!fir.ref<!fir.complex<4>>) -> (!fir.ref<!fir.complex<4>>, !fir.ref<!fir.complex<4>>)
32 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare %{{.*}}z"} : (!fir.ref<!fir.complex<4>>) -> (!fir.ref<!fir.complex<4>>, !fir.ref<!fir.complex<4>>)
33 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<!fir.complex<4>>
34 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<!fir.complex<4>>
35 ! CHECK: %[[VAL_8:.*]] = fir.addc %[[VAL_6]], %[[VAL_7]] : !fir.complex<4>
37 subroutine int_sub(x, y, z)
38 integer :: x, y, z
39 x = y - z
40 end subroutine
41 ! CHECK-LABEL: func.func @_QPint_sub(
42 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}}y"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
43 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare %{{.*}}z"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
44 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<i32>
45 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<i32>
46 ! CHECK: %[[VAL_8:.*]] = arith.subi %[[VAL_6]], %[[VAL_7]] : i32
48 subroutine real_sub(x, y, z)
49 real :: x, y, z
50 x = y - z
51 end subroutine
52 ! CHECK-LABEL: func.func @_QPreal_sub(
53 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}}y"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
54 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare %{{.*}}z"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
55 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<f32>
56 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<f32>
57 ! CHECK: %[[VAL_8:.*]] = arith.subf %[[VAL_6]], %[[VAL_7]] fastmath<contract> : f32
59 subroutine complex_sub(x, y, z)
60 complex :: x, y, z
61 x = y - z
62 end subroutine
63 ! CHECK-LABEL: func.func @_QPcomplex_sub(
64 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}}y"} : (!fir.ref<!fir.complex<4>>) -> (!fir.ref<!fir.complex<4>>, !fir.ref<!fir.complex<4>>)
65 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare %{{.*}}z"} : (!fir.ref<!fir.complex<4>>) -> (!fir.ref<!fir.complex<4>>, !fir.ref<!fir.complex<4>>)
66 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<!fir.complex<4>>
67 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<!fir.complex<4>>
68 ! CHECK: %[[VAL_8:.*]] = fir.subc %[[VAL_6]], %[[VAL_7]] : !fir.complex<4>
70 subroutine int_mul(x, y, z)
71 integer :: x, y, z
72 x = y * z
73 end subroutine
74 ! CHECK-LABEL: func.func @_QPint_mul(
75 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}}y"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
76 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare %{{.*}}z"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
77 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<i32>
78 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<i32>
79 ! CHECK: %[[VAL_8:.*]] = arith.muli %[[VAL_6]], %[[VAL_7]] : i32
81 subroutine real_mul(x, y, z)
82 real :: x, y, z
83 x = y * z
84 end subroutine
85 ! CHECK-LABEL: func.func @_QPreal_mul(
86 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}}y"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
87 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare %{{.*}}z"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
88 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<f32>
89 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<f32>
90 ! CHECK: %[[VAL_8:.*]] = arith.mulf %[[VAL_6]], %[[VAL_7]] fastmath<contract> : f32
92 subroutine complex_mul(x, y, z)
93 complex :: x, y, z
94 x = y * z
95 end subroutine
96 ! CHECK-LABEL: func.func @_QPcomplex_mul(
97 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}}y"} : (!fir.ref<!fir.complex<4>>) -> (!fir.ref<!fir.complex<4>>, !fir.ref<!fir.complex<4>>)
98 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare %{{.*}}z"} : (!fir.ref<!fir.complex<4>>) -> (!fir.ref<!fir.complex<4>>, !fir.ref<!fir.complex<4>>)
99 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<!fir.complex<4>>
100 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<!fir.complex<4>>
101 ! CHECK: %[[VAL_8:.*]] = fir.mulc %[[VAL_6]], %[[VAL_7]] : !fir.complex<4>
103 subroutine int_div(x, y, z)
104 integer :: x, y, z
105 x = y / z
106 end subroutine
107 ! CHECK-LABEL: func.func @_QPint_div(
108 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}}y"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
109 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare %{{.*}}z"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
110 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<i32>
111 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<i32>
112 ! CHECK: %[[VAL_8:.*]] = arith.divsi %[[VAL_6]], %[[VAL_7]] : i32
114 subroutine real_div(x, y, z)
115 real :: x, y, z
116 x = y / z
117 end subroutine
118 ! CHECK-LABEL: func.func @_QPreal_div(
119 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}}y"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
120 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare %{{.*}}z"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
121 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<f32>
122 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<f32>
123 ! CHECK: %[[VAL_8:.*]] = arith.divf %[[VAL_6]], %[[VAL_7]] fastmath<contract> : f32
125 subroutine complex_div(x, y, z)
126 complex :: x, y, z
127 x = y / z
128 end subroutine
129 ! CHECK-LABEL: func.func @_QPcomplex_div(
130 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}}y"} : (!fir.ref<!fir.complex<4>>) -> (!fir.ref<!fir.complex<4>>, !fir.ref<!fir.complex<4>>)
131 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare %{{.*}}z"} : (!fir.ref<!fir.complex<4>>) -> (!fir.ref<!fir.complex<4>>, !fir.ref<!fir.complex<4>>)
132 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<!fir.complex<4>>
133 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<!fir.complex<4>>
134 ! CHECK: %[[VAL_8:.*]] = fir.divc %[[VAL_6]], %[[VAL_7]] : !fir.complex<4>
137 subroutine int_power(x, y, z)
138 integer :: x, y, z
139 x = y**z
140 end subroutine
141 ! CHECK-LABEL: func.func @_QPint_power(
142 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}}y"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
143 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare %{{.*}}z"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
144 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<i32>
145 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<i32>
146 ! CHECK: %[[VAL_8:.*]] = math.ipowi %[[VAL_6]], %[[VAL_7]] : i32
148 subroutine real_power(x, y, z)
149 real :: x, y, z
150 x = y**z
151 end subroutine
152 ! CHECK-LABEL: func.func @_QPreal_power(
153 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}}y"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
154 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare %{{.*}}z"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
155 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<f32>
156 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<f32>
157 ! CHECK: %[[VAL_8:.*]] = math.powf %[[VAL_6]], %[[VAL_7]] fastmath<contract> : f32
159 subroutine complex_power(x, y, z)
160 complex :: x, y, z
161 x = y**z
162 end subroutine
163 ! CHECK-LABEL: func.func @_QPcomplex_power(
164 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}}y"} : (!fir.ref<!fir.complex<4>>) -> (!fir.ref<!fir.complex<4>>, !fir.ref<!fir.complex<4>>)
165 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare %{{.*}}z"} : (!fir.ref<!fir.complex<4>>) -> (!fir.ref<!fir.complex<4>>, !fir.ref<!fir.complex<4>>)
166 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<!fir.complex<4>>
167 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<!fir.complex<4>>
168 ! CHECK: %[[VAL_8:.*]] = fir.convert %[[VAL_6]] : (!fir.complex<4>) -> complex<f32>
169 ! CHECK: %[[VAL_9:.*]] = fir.convert %[[VAL_7]] : (!fir.complex<4>) -> complex<f32>
170 ! CHECK: %[[VAL_10:.*]] = complex.pow %[[VAL_8]], %[[VAL_9]] : complex<f32>
171 ! CHECK: %[[VAL_11:.*]] = fir.convert %[[VAL_10]] : (complex<f32>) -> !fir.complex<4>
173 subroutine real_to_int_power(x, y, z)
174 real :: x, y
175 integer :: z
176 x = y**z
177 end subroutine
178 ! CHECK-LABEL: func.func @_QPreal_to_int_power(
179 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}}y"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
180 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare %{{.*}}z"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
181 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<f32>
182 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<i32>
183 ! CHECK: %[[VAL_8:.*]] = math.fpowi %[[VAL_6]], %[[VAL_7]] fastmath<contract> : f32, i32
185 subroutine complex_to_int_power(x, y, z)
186 complex :: x, y
187 integer :: z
188 x = y**z
189 end subroutine
190 ! CHECK-LABEL: func.func @_QPcomplex_to_int_power(
191 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}}y"} : (!fir.ref<!fir.complex<4>>) -> (!fir.ref<!fir.complex<4>>, !fir.ref<!fir.complex<4>>)
192 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare %{{.*}}z"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
193 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<!fir.complex<4>>
194 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<i32>
195 ! CHECK: %[[VAL_8:.*]] = fir.call @_FortranAcpowi(%[[VAL_6]], %[[VAL_7]]) fastmath<contract> : (!fir.complex<4>, i32) -> !fir.complex<4>
197 subroutine extremum(c, n, l)
198 integer(8), intent(in) :: l
199 integer(8) :: n
200 character(l) :: c
201 ! evaluate::Extremum is created by semantics while analyzing LEN().
202 n = len(c, 8)
203 end subroutine
204 ! CHECK-LABEL: func.func @_QPextremum(
205 ! CHECK: hlfir.declare {{.*}}c
206 ! CHECK: %[[VAL_11:.*]] = arith.constant 0 : i64
207 ! CHECK: %[[VAL_12:.*]] = fir.load %{{.*}} : !fir.ref<i64>
208 ! CHECK: %[[VAL_13:.*]] = arith.cmpi sgt, %[[VAL_11]], %[[VAL_12]] : i64
209 ! CHECK: arith.select %[[VAL_13]], %[[VAL_11]], %[[VAL_12]] : i64
211 subroutine cmp_int(l, x, y)
212 logical :: l
213 integer :: x, y
214 l = x .eq. y
215 end subroutine
216 ! CHECK-LABEL: func.func @_QPcmp_int(
217 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare {{.*}}x"
218 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare {{.*}}y"
219 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<i32>
220 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<i32>
221 ! CHECK: %[[VAL_8:.*]] = arith.cmpi eq, %[[VAL_6]], %[[VAL_7]] : i32
223 subroutine cmp_int_2(l, x, y)
224 logical :: l
225 integer :: x, y
226 l = x .ne. y
227 ! CHECK: arith.cmpi ne
228 l = x .gt. y
229 ! CHECK: arith.cmpi sgt
230 l = x .ge. y
231 ! CHECK: arith.cmpi sge
232 l = x .lt. y
233 ! CHECK: arith.cmpi slt
234 l = x .le. y
235 ! CHECK: arith.cmpi sle
236 end subroutine
238 subroutine cmp_real(l, x, y)
239 logical :: l
240 real :: x, y
241 l = x .eq. y
242 end subroutine
243 ! CHECK-LABEL: func.func @_QPcmp_real(
244 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare {{.*}}x"
245 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare {{.*}}y"
246 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<f32>
247 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<f32>
248 ! CHECK: %[[VAL_8:.*]] = arith.cmpf oeq, %[[VAL_6]], %[[VAL_7]] : f32
250 subroutine cmp_real_2(l, x, y)
251 logical :: l
252 real :: x, y
253 l = x .ne. y
254 ! CHECK: arith.cmpf une
255 l = x .gt. y
256 ! CHECK: arith.cmpf ogt
257 l = x .ge. y
258 ! CHECK: arith.cmpf oge
259 l = x .lt. y
260 ! CHECK: arith.cmpf olt
261 l = x .le. y
262 ! CHECK: arith.cmpf ole
263 end subroutine
265 subroutine cmp_cmplx(l, x, y)
266 logical :: l
267 complex :: x, y
268 l = x .eq. y
269 end subroutine
270 ! CHECK-LABEL: func.func @_QPcmp_cmplx(
271 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare {{.*}}x"
272 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare {{.*}}y"
273 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<!fir.complex<4>>
274 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<!fir.complex<4>>
275 ! CHECK: %[[VAL_8:.*]] = fir.cmpc "oeq", %[[VAL_6]], %[[VAL_7]] : !fir.complex<4>
277 subroutine cmp_char(l, x, y)
278 logical :: l
279 character(*) :: x, y
280 l = x .eq. y
281 end subroutine
282 ! CHECK-LABEL: func.func @_QPcmp_char(
283 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare %{{.*}} typeparams %[[VAL_4:.*]]#1 {uniq_name = "_QFcmp_charEx"} : (!fir.ref<!fir.char<1,?>>, index) -> (!fir.boxchar<1>, !fir.ref<!fir.char<1,?>>)
284 ! CHECK: %[[VAL_7:.*]]:2 = hlfir.declare %{{.*}} typeparams %[[VAL_6:.*]]#1 {uniq_name = "_QFcmp_charEy"} : (!fir.ref<!fir.char<1,?>>, index) -> (!fir.boxchar<1>, !fir.ref<!fir.char<1,?>>)
285 ! CHECK: %[[VAL_8:.*]] = fir.convert %[[VAL_5]]#1 : (!fir.ref<!fir.char<1,?>>) -> !fir.ref<i8>
286 ! CHECK: %[[VAL_9:.*]] = fir.convert %[[VAL_7]]#1 : (!fir.ref<!fir.char<1,?>>) -> !fir.ref<i8>
287 ! CHECK: %[[VAL_10:.*]] = fir.convert %[[VAL_4]]#1 : (index) -> i64
288 ! CHECK: %[[VAL_11:.*]] = fir.convert %[[VAL_6]]#1 : (index) -> i64
289 ! CHECK: %[[VAL_12:.*]] = fir.call @_FortranACharacterCompareScalar1(%[[VAL_8]], %[[VAL_9]], %[[VAL_10]], %[[VAL_11]]) fastmath<contract> : (!fir.ref<i8>, !fir.ref<i8>, i64, i64) -> i32
290 ! CHECK: %[[VAL_13:.*]] = arith.constant 0 : i32
291 ! CHECK: %[[VAL_14:.*]] = arith.cmpi eq, %[[VAL_12]], %[[VAL_13]] : i32
293 subroutine logical_and(x, y, z)
294 logical :: x, y, z
295 x = y.and.z
296 end subroutine
297 ! CHECK-LABEL: func.func @_QPlogical_and(
298 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}}y"} : (!fir.ref<!fir.logical<4>>) -> (!fir.ref<!fir.logical<4>>, !fir.ref<!fir.logical<4>>)
299 ! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare %{{.*}}z"} : (!fir.ref<!fir.logical<4>>) -> (!fir.ref<!fir.logical<4>>, !fir.ref<!fir.logical<4>>)
300 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<!fir.logical<4>>
301 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<!fir.logical<4>>
302 ! CHECK: %[[VAL_8:.*]] = fir.convert %[[VAL_6]] : (!fir.logical<4>) -> i1
303 ! CHECK: %[[VAL_9:.*]] = fir.convert %[[VAL_7]] : (!fir.logical<4>) -> i1
304 ! CHECK: %[[VAL_10:.*]] = arith.andi %[[VAL_8]], %[[VAL_9]] : i1
306 subroutine logical_or(x, y, z)
307 logical :: x, y, z
308 x = y.or.z
309 end subroutine
310 ! CHECK-LABEL: func.func @_QPlogical_or(
311 ! CHECK: %[[VAL_10:.*]] = arith.ori
313 subroutine logical_eqv(x, y, z)
314 logical :: x, y, z
315 x = y.eqv.z
316 end subroutine
317 ! CHECK-LABEL: func.func @_QPlogical_eqv(
318 ! CHECK: %[[VAL_10:.*]] = arith.cmpi eq
320 subroutine logical_neqv(x, y, z)
321 logical :: x, y, z
322 x = y.neqv.z
323 end subroutine
324 ! CHECK-LABEL: func.func @_QPlogical_neqv(
325 ! CHECK: %[[VAL_10:.*]] = arith.cmpi ne
327 subroutine cmplx_ctor(z, x, y)
328 complex :: z
329 real :: x, y
330 z = cmplx(x, y)
331 end subroutine
332 ! CHECK-LABEL: func.func @_QPcmplx_ctor(
333 ! CHECK: %[[VAL_3:.*]]:2 = hlfir.declare %{{.*}}x"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
334 ! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %{{.*}}y"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
335 ! CHECK: %[[VAL_6:.*]] = fir.load %[[VAL_3]]#0 : !fir.ref<f32>
336 ! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_4]]#0 : !fir.ref<f32>
337 ! CHECK: %[[VAL_8:.*]] = fir.undefined !fir.complex<4>
338 ! CHECK: %[[VAL_9:.*]] = fir.insert_value %[[VAL_8]], %[[VAL_6]], [0 : index] : (!fir.complex<4>, f32) -> !fir.complex<4>
339 ! CHECK: %[[VAL_10:.*]] = fir.insert_value %[[VAL_9]], %[[VAL_7]], [1 : index] : (!fir.complex<4>, f32) -> !fir.complex<4>
341 subroutine cmplx_ctor_2(z, x)
342 complex(8) :: z
343 real(8) :: x
344 z = cmplx(x, 1._8, kind=8)
345 end subroutine
346 ! CHECK-LABEL: func.func @_QPcmplx_ctor_2(
347 ! CHECK: %[[VAL_2:.*]]:2 = hlfir.declare %{{.*}}x"} : (!fir.ref<f64>) -> (!fir.ref<f64>, !fir.ref<f64>)
348 ! CHECK: %[[VAL_4:.*]] = fir.load %[[VAL_2]]#0 : !fir.ref<f64>
349 ! CHECK: %[[VAL_5:.*]] = arith.constant 1.000000e+00 : f64
350 ! CHECK: %[[VAL_6:.*]] = fir.undefined !fir.complex<8>
351 ! CHECK: %[[VAL_7:.*]] = fir.insert_value %[[VAL_6]], %[[VAL_4]], [0 : index] : (!fir.complex<8>, f64) -> !fir.complex<8>
352 ! CHECK: %[[VAL_8:.*]] = fir.insert_value %[[VAL_7]], %[[VAL_5]], [1 : index] : (!fir.complex<8>, f64) -> !fir.complex<8>