1 ! RUN: bbc -emit-fir %s -o - | FileCheck %s
2 ! RUN: %flang_fc1 -emit-fir %s -o - | FileCheck %s
5 ! CHECK-LABEL: dot_prod_int_default
6 ! CHECK-SAME: %[[x:arg0]]: !fir.box<!fir.array<?xi32>>
7 ! CHECK-SAME: %[[y:arg1]]: !fir.box<!fir.array<?xi32>>
8 ! CHECK-SAME: %[[z:arg2]]: !fir.box<!fir.array<?xi32>>
9 subroutine dot_prod_int_default (x
, y
, z
)
10 integer, dimension(1:) :: x
,y
11 integer, dimension(1:) :: z
12 ! CHECK-DAG: %[[x_conv:.*]] = fir.convert %[[x]] : (!fir.box<!fir.array<?xi32>>) -> !fir.box<none>
13 ! CHECK-DAG: %[[y_conv:.*]] = fir.convert %[[y]] : (!fir.box<!fir.array<?xi32>>) -> !fir.box<none>
14 ! CHECK-DAG: %[[res:.*]] = fir.call @_FortranADotProductInteger4(%[[x_conv]], %[[y_conv]], %{{[0-9]+}}, %{{.*}}) {{.*}}: (!fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> i32
18 ! CHECK-LABEL: dot_prod_int_kind_1
19 ! CHECK-SAME: %[[x:arg0]]: !fir.box<!fir.array<?xi8>>
20 ! CHECK-SAME: %[[y:arg1]]: !fir.box<!fir.array<?xi8>>
21 ! CHECK-SAME: %[[z:arg2]]: !fir.box<!fir.array<?xi8>>
22 subroutine dot_prod_int_kind_1 (x
, y
, z
)
23 integer(kind
=1), dimension(1:) :: x
,y
24 integer(kind
=1), dimension(1:) :: z
25 ! CHECK-DAG: %[[x_conv:.*]] = fir.convert %[[x]] : (!fir.box<!fir.array<?xi8>>) -> !fir.box<none>
26 ! CHECK-DAG: %[[y_conv:.*]] = fir.convert %[[y]] : (!fir.box<!fir.array<?xi8>>) -> !fir.box<none>
27 ! CHECK-DAG: %[[res:.*]] = fir.call @_FortranADotProductInteger1(%[[x_conv]], %[[y_conv]], %{{[0-9]+}}, %{{.*}}) {{.*}}: (!fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> i8
31 ! CHECK-LABEL: dot_prod_int_kind_2
32 ! CHECK-SAME: %[[x:arg0]]: !fir.box<!fir.array<?xi16>>
33 ! CHECK-SAME: %[[y:arg1]]: !fir.box<!fir.array<?xi16>>
34 ! CHECK-SAME: %[[z:arg2]]: !fir.box<!fir.array<?xi16>>
35 subroutine dot_prod_int_kind_2 (x
, y
, z
)
36 integer(kind
=2), dimension(1:) :: x
,y
37 integer(kind
=2), dimension(1:) :: z
38 ! CHECK-DAG: %[[x_conv:.*]] = fir.convert %[[x]] : (!fir.box<!fir.array<?xi16>>) -> !fir.box<none>
39 ! CHECK-DAG: %[[y_conv:.*]] = fir.convert %[[y]] : (!fir.box<!fir.array<?xi16>>) -> !fir.box<none>
40 ! CHECK-DAG: %[[res:.*]] = fir.call @_FortranADotProductInteger2(%[[x_conv]], %[[y_conv]], %{{[0-9]+}}, %{{.*}}) {{.*}}: (!fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> i16
44 ! CHECK-LABEL: dot_prod_int_kind_4
45 ! CHECK-SAME: %[[x:arg0]]: !fir.box<!fir.array<?xi32>>
46 ! CHECK-SAME: %[[y:arg1]]: !fir.box<!fir.array<?xi32>>
47 ! CHECK-SAME: %[[z:arg2]]: !fir.box<!fir.array<?xi32>>
48 subroutine dot_prod_int_kind_4 (x
, y
, z
)
49 integer(kind
=4), dimension(1:) :: x
,y
50 integer(kind
=4), dimension(1:) :: z
51 ! CHECK-DAG: %[[x_conv:.*]] = fir.convert %[[x]] : (!fir.box<!fir.array<?xi32>>) -> !fir.box<none>
52 ! CHECK-DAG: %[[y_conv:.*]] = fir.convert %[[y]] : (!fir.box<!fir.array<?xi32>>) -> !fir.box<none>
53 ! CHECK-DAG: %[[res:.*]] = fir.call @_FortranADotProductInteger4(%[[x_conv]], %[[y_conv]], %{{[0-9]+}}, %{{.*}}) {{.*}}: (!fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> i32
57 ! CHECK-LABEL: dot_prod_int_kind_8
58 ! CHECK-SAME: %[[x:arg0]]: !fir.box<!fir.array<?xi64>>
59 ! CHECK-SAME: %[[y:arg1]]: !fir.box<!fir.array<?xi64>>
60 ! CHECK-SAME: %[[z:arg2]]: !fir.box<!fir.array<?xi64>>
61 subroutine dot_prod_int_kind_8 (x
, y
, z
)
62 integer(kind
=8), dimension(1:) :: x
,y
63 integer(kind
=8), dimension(1:) :: z
64 ! CHECK-DAG: %[[x_conv:.*]] = fir.convert %[[x]] : (!fir.box<!fir.array<?xi64>>) -> !fir.box<none>
65 ! CHECK-DAG: %[[y_conv:.*]] = fir.convert %[[y]] : (!fir.box<!fir.array<?xi64>>) -> !fir.box<none>
66 ! CHECK-DAG: %[[res:.*]] = fir.call @_FortranADotProductInteger8(%[[x_conv]], %[[y_conv]], %{{[0-9]+}}, %{{.*}}) {{.*}}: (!fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> i64
70 ! CHECK-LABEL: dot_prod_int_kind_16
71 ! CHECK-SAME: %[[x:arg0]]: !fir.box<!fir.array<?xi128>>
72 ! CHECK-SAME: %[[y:arg1]]: !fir.box<!fir.array<?xi128>>
73 ! CHECK-SAME: %[[z:arg2]]: !fir.box<!fir.array<?xi128>>
74 subroutine dot_prod_int_kind_16 (x
, y
, z
)
75 integer(kind
=16), dimension(1:) :: x
,y
76 integer(kind
=16), dimension(1:) :: z
77 ! CHECK-DAG: %[[x_conv:.*]] = fir.convert %[[x]] : (!fir.box<!fir.array<?xi128>>) -> !fir.box<none>
78 ! CHECK-DAG: %[[y_conv:.*]] = fir.convert %[[y]] : (!fir.box<!fir.array<?xi128>>) -> !fir.box<none>
79 ! CHECK-DAG: %[[res:.*]] = fir.call @_FortranADotProductInteger16(%[[x_conv]], %[[y_conv]], %{{[0-9]+}}, %{{.*}}) {{.*}}: (!fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> i128
83 ! CHECK-LABEL: dot_prod_real_kind_default
84 ! CHECK-SAME: %[[x:arg0]]: !fir.box<!fir.array<?xf32>>
85 ! CHECK-SAME: %[[y:arg1]]: !fir.box<!fir.array<?xf32>>
86 ! CHECK-SAME: %[[z:arg2]]: !fir.box<!fir.array<?xf32>>
87 subroutine dot_prod_real_kind_default (x
, y
, z
)
88 real, dimension(1:) :: x
,y
89 real, dimension(1:) :: z
90 ! CHECK-DAG: %[[x_conv:.*]] = fir.convert %[[x]] : (!fir.box<!fir.array<?xf32>>) -> !fir.box<none>
91 ! CHECK-DAG: %[[y_conv:.*]] = fir.convert %[[y]] : (!fir.box<!fir.array<?xf32>>) -> !fir.box<none>
92 ! CHECK-DAG: %[[res:.*]] = fir.call @_FortranADotProductReal4(%[[x_conv]], %[[y_conv]], %{{[0-9]+}}, %{{.*}}) {{.*}}: (!fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> f32
96 ! CHECK-LABEL: dot_prod_real_kind_4
97 ! CHECK-SAME: %[[x:arg0]]: !fir.box<!fir.array<?xf32>>
98 ! CHECK-SAME: %[[y:arg1]]: !fir.box<!fir.array<?xf32>>
99 ! CHECK-SAME: %[[z:arg2]]: !fir.box<!fir.array<?xf32>>
100 subroutine dot_prod_real_kind_4 (x
, y
, z
)
101 real(kind
=4), dimension(1:) :: x
,y
102 real(kind
=4), dimension(1:) :: z
103 ! CHECK-DAG: %[[x_conv:.*]] = fir.convert %[[x]] : (!fir.box<!fir.array<?xf32>>) -> !fir.box<none>
104 ! CHECK-DAG: %[[y_conv:.*]] = fir.convert %[[y]] : (!fir.box<!fir.array<?xf32>>) -> !fir.box<none>
105 ! CHECK-DAG: %[[res:.*]] = fir.call @_FortranADotProductReal4(%[[x_conv]], %[[y_conv]], %{{[0-9]+}}, %{{.*}}) {{.*}}: (!fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> f32
109 ! CHECK-LABEL: dot_prod_real_kind_8
110 ! CHECK-SAME: %[[x:arg0]]: !fir.box<!fir.array<?xf64>>
111 ! CHECK-SAME: %[[y:arg1]]: !fir.box<!fir.array<?xf64>>
112 ! CHECK-SAME: %[[z:arg2]]: !fir.box<!fir.array<?xf64>>
113 subroutine dot_prod_real_kind_8 (x
, y
, z
)
114 real(kind
=8), dimension(1:) :: x
,y
115 real(kind
=8), dimension(1:) :: z
116 ! CHECK-DAG: %[[x_conv:.*]] = fir.convert %[[x]] : (!fir.box<!fir.array<?xf64>>) -> !fir.box<none>
117 ! CHECK-DAG: %[[y_conv:.*]] = fir.convert %[[y]] : (!fir.box<!fir.array<?xf64>>) -> !fir.box<none>
118 ! CHECK-DAG: %[[res:.*]] = fir.call @_FortranADotProductReal8(%[[x_conv]], %[[y_conv]], %{{[0-9]+}}, %{{.*}}) {{.*}}: (!fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> f64
122 ! CHECK-LABEL: dot_prod_real_kind_10
123 ! CHECK-SAME: %[[x:arg0]]: !fir.box<!fir.array<?xf80>>
124 ! CHECK-SAME: %[[y:arg1]]: !fir.box<!fir.array<?xf80>>
125 ! CHECK-SAME: %[[z:arg2]]: !fir.box<!fir.array<?xf80>>
126 subroutine dot_prod_real_kind_10 (x
, y
, z
)
127 real(kind
=10), dimension(1:) :: x
,y
128 real(kind
=10), dimension(1:) :: z
129 ! CHECK-DAG: %[[x_conv:.*]] = fir.convert %[[x]] : (!fir.box<!fir.array<?xf80>>) -> !fir.box<none>
130 ! CHECK-DAG: %[[y_conv:.*]] = fir.convert %[[y]] : (!fir.box<!fir.array<?xf80>>) -> !fir.box<none>
131 ! CHECK-DAG: %[[res:.*]] = fir.call @_FortranADotProductReal10(%[[x_conv]], %[[y_conv]], %{{[0-9]+}}, %{{.*}}) {{.*}}: (!fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> f80
135 ! CHECK-LABEL: dot_prod_real_kind_16
136 ! CHECK-SAME: %[[x:arg0]]: !fir.box<!fir.array<?xf128>>
137 ! CHECK-SAME: %[[y:arg1]]: !fir.box<!fir.array<?xf128>>
138 ! CHECK-SAME: %[[z:arg2]]: !fir.box<!fir.array<?xf128>>
139 subroutine dot_prod_real_kind_16 (x
, y
, z
)
140 real(kind
=16), dimension(1:) :: x
,y
141 real(kind
=16), dimension(1:) :: z
142 ! CHECK-DAG: %[[x_conv:.*]] = fir.convert %[[x]] : (!fir.box<!fir.array<?xf128>>) -> !fir.box<none>
143 ! CHECK-DAG: %[[y_conv:.*]] = fir.convert %[[y]] : (!fir.box<!fir.array<?xf128>>) -> !fir.box<none>
144 ! CHECK-DAG: %[[res:.*]] = fir.call @_FortranADotProductReal16(%[[x_conv]], %[[y_conv]], %{{[0-9]+}}, %{{.*}}) {{.*}}: (!fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> f128
148 ! CHECK-LABEL: dot_prod_double_default
149 ! CHECK-SAME: %[[x:arg0]]: !fir.box<!fir.array<?xf64>>
150 ! CHECK-SAME: %[[y:arg1]]: !fir.box<!fir.array<?xf64>>
151 ! CHECK-SAME: %[[z:arg2]]: !fir.box<!fir.array<?xf64>>
152 subroutine dot_prod_double_default (x
, y
, z
)
153 double precision, dimension(1:) :: x
,y
154 double precision, dimension(1:) :: z
155 ! CHECK-DAG: %[[x_conv:.*]] = fir.convert %[[x]] : (!fir.box<!fir.array<?xf64>>) -> !fir.box<none>
156 ! CHECK-DAG: %[[y_conv:.*]] = fir.convert %[[y]] : (!fir.box<!fir.array<?xf64>>) -> !fir.box<none>
157 ! CHECK-DAG: %[[res:.*]] = fir.call @_FortranADotProductReal8(%[[x_conv]], %[[y_conv]], %{{[0-9]+}}, %{{.*}}) {{.*}}: (!fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> f64
161 ! CHECK-LABEL: dot_prod_complex_default
162 ! CHECK-SAME: %[[x:arg0]]: !fir.box<!fir.array<?x!fir.complex<4>>>
163 ! CHECK-SAME: %[[y:arg1]]: !fir.box<!fir.array<?x!fir.complex<4>>>
164 ! CHECK-SAME: %[[z:arg2]]: !fir.box<!fir.array<?x!fir.complex<4>>>
165 subroutine dot_prod_complex_default (x
, y
, z
)
166 complex, dimension(1:) :: x
,y
167 complex, dimension(1:) :: z
168 ! CHECK-DAG: %0 = fir.alloca !fir.complex<4>
169 ! CHECK-DAG: %[[res_conv:[0-9]+]] = fir.convert %0 : (!fir.ref<!fir.complex<4>>) -> !fir.ref<complex<f32>>
170 ! CHECK-DAG: %[[x_conv:.*]] = fir.convert %[[x]] : (!fir.box<!fir.array<?x!fir.complex<4>>>) -> !fir.box<none>
171 ! CHECK-DAG: %[[y_conv:.*]] = fir.convert %[[y]] : (!fir.box<!fir.array<?x!fir.complex<4>>>) -> !fir.box<none>
172 ! CHECK-DAG: fir.call @_FortranACppDotProductComplex4(%[[res_conv]], %[[x_conv]], %[[y_conv]], %{{[0-9]+}}, %{{.*}}) {{.*}}: (!fir.ref<complex<f32>>, !fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> none
176 ! CHECK-LABEL: dot_prod_complex_kind_4
177 ! CHECK-SAME: %[[x:arg0]]: !fir.box<!fir.array<?x!fir.complex<4>>>
178 ! CHECK-SAME: %[[y:arg1]]: !fir.box<!fir.array<?x!fir.complex<4>>>
179 ! CHECK-SAME: %[[z:arg2]]: !fir.box<!fir.array<?x!fir.complex<4>>>
180 subroutine dot_prod_complex_kind_4 (x
, y
, z
)
181 complex(kind
=4), dimension(1:) :: x
,y
182 complex(kind
=4), dimension(1:) :: z
183 ! CHECK-DAG: %0 = fir.alloca !fir.complex<4>
184 ! CHECK-DAG: %[[res_conv:[0-9]+]] = fir.convert %0 : (!fir.ref<!fir.complex<4>>) -> !fir.ref<complex<f32>>
185 ! CHECK-DAG: %[[x_conv:.*]] = fir.convert %[[x]] : (!fir.box<!fir.array<?x!fir.complex<4>>>) -> !fir.box<none>
186 ! CHECK-DAG: %[[y_conv:.*]] = fir.convert %[[y]] : (!fir.box<!fir.array<?x!fir.complex<4>>>) -> !fir.box<none>
187 ! CHECK-DAG: fir.call @_FortranACppDotProductComplex4(%[[res_conv]], %[[x_conv]], %[[y_conv]], %{{[0-9]+}}, %{{.*}}) {{.*}}: (!fir.ref<complex<f32>>, !fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> none
191 ! CHECK-LABEL: dot_prod_complex_kind_8
192 ! CHECK-SAME: %[[x:arg0]]: !fir.box<!fir.array<?x!fir.complex<8>>>
193 ! CHECK-SAME: %[[y:arg1]]: !fir.box<!fir.array<?x!fir.complex<8>>>
194 ! CHECK-SAME: %[[z:arg2]]: !fir.box<!fir.array<?x!fir.complex<8>>>
195 subroutine dot_prod_complex_kind_8 (x
, y
, z
)
196 complex(kind
=8), dimension(1:) :: x
,y
197 complex(kind
=8), dimension(1:) :: z
198 ! CHECK-DAG: %0 = fir.alloca !fir.complex<8>
199 ! CHECK-DAG: %[[res_conv:[0-9]+]] = fir.convert %0 : (!fir.ref<!fir.complex<8>>) -> !fir.ref<complex<f64>>
200 ! CHECK-DAG: %[[x_conv:.*]] = fir.convert %[[x]] : (!fir.box<!fir.array<?x!fir.complex<8>>>) -> !fir.box<none>
201 ! CHECK-DAG: %[[y_conv:.*]] = fir.convert %[[y]] : (!fir.box<!fir.array<?x!fir.complex<8>>>) -> !fir.box<none>
202 ! CHECK-DAG: fir.call @_FortranACppDotProductComplex8(%[[res_conv]], %[[x_conv]], %[[y_conv]], %{{[0-9]+}}, %{{.*}}) {{.*}}: (!fir.ref<complex<f64>>, !fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> none
206 ! CHECK-LABEL: dot_prod_complex_kind_10
207 ! CHECK-SAME: %[[x:arg0]]: !fir.box<!fir.array<?x!fir.complex<10>>>
208 ! CHECK-SAME: %[[y:arg1]]: !fir.box<!fir.array<?x!fir.complex<10>>>
209 ! CHECK-SAME: %[[z:arg2]]: !fir.box<!fir.array<?x!fir.complex<10>>>
210 subroutine dot_prod_complex_kind_10 (x
, y
, z
)
211 complex(kind
=10), dimension(1:) :: x
,y
212 complex(kind
=10), dimension(1:) :: z
213 ! CHECK-DAG: %0 = fir.alloca !fir.complex<10>
214 ! CHECK-DAG: %[[res_conv:[0-9]+]] = fir.convert %0 : (!fir.ref<!fir.complex<10>>) -> !fir.ref<complex<f80>>
215 ! CHECK-DAG: %[[x_conv:.*]] = fir.convert %[[x]] : (!fir.box<!fir.array<?x!fir.complex<10>>>) -> !fir.box<none>
216 ! CHECK-DAG: %[[y_conv:.*]] = fir.convert %[[y]] : (!fir.box<!fir.array<?x!fir.complex<10>>>) -> !fir.box<none>
217 ! CHECK-DAG: fir.call @_FortranACppDotProductComplex10(%[[res_conv]], %[[x_conv]], %[[y_conv]], %{{[0-9]+}}, %{{.*}}) {{.*}}: (!fir.ref<complex<f80>>, !fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> ()
221 ! CHECK-LABEL: dot_prod_complex_kind_16
222 ! CHECK-SAME: %[[x:arg0]]: !fir.box<!fir.array<?x!fir.complex<16>>>
223 ! CHECK-SAME: %[[y:arg1]]: !fir.box<!fir.array<?x!fir.complex<16>>>
224 ! CHECK-SAME: %[[z:arg2]]: !fir.box<!fir.array<?x!fir.complex<16>>>
225 subroutine dot_prod_complex_kind_16 (x
, y
, z
)
226 complex(kind
=16), dimension(1:) :: x
,y
227 complex(kind
=16), dimension(1:) :: z
228 ! CHECK-DAG: %0 = fir.alloca !fir.complex<16>
229 ! CHECK-DAG: %[[res_conv:[0-9]+]] = fir.convert %0 : (!fir.ref<!fir.complex<16>>) -> !fir.ref<complex<f128>>
230 ! CHECK-DAG: %[[x_conv:.*]] = fir.convert %[[x]] : (!fir.box<!fir.array<?x!fir.complex<16>>>) -> !fir.box<none>
231 ! CHECK-DAG: %[[y_conv:.*]] = fir.convert %[[y]] : (!fir.box<!fir.array<?x!fir.complex<16>>>) -> !fir.box<none>
232 ! CHECK-DAG: fir.call @_FortranACppDotProductComplex16(%[[res_conv]], %[[x_conv]], %[[y_conv]], %{{[0-9]+}}, %{{.*}}) {{.*}}: (!fir.ref<complex<f128>>, !fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> ()
236 ! CHECK-LABEL: dot_prod_logical
237 ! CHECK-SAME: %[[x:arg0]]: !fir.box<!fir.array<?x!fir.logical<4>>>
238 ! CHECK-SAME: %[[y:arg1]]: !fir.box<!fir.array<?x!fir.logical<4>>>
239 ! CHECK-SAME: %[[z:arg2]]: !fir.box<!fir.array<?x!fir.logical<4>>>
240 subroutine dot_prod_logical (x
, y
, z
)
241 logical, dimension(1:) :: x
,y
242 logical, dimension(1:) :: z
243 ! CHECK-DAG: %[[x_conv:.*]] = fir.convert %[[x]] : (!fir.box<!fir.array<?x!fir.logical<4>>>) -> !fir.box<none>
244 ! CHECK-DAG: %[[y_conv:.*]] = fir.convert %[[y]] : (!fir.box<!fir.array<?x!fir.logical<4>>>) -> !fir.box<none>
245 ! CHECK-DAG: %[[res:.*]] = fir.call @_FortranADotProductLogical(%[[x_conv]], %[[y_conv]], %{{[0-9]+}}, %{{.*}}) {{.*}}: (!fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> i1
249 ! CHECK-LABEL: dot_product_mixed_int_real
250 ! CHECK-SAME: %[[x:arg0]]: !fir.box<!fir.array<?xi32>>
251 ! CHECK-SAME: %[[y:arg1]]: !fir.box<!fir.array<?xf32>>
252 ! CHECK-SAME: %[[z:arg2]]: !fir.box<!fir.array<?xf32>>
253 subroutine dot_product_mixed_int_real(x
, y
, z
)
254 integer, dimension(1:) :: x
255 real, dimension(1:) :: y
, z
256 ! CHECK-DAG: %[[x_conv:.*]] = fir.convert %[[x]] : (!fir.box<!fir.array<?xi32>>) -> !fir.box<none>
257 ! CHECK-DAG: %[[y_conv:.*]] = fir.convert %[[y]] : (!fir.box<!fir.array<?xf32>>) -> !fir.box<none>
258 ! CHECK-DAG: %[[res:.*]] = fir.call @_FortranADotProductReal4(%[[x_conv]], %[[y_conv]], %{{[0-9]+}}, %{{.*}}) {{.*}}: (!fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> f32
262 ! CHECK-LABEL: dot_product_mixed_int_complex
263 ! CHECK-SAME: %[[x:arg0]]: !fir.box<!fir.array<?xi32>>
264 ! CHECK-SAME: %[[y:arg1]]: !fir.box<!fir.array<?x!fir.complex<4>>>
265 ! CHECK-SAME: %[[z:arg2]]: !fir.box<!fir.array<?x!fir.complex<4>>>
266 subroutine dot_product_mixed_int_complex(x
, y
, z
)
267 integer, dimension(1:) :: x
268 complex, dimension(1:) :: y
, z
269 ! CHECK-DAG: %[[res:.*]] = fir.alloca !fir.complex<4>
270 ! CHECK-DAG: %[[res_conv:.*]] = fir.convert %[[res]] : (!fir.ref<!fir.complex<4>>) -> !fir.ref<complex<f32>>
271 ! CHECK-DAG: %[[x_conv:.*]] = fir.convert %[[x]] : (!fir.box<!fir.array<?xi32>>) -> !fir.box<none>
272 ! CHECK-DAG: %[[y_conv:.*]] = fir.convert %[[y]] : (!fir.box<!fir.array<?x!fir.complex<4>>>) -> !fir.box<none>
273 ! CHECK-DAG: fir.call @_FortranACppDotProductComplex4(%[[res_conv]], %[[x_conv]], %[[y_conv]], %{{[0-9]+}}, %{{.*}}) {{.*}}: (!fir.ref<complex<f32>>, !fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> none
277 ! CHECK-LABEL: dot_product_mixed_real_complex
278 ! CHECK-SAME: %[[x:arg0]]: !fir.box<!fir.array<?xf32>>
279 ! CHECK-SAME: %[[y:arg1]]: !fir.box<!fir.array<?x!fir.complex<4>>>
280 ! CHECK-SAME: %[[z:arg2]]: !fir.box<!fir.array<?x!fir.complex<4>>>
281 subroutine dot_product_mixed_real_complex(x
, y
, z
)
282 real, dimension(1:) :: x
283 complex, dimension(1:) :: y
, z
284 ! CHECK-DAG: %[[res:.*]] = fir.alloca !fir.complex<4>
285 ! CHECK-DAG: %[[res_conv:.*]] = fir.convert %[[res]] : (!fir.ref<!fir.complex<4>>) -> !fir.ref<complex<f32>>
286 ! CHECK-DAG: %[[x_conv:.*]] = fir.convert %[[x]] : (!fir.box<!fir.array<?xf32>>) -> !fir.box<none>
287 ! CHECK-DAG: %[[y_conv:.*]] = fir.convert %[[y]] : (!fir.box<!fir.array<?x!fir.complex<4>>>) -> !fir.box<none>
288 ! CHECK-DAG: fir.call @_FortranACppDotProductComplex4(%[[res_conv]], %[[x_conv]], %[[y_conv]], %{{[0-9]+}}, %{{.*}}) {{.*}}: (!fir.ref<complex<f32>>, !fir.box<none>, !fir.box<none>, !fir.ref<i8>, i32) -> none