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