[flang][openacc] Use OpenACC terminator instead of fir.unreachable after Stop stmt...
[llvm-project.git] / flang / test / Lower / PowerPC / ppc-vec-load.f90
blob1af8cd39c506b768f8d48fdb79bd6106672bd294
1 ! RUN: bbc -emit-fir %s -o - | FileCheck --check-prefixes="FIR" %s
2 ! RUN: %flang -emit-llvm -S %s -o - | FileCheck --check-prefixes="LLVMIR" %s
3 ! REQUIRES: target=powerpc{{.*}}
5 !----------------------
6 ! vec_ld
7 !----------------------
9 ! CHECK-LABEL: @vec_ld_testi8
10 subroutine vec_ld_testi8(arg1, arg2, res)
11 integer(1) :: arg1
12 vector(integer(1)) :: arg2, res
13 res = vec_ld(arg1, arg2)
15 ! FIR: %[[arg1:.*]] = fir.load %{{.*}} : !fir.ref<i8>
16 ! FIR: %[[arg2:.*]] = fir.convert %{{.*}} : (!fir.ref<!fir.vector<16:i8>>) -> !fir.ref<!fir.array<?xi8>>
17 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i8) -> !fir.ref<!fir.array<?xi8>>
18 ! FIR: %[[call:.*]] = fir.call @llvm.ppc.altivec.lvx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
19 ! FIR: %[[bc:.*]] = vector.bitcast %[[call]] : vector<4xi32> to vector<16xi8>
20 ! FIR: %[[cnv:.*]] = fir.convert %[[bc]] : (vector<16xi8>) -> !fir.vector<16:i8>
21 ! FIR: fir.store %[[cnv]] to %arg2 : !fir.ref<!fir.vector<16:i8>>
23 ! LLVMIR: %[[arg1:.*]] = load i8, ptr %{{.*}}, align 1
24 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i8 %[[arg1]]
25 ! LLVMIR: %[[call:.*]] = call <4 x i32> @llvm.ppc.altivec.lvx(ptr %[[addr]])
26 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[call]] to <16 x i8>
27 ! LLVMIR: store <16 x i8> %[[bc]], ptr %2, align 16
28 end subroutine vec_ld_testi8
30 ! CHECK-LABEL: @vec_ld_testi16
31 subroutine vec_ld_testi16(arg1, arg2, res)
32 integer(2) :: arg1
33 vector(integer(2)) :: arg2, res
34 res = vec_ld(arg1, arg2)
36 ! FIR: %[[arg1:.*]] = fir.load %{{.*}} : !fir.ref<i16>
37 ! FIR: %[[arg2:.*]] = fir.convert %{{.*}} : (!fir.ref<!fir.vector<8:i16>>) -> !fir.ref<!fir.array<?xi8>>
38 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
39 ! FIR: %[[call:.*]] = fir.call @llvm.ppc.altivec.lvx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
40 ! FIR: %[[bc:.*]] = vector.bitcast %[[call]] : vector<4xi32> to vector<8xi16>
41 ! FIR: %[[cnv:.*]] = fir.convert %[[bc]] : (vector<8xi16>) -> !fir.vector<8:i16>
42 ! FIR: fir.store %[[cnv]] to %arg2 : !fir.ref<!fir.vector<8:i16>>
44 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
45 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[arg1]]
46 ! LLVMIR: %[[call:.*]] = call <4 x i32> @llvm.ppc.altivec.lvx(ptr %[[addr]])
47 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[call]] to <8 x i16>
48 ! LLVMIR: store <8 x i16> %[[bc]], ptr %2, align 16
49 end subroutine vec_ld_testi16
51 ! CHECK-LABEL: @vec_ld_testi32
52 subroutine vec_ld_testi32(arg1, arg2, res)
53 integer(4) :: arg1
54 vector(integer(4)) :: arg2, res
55 res = vec_ld(arg1, arg2)
57 ! FIR: %[[arg1:.*]] = fir.load %{{.*}} : !fir.ref<i32>
58 ! FIR: %[[arg2:.*]] = fir.convert %{{.*}} : (!fir.ref<!fir.vector<4:i32>>) -> !fir.ref<!fir.array<?xi8>>
59 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
60 ! FIR: %[[call:.*]] = fir.call @llvm.ppc.altivec.lvx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
61 ! FIR: %[[cnv:.*]] = fir.convert %[[call]] : (vector<4xi32>) -> !fir.vector<4:i32>
62 ! FIR: fir.store %[[cnv]] to %arg2 : !fir.ref<!fir.vector<4:i32>>
64 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
65 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1]]
66 ! LLVMIR: %[[bc:.*]] = call <4 x i32> @llvm.ppc.altivec.lvx(ptr %[[addr]])
67 ! LLVMIR: store <4 x i32> %[[bc]], ptr %2, align 16
68 end subroutine vec_ld_testi32
70 ! CHECK-LABEL: @vec_ld_testf32
71 subroutine vec_ld_testf32(arg1, arg2, res)
72 integer(8) :: arg1
73 vector(real(4)) :: arg2, res
74 res = vec_ld(arg1, arg2)
76 ! FIR: %[[arg1:.*]] = fir.load %{{.*}} : !fir.ref<i64>
77 ! FIR: %[[arg1i32:.*]] = fir.convert %[[arg1]] : (i64) -> i32
78 ! FIR: %[[arg2:.*]] = fir.convert %{{.*}} : (!fir.ref<!fir.vector<4:f32>>) -> !fir.ref<!fir.array<?xi8>>
79 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1i32]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
80 ! FIR: %[[call:.*]] = fir.call @llvm.ppc.altivec.lvx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
81 ! FIR: %[[bc:.*]] = vector.bitcast %[[call]] : vector<4xi32> to vector<4xf32>
82 ! FIR: %[[cnv:.*]] = fir.convert %[[bc]] : (vector<4xf32>) -> !fir.vector<4:f32>
83 ! FIR: fir.store %[[cnv]] to %arg2 : !fir.ref<!fir.vector<4:f32>>
85 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
86 ! LLVMIR: %[[arg1i32:.*]] = trunc i64 %[[arg1]] to i32
87 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1i32]]
88 ! LLVMIR: %[[call:.*]] = call <4 x i32> @llvm.ppc.altivec.lvx(ptr %[[addr]])
89 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[call]] to <4 x float>
90 ! LLVMIR: store <4 x float> %[[bc]], ptr %2, align 16
91 end subroutine vec_ld_testf32
93 ! CHECK-LABEL: @vec_ld_testu32
94 subroutine vec_ld_testu32(arg1, arg2, res)
95 integer(1) :: arg1
96 vector(unsigned(4)) :: arg2, res
97 res = vec_ld(arg1, arg2)
99 ! FIR: %[[arg1:.*]] = fir.load %{{.*}} : !fir.ref<i8>
100 ! FIR: %[[arg2:.*]] = fir.convert %{{.*}} : (!fir.ref<!fir.vector<4:ui32>>) -> !fir.ref<!fir.array<?xi8>>
101 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i8) -> !fir.ref<!fir.array<?xi8>>
102 ! FIR: %[[call:.*]] = fir.call @llvm.ppc.altivec.lvx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
103 ! FIR: %[[cnv:.*]] = fir.convert %[[call]] : (vector<4xi32>) -> !fir.vector<4:ui32>
104 ! FIR: fir.store %[[cnv]] to %arg2 : !fir.ref<!fir.vector<4:ui32>>
106 ! LLVMIR: %[[arg1:.*]] = load i8, ptr %0, align 1
107 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i8 %[[arg1]]
108 ! LLVMIR: %[[call:.*]] = call <4 x i32> @llvm.ppc.altivec.lvx(ptr %[[addr]])
109 ! LLVMIR: store <4 x i32> %[[call]], ptr %2, align 16
110 end subroutine vec_ld_testu32
112 ! CHECK-LABEL: @vec_ld_testi32a
113 subroutine vec_ld_testi32a(arg1, arg2, res)
114 integer(4) :: arg1
115 integer(4) :: arg2(10)
116 vector(integer(4)) :: res
117 res = vec_ld(arg1, arg2)
119 ! FIR: %[[arg1:.*]] = fir.load %{{.*}} : !fir.ref<i32>
120 ! FIR: %[[arg2:.*]] = fir.convert %{{.*}} : (!fir.ref<!fir.array<10xi32>>) -> !fir.ref<!fir.array<?xi8>>
121 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
122 ! FIR: %[[call:.*]] = fir.call @llvm.ppc.altivec.lvx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
123 ! FIR: %[[cnv:.*]] = fir.convert %[[call]] : (vector<4xi32>) -> !fir.vector<4:i32>
124 ! FIR: fir.store %[[cnv]] to %arg2 : !fir.ref<!fir.vector<4:i32>>
126 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
127 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1]]
128 ! LLVMIR: %[[call:.*]] = call <4 x i32> @llvm.ppc.altivec.lvx(ptr %[[addr]])
129 ! LLVMIR: store <4 x i32> %[[call]], ptr %2, align 16
130 end subroutine vec_ld_testi32a
132 ! CHECK-LABEL: @vec_ld_testf32av
133 subroutine vec_ld_testf32av(arg1, arg2, res)
134 integer(8) :: arg1
135 vector(real(4)) :: arg2(2, 4, 8)
136 vector(real(4)) :: res
137 res = vec_ld(arg1, arg2)
139 ! FIR: %[[arg1:.*]] = fir.load %{{.*}} : !fir.ref<i64>
140 ! FIR: %[[arg1i32:.*]] = fir.convert %[[arg1]] : (i64) -> i32
141 ! FIR: %[[arg2:.*]] = fir.convert %{{.*}} : (!fir.ref<!fir.array<2x4x8x!fir.vector<4:f32>>>) -> !fir.ref<!fir.array<?xi8>>
142 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1i32]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
143 ! FIR: %[[call:.*]] = fir.call @llvm.ppc.altivec.lvx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
144 ! FIR: %[[bc:.*]] = vector.bitcast %[[call]] : vector<4xi32> to vector<4xf32>
145 ! FIR: %[[cnv:.*]] = fir.convert %[[bc]] : (vector<4xf32>) -> !fir.vector<4:f32>
146 ! FIR: fir.store %[[cnv]] to %arg2 : !fir.ref<!fir.vector<4:f32>>
148 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
149 ! LLVMIR: %[[arg1i32:.*]] = trunc i64 %[[arg1]] to i32
150 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1i32]]
151 ! LLVMIR: %[[call:.*]] = call <4 x i32> @llvm.ppc.altivec.lvx(ptr %[[addr]])
152 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[call]] to <4 x float>
153 ! LLVMIR: store <4 x float> %[[bc]], ptr %2, align 16
154 end subroutine vec_ld_testf32av
156 ! CHECK-LABEL: @vec_ld_testi32s
157 subroutine vec_ld_testi32s(arg1, arg2, res)
158 integer(4) :: arg1
159 real(4) :: arg2
160 vector(real(4)) :: res
161 res = vec_ld(arg1, arg2)
163 ! FIR: %[[arg1:.*]] = fir.load %{{.*}} : !fir.ref<i32>
164 ! FIR: %[[arg2:.*]] = fir.convert %{{.*}} : (!fir.ref<f32>) -> !fir.ref<!fir.array<?xi8>>
165 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
166 ! FIR: %[[call:.*]] = fir.call @llvm.ppc.altivec.lvx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
167 ! FIR: %[[bc:.*]] = vector.bitcast %[[call]] : vector<4xi32> to vector<4xf32>
168 ! FIR: %[[cnv:.*]] = fir.convert %[[bc]] : (vector<4xf32>) -> !fir.vector<4:f32>
169 ! FIR: fir.store %[[cnv]] to %arg2 : !fir.ref<!fir.vector<4:f32>>
171 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
172 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1]]
173 ! LLVMIR: %[[call:.*]] = call <4 x i32> @llvm.ppc.altivec.lvx(ptr %[[addr]])
174 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[call]] to <4 x float>
175 ! LLVMIR: store <4 x float> %[[bc]], ptr %2, align 16
176 end subroutine vec_ld_testi32s
178 !----------------------
179 ! vec_lde
180 !----------------------
182 ! CHECK-LABEL: @vec_lde_testi8s
183 subroutine vec_lde_testi8s(arg1, arg2, res)
184 integer(1) :: arg1
185 integer(1) :: arg2
186 vector(integer(1)) :: res
187 res = vec_lde(arg1, arg2)
189 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i8>
190 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<i8>) -> !fir.ref<!fir.array<?xi8>>
191 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i8) -> !fir.ref<!fir.array<?xi8>>
192 ! FIR: %[[call:.*]] = fir.call @llvm.ppc.altivec.lvebx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<16xi8>
193 ! FIR: %[[cnv:.*]] = fir.convert %[[call]] : (vector<16xi8>) -> !fir.vector<16:i8>
194 ! FIR: fir.store %[[cnv]] to %arg2 : !fir.ref<!fir.vector<16:i8>>
196 ! LLVMIR: %[[arg1:.*]] = load i8, ptr %0, align 1
197 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i8 %[[arg1]]
198 ! LLVMIR: %[[call:.*]] = call <16 x i8> @llvm.ppc.altivec.lvebx(ptr %[[addr]])
199 ! LLVMIR: store <16 x i8> %[[call]], ptr %2, align 16
200 end subroutine vec_lde_testi8s
202 ! CHECK-LABEL: @vec_lde_testi16a
203 subroutine vec_lde_testi16a(arg1, arg2, res)
204 integer(2) :: arg1
205 integer(2) :: arg2(2, 4, 8)
206 vector(integer(2)) :: res
207 res = vec_lde(arg1, arg2)
209 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
210 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x4x8xi16>>) -> !fir.ref<!fir.array<?xi8>>
211 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
212 ! FIR: %[[call:.*]] = fir.call @llvm.ppc.altivec.lvehx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<8xi16>
213 ! FIR: %[[cnv:.*]] = fir.convert %[[call]] : (vector<8xi16>) -> !fir.vector<8:i16>
214 ! FIR: fir.store %[[cnv]] to %arg2 : !fir.ref<!fir.vector<8:i16>>
216 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
217 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[arg1]]
218 ! LLVMIR: %[[call:.*]] = call <8 x i16> @llvm.ppc.altivec.lvehx(ptr %[[addr]])
219 ! LLVMIR: store <8 x i16> %[[call]], ptr %2, align 16
220 end subroutine vec_lde_testi16a
222 ! CHECK-LABEL: @vec_lde_testi32a
223 subroutine vec_lde_testi32a(arg1, arg2, res)
224 integer(4) :: arg1
225 integer(4) :: arg2(4)
226 vector(integer(4)) :: res
227 res = vec_lde(arg1, arg2)
229 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i32>
230 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4xi32>>) -> !fir.ref<!fir.array<?xi8>>
231 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
232 ! FIR: %[[call:.*]] = fir.call @llvm.ppc.altivec.lvewx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
233 ! FIR: %[[cnv:.*]] = fir.convert %[[call]] : (vector<4xi32>) -> !fir.vector<4:i32>
234 ! FIR: fir.store %[[cnv]] to %arg2 : !fir.ref<!fir.vector<4:i32>>
236 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
237 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1]]
238 ! LLVMIR: %[[call:.*]] = call <4 x i32> @llvm.ppc.altivec.lvewx(ptr %[[addr]])
239 ! LLVMIR: store <4 x i32> %[[call]], ptr %2, align 16
240 end subroutine vec_lde_testi32a
242 ! CHECK-LABEL: @vec_lde_testf32a
243 subroutine vec_lde_testf32a(arg1, arg2, res)
244 integer(8) :: arg1
245 real(4) :: arg2(4)
246 vector(real(4)) :: res
247 res = vec_lde(arg1, arg2)
249 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
250 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4xf32>>) -> !fir.ref<!fir.array<?xi8>>
251 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
252 ! FIR: %[[call:.*]] = fir.call @llvm.ppc.altivec.lvewx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
253 ! FIR: %[[bc:.*]] = vector.bitcast %[[call]] : vector<4xi32> to vector<4xf32>
254 ! FIR: %[[cnv:.*]] = fir.convert %[[bc]] : (vector<4xf32>) -> !fir.vector<4:f32>
255 ! FIR: fir.store %[[cnv]] to %arg2 : !fir.ref<!fir.vector<4:f32>>
257 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
258 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[arg1]]
259 ! LLVMIR: %[[call:.*]] = call <4 x i32> @llvm.ppc.altivec.lvewx(ptr %[[addr]])
260 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[call]] to <4 x float>
261 ! LLVMIR: store <4 x float> %[[bc]], ptr %2, align 16
262 end subroutine vec_lde_testf32a
264 !----------------------
265 ! vec_ldl
266 !----------------------
268 ! CHECK-LABEL: @vec_ldl_testi8
269 subroutine vec_ldl_testi8(arg1, arg2, res)
270 integer(1) :: arg1
271 vector(integer(1)) :: arg2, res
272 res = vec_ldl(arg1, arg2)
274 ! FIR: %[[arg1:.*]] = fir.load %{{.*}} : !fir.ref<i8>
275 ! FIR: %[[arg2:.*]] = fir.convert %{{.*}} : (!fir.ref<!fir.vector<16:i8>>) -> !fir.ref<!fir.array<?xi8>>
276 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i8) -> !fir.ref<!fir.array<?xi8>>
277 ! FIR: %[[call:.*]] = fir.call @llvm.ppc.altivec.lvxl(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
278 ! FIR: %[[bc:.*]] = vector.bitcast %[[call]] : vector<4xi32> to vector<16xi8>
279 ! FIR: %[[cnv:.*]] = fir.convert %[[bc]] : (vector<16xi8>) -> !fir.vector<16:i8>
280 ! FIR: fir.store %[[cnv]] to %arg2 : !fir.ref<!fir.vector<16:i8>>
282 ! LLVMIR: %[[arg1:.*]] = load i8, ptr %{{.*}}, align 1
283 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i8 %[[arg1]]
284 ! LLVMIR: %[[call:.*]] = call <4 x i32> @llvm.ppc.altivec.lvxl(ptr %[[addr]])
285 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[call]] to <16 x i8>
286 ! LLVMIR: store <16 x i8> %[[bc]], ptr %2, align 16
287 end subroutine vec_ldl_testi8
289 ! CHECK-LABEL: @vec_ldl_testi16
290 subroutine vec_ldl_testi16(arg1, arg2, res)
291 integer(2) :: arg1
292 vector(integer(2)) :: arg2, res
293 res = vec_ldl(arg1, arg2)
295 ! FIR: %[[arg1:.*]] = fir.load %{{.*}} : !fir.ref<i16>
296 ! FIR: %[[arg2:.*]] = fir.convert %{{.*}} : (!fir.ref<!fir.vector<8:i16>>) -> !fir.ref<!fir.array<?xi8>>
297 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
298 ! FIR: %[[call:.*]] = fir.call @llvm.ppc.altivec.lvxl(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
299 ! FIR: %[[bc:.*]] = vector.bitcast %[[call]] : vector<4xi32> to vector<8xi16>
300 ! FIR: %[[cnv:.*]] = fir.convert %[[bc]] : (vector<8xi16>) -> !fir.vector<8:i16>
301 ! FIR: fir.store %[[cnv]] to %arg2 : !fir.ref<!fir.vector<8:i16>>
303 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
304 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[arg1]]
305 ! LLVMIR: %[[call:.*]] = call <4 x i32> @llvm.ppc.altivec.lvxl(ptr %[[addr]])
306 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[call]] to <8 x i16>
307 ! LLVMIR: store <8 x i16> %[[bc]], ptr %2, align 16
308 end subroutine vec_ldl_testi16
310 ! CHECK-LABEL: @vec_ldl_testi32
311 subroutine vec_ldl_testi32(arg1, arg2, res)
312 integer(4) :: arg1
313 vector(integer(4)) :: arg2, res
314 res = vec_ldl(arg1, arg2)
316 ! FIR: %[[arg1:.*]] = fir.load %{{.*}} : !fir.ref<i32>
317 ! FIR: %[[arg2:.*]] = fir.convert %{{.*}} : (!fir.ref<!fir.vector<4:i32>>) -> !fir.ref<!fir.array<?xi8>>
318 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
319 ! FIR: %[[call:.*]] = fir.call @llvm.ppc.altivec.lvxl(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
320 ! FIR: %[[cnv:.*]] = fir.convert %[[call]] : (vector<4xi32>) -> !fir.vector<4:i32>
321 ! FIR: fir.store %[[cnv]] to %arg2 : !fir.ref<!fir.vector<4:i32>>
323 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
324 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1]]
325 ! LLVMIR: %[[bc:.*]] = call <4 x i32> @llvm.ppc.altivec.lvxl(ptr %[[addr]])
326 ! LLVMIR: store <4 x i32> %[[bc]], ptr %2, align 16
327 end subroutine vec_ldl_testi32
329 ! CHECK-LABEL: @vec_ldl_testf32
330 subroutine vec_ldl_testf32(arg1, arg2, res)
331 integer(8) :: arg1
332 vector(real(4)) :: arg2, res
333 res = vec_ldl(arg1, arg2)
335 ! FIR: %[[arg1:.*]] = fir.load %{{.*}} : !fir.ref<i64>
336 ! FIR: %[[arg2:.*]] = fir.convert %{{.*}} : (!fir.ref<!fir.vector<4:f32>>) -> !fir.ref<!fir.array<?xi8>>
337 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
338 ! FIR: %[[call:.*]] = fir.call @llvm.ppc.altivec.lvxl(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
339 ! FIR: %[[bc:.*]] = vector.bitcast %[[call]] : vector<4xi32> to vector<4xf32>
340 ! FIR: %[[cnv:.*]] = fir.convert %[[bc]] : (vector<4xf32>) -> !fir.vector<4:f32>
341 ! FIR: fir.store %[[cnv]] to %arg2 : !fir.ref<!fir.vector<4:f32>>
343 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
344 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[arg1]]
345 ! LLVMIR: %[[call:.*]] = call <4 x i32> @llvm.ppc.altivec.lvxl(ptr %[[addr]])
346 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[call]] to <4 x float>
347 ! LLVMIR: store <4 x float> %[[bc]], ptr %2, align 16
348 end subroutine vec_ldl_testf32
350 ! CHECK-LABEL: @vec_ldl_testu32
351 subroutine vec_ldl_testu32(arg1, arg2, res)
352 integer(1) :: arg1
353 vector(unsigned(4)) :: arg2, res
354 res = vec_ldl(arg1, arg2)
356 ! FIR: %[[arg1:.*]] = fir.load %{{.*}} : !fir.ref<i8>
357 ! FIR: %[[arg2:.*]] = fir.convert %{{.*}} : (!fir.ref<!fir.vector<4:ui32>>) -> !fir.ref<!fir.array<?xi8>>
358 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i8) -> !fir.ref<!fir.array<?xi8>>
359 ! FIR: %[[call:.*]] = fir.call @llvm.ppc.altivec.lvxl(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
360 ! FIR: %[[cnv:.*]] = fir.convert %[[call]] : (vector<4xi32>) -> !fir.vector<4:ui32>
361 ! FIR: fir.store %[[cnv]] to %arg2 : !fir.ref<!fir.vector<4:ui32>>
363 ! LLVMIR: %[[arg1:.*]] = load i8, ptr %0, align 1
364 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i8 %[[arg1]]
365 ! LLVMIR: %[[call:.*]] = call <4 x i32> @llvm.ppc.altivec.lvxl(ptr %[[addr]])
366 ! LLVMIR: store <4 x i32> %[[call]], ptr %2, align 16
367 end subroutine vec_ldl_testu32
369 ! CHECK-LABEL: @vec_ldl_testi32a
370 subroutine vec_ldl_testi32a(arg1, arg2, res)
371 integer(4) :: arg1
372 integer(4) :: arg2(10)
373 vector(integer(4)) :: res
374 res = vec_ldl(arg1, arg2)
376 ! FIR: %[[arg1:.*]] = fir.load %{{.*}} : !fir.ref<i32>
377 ! FIR: %[[arg2:.*]] = fir.convert %{{.*}} : (!fir.ref<!fir.array<10xi32>>) -> !fir.ref<!fir.array<?xi8>>
378 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
379 ! FIR: %[[call:.*]] = fir.call @llvm.ppc.altivec.lvxl(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
380 ! FIR: %[[cnv:.*]] = fir.convert %[[call]] : (vector<4xi32>) -> !fir.vector<4:i32>
381 ! FIR: fir.store %[[cnv]] to %arg2 : !fir.ref<!fir.vector<4:i32>>
383 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
384 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1]]
385 ! LLVMIR: %[[call:.*]] = call <4 x i32> @llvm.ppc.altivec.lvxl(ptr %[[addr]])
386 ! LLVMIR: store <4 x i32> %[[call]], ptr %2, align 16
387 end subroutine vec_ldl_testi32a
389 ! CHECK-LABEL: @vec_ldl_testf32av
390 subroutine vec_ldl_testf32av(arg1, arg2, res)
391 integer(8) :: arg1
392 vector(real(4)) :: arg2(2, 4, 8)
393 vector(real(4)) :: res
394 res = vec_ldl(arg1, arg2)
396 ! FIR: %[[arg1:.*]] = fir.load %{{.*}} : !fir.ref<i64>
397 ! FIR: %[[arg2:.*]] = fir.convert %{{.*}} : (!fir.ref<!fir.array<2x4x8x!fir.vector<4:f32>>>) -> !fir.ref<!fir.array<?xi8>>
398 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
399 ! FIR: %[[call:.*]] = fir.call @llvm.ppc.altivec.lvxl(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
400 ! FIR: %[[bc:.*]] = vector.bitcast %[[call]] : vector<4xi32> to vector<4xf32>
401 ! FIR: %[[cnv:.*]] = fir.convert %[[bc]] : (vector<4xf32>) -> !fir.vector<4:f32>
402 ! FIR: fir.store %[[cnv]] to %arg2 : !fir.ref<!fir.vector<4:f32>>
404 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
405 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[arg1]]
406 ! LLVMIR: %[[call:.*]] = call <4 x i32> @llvm.ppc.altivec.lvxl(ptr %[[addr]])
407 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[call]] to <4 x float>
408 ! LLVMIR: store <4 x float> %[[bc]], ptr %2, align 16
409 end subroutine vec_ldl_testf32av
411 ! CHECK-LABEL: @vec_ldl_testi32s
412 subroutine vec_ldl_testi32s(arg1, arg2, res)
413 integer(4) :: arg1
414 real(4) :: arg2
415 vector(real(4)) :: res
416 res = vec_ldl(arg1, arg2)
418 ! FIR: %[[arg1:.*]] = fir.load %{{.*}} : !fir.ref<i32>
419 ! FIR: %[[arg2:.*]] = fir.convert %{{.*}} : (!fir.ref<f32>) -> !fir.ref<!fir.array<?xi8>>
420 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
421 ! FIR: %[[call:.*]] = fir.call @llvm.ppc.altivec.lvxl(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
422 ! FIR: %[[bc:.*]] = vector.bitcast %[[call]] : vector<4xi32> to vector<4xf32>
423 ! FIR: %[[cnv:.*]] = fir.convert %[[bc]] : (vector<4xf32>) -> !fir.vector<4:f32>
424 ! FIR: fir.store %[[cnv]] to %arg2 : !fir.ref<!fir.vector<4:f32>>
426 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
427 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1]]
428 ! LLVMIR: %[[call:.*]] = call <4 x i32> @llvm.ppc.altivec.lvxl(ptr %[[addr]])
429 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[call]] to <4 x float>
430 ! LLVMIR: store <4 x float> %[[bc]], ptr %2, align 16
431 end subroutine vec_ldl_testi32s
433 !----------------------
434 ! vec_lvsl
435 !----------------------
437 ! CHECK-LABEL: @vec_lvsl_testi8s
438 subroutine vec_lvsl_testi8s(arg1, arg2, res)
439 integer(1) :: arg1
440 integer(1) :: arg2
441 vector(unsigned(1)) :: res
442 res = vec_lvsl(arg1, arg2)
444 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i8>
445 ! FIR: %[[arg1ext:.*]] = fir.convert %[[arg1]] : (i8) -> i64
446 ! FIR: %[[c56:.*]] = arith.constant 56 : i64
447 ! FIR: %[[lshft:.*]] = arith.shli %[[arg1ext]], %[[c56]] : i64
448 ! FIR: %[[rshft:.*]] = arith.shrsi %[[lshft]], %[[c56]] : i64
449 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<i8>) -> !fir.ref<!fir.array<?xi8>>
450 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[rshft]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
451 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvsl(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<16xi8>
452 ! FIR: %[[vundef:.*]] = fir.undefined vector<16xi8>
453 ! FIR: %[[sv:.*]] = vector.shuffle %[[ld]], %[[vundef]] [15, 14, 13, 12, 11, 10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0] : vector<16xi8>, vector<16xi8>
454 ! FIR: %[[res:.*]] = fir.convert %[[sv]] : (vector<16xi8>) -> !fir.vector<16:ui8>
455 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:ui8>>
457 ! LLVMIR: %[[arg1:.*]] = load i8, ptr %0, align 1
458 ! LLVMIR: %[[ext:.*]] = sext i8 %[[arg1]] to i64
459 ! LLVMIR: %[[lshft:.*]] = shl i64 %[[ext]], 56
460 ! LLVMIR: %[[rshft:.*]] = ashr i64 %[[lshft]], 56
461 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[rshft]]
462 ! LLVMIR: %[[ld:.*]] = call <16 x i8> @llvm.ppc.altivec.lvsl(ptr %[[addr]])
463 ! LLVMIR: %[[sv:.*]] = shufflevector <16 x i8> %[[ld]], <16 x i8> undef, <16 x i32> <i32 15, i32 14, i32 13, i32 12, i32 11, i32 10, i32 9, i32 8, i32 7, i32 6, i32 5, i32 4, i32 3, i32 2, i32 1, i32 0>
464 ! LLVMIR: store <16 x i8> %[[sv]], ptr %2, align 16
465 end subroutine vec_lvsl_testi8s
467 ! CHECK-LABEL: @vec_lvsl_testi16a
468 subroutine vec_lvsl_testi16a(arg1, arg2, res)
469 integer(2) :: arg1
470 integer(2) :: arg2(4)
471 vector(unsigned(1)) :: res
472 res = vec_lvsl(arg1, arg2)
474 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
475 ! FIR: %[[arg1ext:.*]] = fir.convert %[[arg1]] : (i16) -> i64
476 ! FIR: %[[c56:.*]] = arith.constant 56 : i64
477 ! FIR: %[[lshft:.*]] = arith.shli %[[arg1ext]], %[[c56]] : i64
478 ! FIR: %[[rshft:.*]] = arith.shrsi %[[lshft]], %[[c56]] : i64
479 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4xi16>>) -> !fir.ref<!fir.array<?xi8>>
480 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[rshft]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
481 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvsl(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<16xi8>
482 ! FIR: %[[vundef:.*]] = fir.undefined vector<16xi8>
483 ! FIR: %[[sv:.*]] = vector.shuffle %[[ld]], %[[vundef]] [15, 14, 13, 12, 11, 10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0] : vector<16xi8>, vector<16xi8>
484 ! FIR: %[[res:.*]] = fir.convert %[[sv]] : (vector<16xi8>) -> !fir.vector<16:ui8>
485 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:ui8>>
487 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
488 ! LLVMIR: %[[ext:.*]] = sext i16 %[[arg1]] to i64
489 ! LLVMIR: %[[lshft:.*]] = shl i64 %[[ext]], 56
490 ! LLVMIR: %[[rshft:.*]] = ashr i64 %[[lshft]], 56
491 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[rshft]]
492 ! LLVMIR: %[[ld:.*]] = call <16 x i8> @llvm.ppc.altivec.lvsl(ptr %[[addr]])
493 ! LLVMIR: %[[sv:.*]] = shufflevector <16 x i8> %[[ld]], <16 x i8> undef, <16 x i32> <i32 15, i32 14, i32 13, i32 12, i32 11, i32 10, i32 9, i32 8, i32 7, i32 6, i32 5, i32 4, i32 3, i32 2, i32 1, i32 0>
494 ! LLVMIR: store <16 x i8> %[[sv]], ptr %2, align 16
495 end subroutine vec_lvsl_testi16a
497 ! CHECK-LABEL: @vec_lvsl_testi32a
498 subroutine vec_lvsl_testi32a(arg1, arg2, res)
499 integer(4) :: arg1
500 integer(4) :: arg2(2, 3, 4)
501 vector(unsigned(1)) :: res
502 res = vec_lvsl(arg1, arg2)
504 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i32>
505 ! FIR: %[[arg1ext:.*]] = fir.convert %[[arg1]] : (i32) -> i64
506 ! FIR: %[[c56:.*]] = arith.constant 56 : i64
507 ! FIR: %[[lshft:.*]] = arith.shli %[[arg1ext]], %[[c56]] : i64
508 ! FIR: %[[rshft:.*]] = arith.shrsi %[[lshft]], %[[c56]] : i64
509 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x3x4xi32>>) -> !fir.ref<!fir.array<?xi8>>
510 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[rshft]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
511 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvsl(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<16xi8>
512 ! FIR: %[[vundef:.*]] = fir.undefined vector<16xi8>
513 ! FIR: %[[sv:.*]] = vector.shuffle %[[ld]], %[[vundef]] [15, 14, 13, 12, 11, 10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0] : vector<16xi8>, vector<16xi8>
514 ! FIR: %[[res:.*]] = fir.convert %[[sv]] : (vector<16xi8>) -> !fir.vector<16:ui8>
515 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:ui8>>
517 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
518 ! LLVMIR: %[[ext:.*]] = sext i32 %[[arg1]] to i64
519 ! LLVMIR: %[[lshft:.*]] = shl i64 %[[ext]], 56
520 ! LLVMIR: %[[rshft:.*]] = ashr i64 %[[lshft]], 56
521 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[rshft]]
522 ! LLVMIR: %[[ld:.*]] = call <16 x i8> @llvm.ppc.altivec.lvsl(ptr %[[addr]])
523 ! LLVMIR: %[[sv:.*]] = shufflevector <16 x i8> %[[ld]], <16 x i8> undef, <16 x i32> <i32 15, i32 14, i32 13, i32 12, i32 11, i32 10, i32 9, i32 8, i32 7, i32 6, i32 5, i32 4, i32 3, i32 2, i32 1, i32 0>
524 ! LLVMIR: store <16 x i8> %[[sv]], ptr %2, align 16
525 end subroutine vec_lvsl_testi32a
527 ! CHECK-LABEL: @vec_lvsl_testf32a
528 subroutine vec_lvsl_testf32a(arg1, arg2, res)
529 integer(8) :: arg1
530 real(4) :: arg2(4)
531 vector(unsigned(1)) :: res
532 res = vec_lvsl(arg1, arg2)
534 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
535 ! FIR: %[[c56:.*]] = arith.constant 56 : i64
536 ! FIR: %[[lshft:.*]] = arith.shli %[[arg1]], %[[c56]] : i64
537 ! FIR: %[[rshft:.*]] = arith.shrsi %[[lshft]], %[[c56]] : i64
538 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4xf32>>) -> !fir.ref<!fir.array<?xi8>>
539 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[rshft]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
540 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvsl(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<16xi8>
541 ! FIR: %[[vundef:.*]] = fir.undefined vector<16xi8>
542 ! FIR: %[[sv:.*]] = vector.shuffle %[[ld]], %[[vundef]] [15, 14, 13, 12, 11, 10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0] : vector<16xi8>, vector<16xi8>
543 ! FIR: %[[res:.*]] = fir.convert %[[sv]] : (vector<16xi8>) -> !fir.vector<16:ui8>
544 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:ui8>>
546 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
547 ! LLVMIR: %[[lshft:.*]] = shl i64 %[[arg1]], 56
548 ! LLVMIR: %[[rshft:.*]] = ashr i64 %[[lshft]], 56
549 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[rshft]]
550 ! LLVMIR: %[[ld:.*]] = call <16 x i8> @llvm.ppc.altivec.lvsl(ptr %[[addr]])
551 ! LLVMIR: %[[sv:.*]] = shufflevector <16 x i8> %[[ld]], <16 x i8> undef, <16 x i32> <i32 15, i32 14, i32 13, i32 12, i32 11, i32 10, i32 9, i32 8, i32 7, i32 6, i32 5, i32 4, i32 3, i32 2, i32 1, i32 0>
552 ! LLVMIR: store <16 x i8> %[[sv]], ptr %2, align 16
553 end subroutine vec_lvsl_testf32a
555 !----------------------
556 ! vec_lvsr
557 !----------------------
559 ! CHECK-LABEL: @vec_lvsr_testi8s
560 subroutine vec_lvsr_testi8s(arg1, arg2, res)
561 integer(1) :: arg1
562 integer(1) :: arg2
563 vector(unsigned(1)) :: res
564 res = vec_lvsr(arg1, arg2)
566 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i8>
567 ! FIR: %[[arg1ext:.*]] = fir.convert %[[arg1]] : (i8) -> i64
568 ! FIR: %[[c56:.*]] = arith.constant 56 : i64
569 ! FIR: %[[lshft:.*]] = arith.shli %[[arg1ext]], %[[c56]] : i64
570 ! FIR: %[[rshft:.*]] = arith.shrsi %[[lshft]], %[[c56]] : i64
571 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<i8>) -> !fir.ref<!fir.array<?xi8>>
572 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[rshft]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
573 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvsr(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<16xi8>
574 ! FIR: %[[vundef:.*]] = fir.undefined vector<16xi8>
575 ! FIR: %[[sv:.*]] = vector.shuffle %[[ld]], %[[vundef]] [15, 14, 13, 12, 11, 10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0] : vector<16xi8>, vector<16xi8>
576 ! FIR: %[[res:.*]] = fir.convert %[[sv]] : (vector<16xi8>) -> !fir.vector<16:ui8>
577 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:ui8>>
579 ! LLVMIR: %[[arg1:.*]] = load i8, ptr %0, align 1
580 ! LLVMIR: %[[ext:.*]] = sext i8 %[[arg1]] to i64
581 ! LLVMIR: %[[lshft:.*]] = shl i64 %[[ext]], 56
582 ! LLVMIR: %[[rshft:.*]] = ashr i64 %[[lshft]], 56
583 ! LLVMIR: %[[ld:.*]] = getelementptr i8, ptr %1, i64 %[[rshft]]
584 ! LLVMIR: %[[addr:.*]] = call <16 x i8> @llvm.ppc.altivec.lvsr(ptr %[[ld]])
585 ! LLVMIR: %[[sv:.*]] = shufflevector <16 x i8> %[[addr]], <16 x i8> undef, <16 x i32> <i32 15, i32 14, i32 13, i32 12, i32 11, i32 10, i32 9, i32 8, i32 7, i32 6, i32 5, i32 4, i32 3, i32 2, i32 1, i32 0>
586 ! LLVMIR: store <16 x i8> %[[sv]], ptr %2, align 16
587 end subroutine vec_lvsr_testi8s
589 ! CHECK-LABEL: @vec_lvsr_testi16a
590 subroutine vec_lvsr_testi16a(arg1, arg2, res)
591 integer(2) :: arg1
592 integer(2) :: arg2(4)
593 vector(unsigned(1)) :: res
594 res = vec_lvsr(arg1, arg2)
596 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
597 ! FIR: %[[arg1ext:.*]] = fir.convert %[[arg1]] : (i16) -> i64
598 ! FIR: %[[c56:.*]] = arith.constant 56 : i64
599 ! FIR: %[[lshft:.*]] = arith.shli %[[arg1ext]], %[[c56]] : i64
600 ! FIR: %[[rshft:.*]] = arith.shrsi %[[lshft]], %[[c56]] : i64
601 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4xi16>>) -> !fir.ref<!fir.array<?xi8>>
602 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[rshft]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
603 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvsr(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<16xi8>
604 ! FIR: %[[vundef:.*]] = fir.undefined vector<16xi8>
605 ! FIR: %[[sv:.*]] = vector.shuffle %[[ld]], %[[vundef]] [15, 14, 13, 12, 11, 10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0] : vector<16xi8>, vector<16xi8>
606 ! FIR: %[[res:.*]] = fir.convert %[[sv]] : (vector<16xi8>) -> !fir.vector<16:ui8>
607 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:ui8>>
609 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
610 ! LLVMIR: %[[ext:.*]] = sext i16 %[[arg1]] to i64
611 ! LLVMIR: %[[lshft:.*]] = shl i64 %[[ext]], 56
612 ! LLVMIR: %[[rshft:.*]] = ashr i64 %[[lshft]], 56
613 ! LLVMIR: %[[ld:.*]] = getelementptr i8, ptr %1, i64 %[[rshft]]
614 ! LLVMIR: %[[addr:.*]] = call <16 x i8> @llvm.ppc.altivec.lvsr(ptr %[[ld]])
615 ! LLVMIR: %[[sv:.*]] = shufflevector <16 x i8> %[[addr]], <16 x i8> undef, <16 x i32> <i32 15, i32 14, i32 13, i32 12, i32 11, i32 10, i32 9, i32 8, i32 7, i32 6, i32 5, i32 4, i32 3, i32 2, i32 1, i32 0>
616 ! LLVMIR: store <16 x i8> %[[sv]], ptr %2, align 16
617 end subroutine vec_lvsr_testi16a
619 ! CHECK-LABEL: @vec_lvsr_testi32a
620 subroutine vec_lvsr_testi32a(arg1, arg2, res)
621 integer(4) :: arg1
622 integer(4) :: arg2(2, 3, 4)
623 vector(unsigned(1)) :: res
624 res = vec_lvsr(arg1, arg2)
626 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i32>
627 ! FIR: %[[arg1ext:.*]] = fir.convert %[[arg1]] : (i32) -> i64
628 ! FIR: %[[c56:.*]] = arith.constant 56 : i64
629 ! FIR: %[[lshft:.*]] = arith.shli %[[arg1ext]], %[[c56]] : i64
630 ! FIR: %[[rshft:.*]] = arith.shrsi %[[lshft]], %[[c56]] : i64
631 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x3x4xi32>>) -> !fir.ref<!fir.array<?xi8>>
632 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[rshft]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
633 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvsr(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<16xi8>
634 ! FIR: %[[vundef:.*]] = fir.undefined vector<16xi8>
635 ! FIR: %[[sv:.*]] = vector.shuffle %[[ld]], %[[vundef]] [15, 14, 13, 12, 11, 10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0] : vector<16xi8>, vector<16xi8>
636 ! FIR: %[[res:.*]] = fir.convert %[[sv]] : (vector<16xi8>) -> !fir.vector<16:ui8>
637 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:ui8>>
639 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
640 ! LLVMIR: %[[ext:.*]] = sext i32 %[[arg1]] to i64
641 ! LLVMIR: %[[lshft:.*]] = shl i64 %[[ext]], 56
642 ! LLVMIR: %[[rshft:.*]] = ashr i64 %[[lshft]], 56
643 ! LLVMIR: %[[ld:.*]] = getelementptr i8, ptr %1, i64 %[[rshft]]
644 ! LLVMIR: %[[addr:.*]] = call <16 x i8> @llvm.ppc.altivec.lvsr(ptr %[[ld]])
645 ! LLVMIR: %[[sv:.*]] = shufflevector <16 x i8> %[[addr]], <16 x i8> undef, <16 x i32> <i32 15, i32 14, i32 13, i32 12, i32 11, i32 10, i32 9, i32 8, i32 7, i32 6, i32 5, i32 4, i32 3, i32 2, i32 1, i32 0>
646 ! LLVMIR: store <16 x i8> %[[sv]], ptr %2, align 16
647 end subroutine vec_lvsr_testi32a
649 ! CHECK-LABEL: @vec_lvsr_testf32a
650 subroutine vec_lvsr_testf32a(arg1, arg2, res)
651 integer(8) :: arg1
652 real(4) :: arg2(4)
653 vector(unsigned(1)) :: res
654 res = vec_lvsr(arg1, arg2)
656 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
657 ! FIR: %[[c56:.*]] = arith.constant 56 : i64
658 ! FIR: %[[lshft:.*]] = arith.shli %[[arg1]], %[[c56]] : i64
659 ! FIR: %[[rshft:.*]] = arith.shrsi %[[lshft]], %[[c56]] : i64
660 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4xf32>>) -> !fir.ref<!fir.array<?xi8>>
661 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[rshft]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
662 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvsr(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<16xi8>
663 ! FIR: %[[vundef:.*]] = fir.undefined vector<16xi8>
664 ! FIR: %[[sv:.*]] = vector.shuffle %[[ld]], %[[vundef]] [15, 14, 13, 12, 11, 10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0] : vector<16xi8>, vector<16xi8>
665 ! FIR: %[[res:.*]] = fir.convert %[[sv]] : (vector<16xi8>) -> !fir.vector<16:ui8>
666 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:ui8>>
668 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
669 ! LLVMIR: %[[lshft:.*]] = shl i64 %[[arg1]], 56
670 ! LLVMIR: %[[rshft:.*]] = ashr i64 %[[lshft]], 56
671 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[rshft]]
672 ! LLVMIR: %[[ld:.*]] = call <16 x i8> @llvm.ppc.altivec.lvsr(ptr %[[addr]])
673 ! LLVMIR: %[[sv:.*]] = shufflevector <16 x i8> %[[ld]], <16 x i8> undef, <16 x i32> <i32 15, i32 14, i32 13, i32 12, i32 11, i32 10, i32 9, i32 8, i32 7, i32 6, i32 5, i32 4, i32 3, i32 2, i32 1, i32 0>
674 ! LLVMIR: store <16 x i8> %[[sv]], ptr %2, align 16
675 end subroutine vec_lvsr_testf32a
677 !----------------------
678 ! vec_lxv
679 !----------------------
681 ! CHECK-LABEL: @vec_lxv_testi8a
682 subroutine vec_lxv_testi8a(arg1, arg2, res)
683 integer(1) :: arg1
684 integer(1) :: arg2(4)
685 vector(integer(1)) :: res
686 res = vec_lxv(arg1, arg2)
688 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i8>
689 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4xi8>>) -> !fir.ref<!fir.array<?xi8>>
690 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i8) -> !fir.ref<!fir.array<?xi8>>
691 ! FIR: %[[ld:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
692 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<16xi8>) -> !fir.vector<16:i8>
693 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:i8>>
695 ! LLVMIR_P9: %[[arg1:.*]] = load i8, ptr %0, align 1
696 ! LLVMIR_P9: %[[addr:.*]] = getelementptr i8, ptr %1, i8 %[[arg1]]
697 ! LLVMIR_P9: %[[ld:.*]] = load <16 x i8>, ptr %[[addr]], align 1
698 ! LLVMIR_P9: store <16 x i8> %[[ld]], ptr %2, align 16
699 end subroutine vec_lxv_testi8a
701 ! CHECK-LABEL: @vec_lxv_testi16a
702 subroutine vec_lxv_testi16a(arg1, arg2, res)
703 integer(2) :: arg1
704 integer(2) :: arg2(2, 4, 8)
705 vector(integer(2)) :: res
706 res = vec_lxv(arg1, arg2)
708 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
709 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x4x8xi16>>) -> !fir.ref<!fir.array<?xi8>>
710 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
711 ! FIR: %[[ld:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
712 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<8xi16>) -> !fir.vector<8:i16>
713 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<8:i16>>
715 ! LLVMIR_P9: %[[arg1:.*]] = load i16, ptr %0, align 2
716 ! LLVMIR_P9: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[arg1]]
717 ! LLVMIR_P9: %[[ld:.*]] = load <8 x i16>, ptr %[[addr]], align 1
718 ! LLVMIR_P9: store <8 x i16> %[[ld]], ptr %2, align 16
719 end subroutine vec_lxv_testi16a
721 ! CHECK-LABEL: @vec_lxv_testi32a
722 subroutine vec_lxv_testi32a(arg1, arg2, res)
723 integer(4) :: arg1
724 integer(4) :: arg2(2, 4, 8)
725 vector(integer(4)) :: res
726 res = vec_lxv(arg1, arg2)
728 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i32>
729 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x4x8xi32>>) -> !fir.ref<!fir.array<?xi8>>
730 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
731 ! FIR: %[[ld:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
732 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<4xi32>) -> !fir.vector<4:i32>
733 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:i32>>
735 ! LLVMIR_P9: %[[arg1:.*]] = load i32, ptr %0, align 4
736 ! LLVMIR_P9: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1]]
737 ! LLVMIR_P9: %[[ld:.*]] = load <4 x i32>, ptr %[[addr]], align 1
738 ! LLVMIR_P9: store <4 x i32> %[[ld]], ptr %2, align 16
739 end subroutine vec_lxv_testi32a
741 ! CHECK-LABEL: @vec_lxv_testf32a
742 subroutine vec_lxv_testf32a(arg1, arg2, res)
743 integer(2) :: arg1
744 real(4) :: arg2(4)
745 vector(real(4)) :: res
746 res = vec_lxv(arg1, arg2)
748 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
749 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4xf32>>) -> !fir.ref<!fir.array<?xi8>>
750 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
751 ! FIR: %[[ld:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
752 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<4xf32>) -> !fir.vector<4:f32>
753 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:f32>>
755 ! LLVMIR_P9: %[[arg1:.*]] = load i16, ptr %0, align 2
756 ! LLVMIR_P9: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[arg1]]
757 ! LLVMIR_P9: %[[ld:.*]] = load <4 x float>, ptr %[[addr]], align 1
758 ! LLVMIR_P9: store <4 x float> %[[ld]], ptr %2, align 16
759 end subroutine vec_lxv_testf32a
761 ! CHECK-LABEL: @vec_lxv_testf64a
762 subroutine vec_lxv_testf64a(arg1, arg2, res)
763 integer(8) :: arg1
764 real(8) :: arg2(4)
765 vector(real(8)) :: res
766 res = vec_lxv(arg1, arg2)
768 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
769 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4xf64>>) -> !fir.ref<!fir.array<?xi8>>
770 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
771 ! FIR: %[[ld:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
772 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<2xf64>) -> !fir.vector<2:f64>
773 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<2:f64>>
775 ! LLVMIR_P9: %[[arg1:.*]] = load i64, ptr %0, align 8
776 ! LLVMIR_P9: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[arg1]]
777 ! LLVMIR_P9: %[[ld:.*]] = load <2 x double>, ptr %[[addr]], align 1
778 ! LLVMIR_P9: store <2 x double> %[[ld]], ptr %2, align 16
779 end subroutine vec_lxv_testf64a
781 !----------------------
782 ! vec_xld2
783 !----------------------
785 ! CHECK-LABEL: @vec_xld2_testi8a
786 subroutine vec_xld2_testi8a(arg1, arg2, res)
787 integer(1) :: arg1
788 vector(integer(1)) :: arg2(4)
789 vector(integer(1)) :: res
790 res = vec_xld2(arg1, arg2)
792 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i8>
793 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4x!fir.vector<16:i8>>>) -> !fir.ref<!fir.array<?xi8>>
794 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i8) -> !fir.ref<!fir.array<?xi8>>
795 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvd2x(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<2xf64>
796 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<2xf64> to vector<16xi8>
797 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<16xi8>) -> !fir.vector<16:i8>
798 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:i8>>
800 ! LLVMIR: %[[arg1:.*]] = load i8, ptr %0, align 1
801 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i8 %[[arg1]]
802 ! LLVMIR: %[[ld:.*]] = call contract <2 x double> @llvm.ppc.vsx.lxvd2x(ptr %[[addr]])
803 ! LLVMIR: %[[bc:.*]] = bitcast <2 x double> %[[ld]] to <16 x i8>
804 ! LLVMIR: store <16 x i8> %[[bc]], ptr %2, align 16
805 end subroutine vec_xld2_testi8a
807 ! CHECK-LABEL: @vec_xld2_testi16
808 subroutine vec_xld2_testi16(arg1, arg2, res)
809 integer :: arg1
810 vector(integer(2)) :: arg2
811 vector(integer(2)) :: res
812 res = vec_xld2(arg1, arg2)
814 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i32>
815 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.vector<8:i16>>) -> !fir.ref<!fir.array<?xi8>>
816 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
817 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvd2x(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<2xf64>
818 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<2xf64> to vector<8xi16>
819 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<8xi16>) -> !fir.vector<8:i16>
820 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<8:i16>>
822 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
823 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1]]
824 ! LLVMIR: %[[ld:.*]] = call contract <2 x double> @llvm.ppc.vsx.lxvd2x(ptr %[[addr]])
825 ! LLVMIR: %[[bc:.*]] = bitcast <2 x double> %[[ld]] to <8 x i16>
826 ! LLVMIR: store <8 x i16> %[[bc]], ptr %2, align 16
827 end subroutine vec_xld2_testi16
829 ! CHECK-LABEL: @vec_xld2_testi32a
830 subroutine vec_xld2_testi32a(arg1, arg2, res)
831 integer(4) :: arg1
832 vector(integer(4)) :: arg2(41)
833 vector(integer(4)) :: res
834 res = vec_xld2(arg1, arg2)
836 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i32>
837 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<41x!fir.vector<4:i32>>>) -> !fir.ref<!fir.array<?xi8>>
838 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
839 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvd2x(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<2xf64>
840 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<2xf64> to vector<4xi32>
841 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<4xi32>) -> !fir.vector<4:i32>
842 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:i32>>
844 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
845 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1]]
846 ! LLVMIR: %[[ld:.*]] = call contract <2 x double> @llvm.ppc.vsx.lxvd2x(ptr %[[addr]])
847 ! LLVMIR: %[[bc:.*]] = bitcast <2 x double> %[[ld]] to <4 x i32>
848 ! LLVMIR: store <4 x i32> %[[bc]], ptr %2, align 16
849 end subroutine vec_xld2_testi32a
851 ! CHECK-LABEL: @vec_xld2_testi64a
852 subroutine vec_xld2_testi64a(arg1, arg2, res)
853 integer(8) :: arg1
854 vector(integer(8)) :: arg2(4)
855 vector(integer(8)) :: res
856 res = vec_xld2(arg1, arg2)
858 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
859 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4x!fir.vector<2:i64>>>) -> !fir.ref<!fir.array<?xi8>>
860 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
861 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvd2x(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<2xf64>
862 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<2xf64> to vector<2xi64>
863 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<2xi64>) -> !fir.vector<2:i64>
864 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<2:i64>>
866 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
867 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[arg1]]
868 ! LLVMIR: %[[ld:.*]] = call contract <2 x double> @llvm.ppc.vsx.lxvd2x(ptr %[[addr]])
869 ! LLVMIR: %[[bc:.*]] = bitcast <2 x double> %[[ld]] to <2 x i64>
870 ! LLVMIR: store <2 x i64> %[[bc]], ptr %2, align 16
871 end subroutine vec_xld2_testi64a
873 ! CHECK-LABEL: @vec_xld2_testf32a
874 subroutine vec_xld2_testf32a(arg1, arg2, res)
875 integer(2) :: arg1
876 vector(real(4)) :: arg2(4)
877 vector(real(4)) :: res
878 res = vec_xld2(arg1, arg2)
880 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
881 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4x!fir.vector<4:f32>>>) -> !fir.ref<!fir.array<?xi8>>
882 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
883 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvd2x(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<2xf64>
884 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<2xf64> to vector<4xf32>
885 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<4xf32>) -> !fir.vector<4:f32>
886 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:f32>>
888 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
889 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[arg1]]
890 ! LLVMIR: %[[ld:.*]] = call contract <2 x double> @llvm.ppc.vsx.lxvd2x(ptr %[[addr]])
891 ! LLVMIR: %[[bc:.*]] = bitcast <2 x double> %[[ld]] to <4 x float>
892 ! LLVMIR: store <4 x float> %[[bc]], ptr %2, align 16
893 end subroutine vec_xld2_testf32a
895 ! CHECK-LABEL: @vec_xld2_testf64a
896 subroutine vec_xld2_testf64a(arg1, arg2, res)
897 integer(8) :: arg1
898 vector(real(8)) :: arg2(4)
899 vector(real(8)) :: res
900 res = vec_xld2(arg1, arg2)
902 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
903 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4x!fir.vector<2:f64>>>) -> !fir.ref<!fir.array<?xi8>>
904 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
905 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvd2x(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<2xf64>
906 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<2xf64>) -> !fir.vector<2:f64>
907 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<2:f64>>
909 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
910 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[arg1]]
911 ! LLVMIR: %[[ld:.*]] = call contract <2 x double> @llvm.ppc.vsx.lxvd2x(ptr %[[addr]])
912 ! LLVMIR: store <2 x double> %[[ld]], ptr %2, align 16
913 end subroutine vec_xld2_testf64a
915 !----------------------
916 ! vec_xl
917 !----------------------
919 ! CHECK-LABEL: @vec_xl_testi8a
920 subroutine vec_xl_testi8a(arg1, arg2, res)
921 integer(1) :: arg1
922 integer(1) :: arg2(4)
923 vector(integer(1)) :: res
924 res = vec_xl(arg1, arg2)
926 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i8>
927 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4xi8>>) -> !fir.ref<!fir.array<?xi8>>
928 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i8) -> !fir.ref<!fir.array<?xi8>>
929 ! FIR: %[[ld:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
930 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<16xi8>) -> !fir.vector<16:i8>
931 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:i8>>
933 ! LLVMIR: %[[arg1:.*]] = load i8, ptr %0, align 1
934 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i8 %[[arg1]]
935 ! LLVMIR: %[[ld:.*]] = load <16 x i8>, ptr %[[addr]], align 1
936 ! LLVMIR: store <16 x i8> %[[ld]], ptr %2, align 16
937 end subroutine vec_xl_testi8a
939 ! CHECK-LABEL: @vec_xl_testi16a
940 subroutine vec_xl_testi16a(arg1, arg2, res)
941 integer(2) :: arg1
942 integer(2) :: arg2(2, 4, 8)
943 vector(integer(2)) :: res
944 res = vec_xl(arg1, arg2)
946 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
947 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x4x8xi16>>) -> !fir.ref<!fir.array<?xi8>>
948 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
949 ! FIR: %[[ld:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
950 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<8xi16>) -> !fir.vector<8:i16>
951 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<8:i16>>
953 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
954 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[arg1]]
955 ! LLVMIR: %[[ld:.*]] = load <8 x i16>, ptr %[[addr]], align 1
956 ! LLVMIR: store <8 x i16> %[[ld]], ptr %2, align 16
957 end subroutine vec_xl_testi16a
959 ! CHECK-LABEL: @vec_xl_testi32a
960 subroutine vec_xl_testi32a(arg1, arg2, res)
961 integer(4) :: arg1
962 integer(4) :: arg2(2, 4, 8)
963 vector(integer(4)) :: res
964 res = vec_xl(arg1, arg2)
966 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i32>
967 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x4x8xi32>>) -> !fir.ref<!fir.array<?xi8>>
968 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
969 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvw4x(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
970 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<4xi32>) -> !fir.vector<4:i32>
971 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:i32>>
973 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
974 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1]]
975 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.vsx.lxvw4x(ptr %[[addr]])
976 ! LLVMIR: store <4 x i32> %[[ld]], ptr %2, align 16
977 end subroutine vec_xl_testi32a
979 ! CHECK-LABEL: @vec_xl_testi64a
980 subroutine vec_xl_testi64a(arg1, arg2, res)
981 integer(8) :: arg1
982 integer(8) :: arg2(2, 4, 8)
983 vector(integer(8)) :: res
984 res = vec_xl(arg1, arg2)
986 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
987 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x4x8xi64>>) -> !fir.ref<!fir.array<?xi8>>
988 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
989 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvd2x(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<2xf64>
990 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<2xf64> to vector<2xi64>
991 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<2xi64>) -> !fir.vector<2:i64>
992 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<2:i64>>
994 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
995 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[arg1]]
996 ! LLVMIR: %[[ld:.*]] = call contract <2 x double> @llvm.ppc.vsx.lxvd2x(ptr %[[addr]])
997 ! LLVMIR: %[[bc:.*]] = bitcast <2 x double> %[[ld]] to <2 x i64>
998 ! LLVMIR: store <2 x i64> %[[bc]], ptr %2, align 16
999 end subroutine vec_xl_testi64a
1001 ! CHECK-LABEL: @vec_xl_testf32a
1002 subroutine vec_xl_testf32a(arg1, arg2, res)
1003 integer(2) :: arg1
1004 real(4) :: arg2(4)
1005 vector(real(4)) :: res
1006 res = vec_xl(arg1, arg2)
1008 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
1009 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4xf32>>) -> !fir.ref<!fir.array<?xi8>>
1010 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
1011 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvw4x(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
1012 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<4xi32> to vector<4xf32>
1013 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<4xf32>) -> !fir.vector<4:f32>
1014 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:f32>>
1016 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
1017 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[arg1]]
1018 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.vsx.lxvw4x(ptr %[[addr]])
1019 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[ld]] to <4 x float>
1020 ! LLVMIR: store <4 x float> %[[bc]], ptr %2, align 16
1021 end subroutine vec_xl_testf32a
1023 ! CHECK-LABEL: @vec_xl_testf64a
1024 subroutine vec_xl_testf64a(arg1, arg2, res)
1025 integer(8) :: arg1
1026 real(8) :: arg2
1027 vector(real(8)) :: res
1028 res = vec_xl(arg1, arg2)
1030 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
1031 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<f64>) -> !fir.ref<!fir.array<?xi8>>
1032 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
1033 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvd2x(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<2xf64>
1034 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<2xf64>) -> !fir.vector<2:f64>
1035 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<2:f64>>
1037 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
1038 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[arg1]]
1039 ! LLVMIR: %[[ld:.*]] = call contract <2 x double> @llvm.ppc.vsx.lxvd2x(ptr %[[addr]])
1040 ! LLVMIR: store <2 x double> %[[ld]], ptr %2, align 16
1041 end subroutine vec_xl_testf64a
1043 !----------------------
1044 ! vec_xlds
1045 !----------------------
1047 ! CHECK-LABEL: @vec_xlds_testi64a
1048 subroutine vec_xlds_testi64a(arg1, arg2, res)
1049 integer(8) :: arg1
1050 vector(integer(8)) :: arg2(4)
1051 vector(integer(8)) :: res
1052 res = vec_xlds(arg1, arg2)
1054 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
1055 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4x!fir.vector<2:i64>>>) -> !fir.ref<!fir.array<?xi8>>
1056 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
1057 ! FIR: %[[cnv:.*]] = fir.convert %[[addr]] : (!fir.ref<!fir.array<?xi8>>) -> !fir.ref<i64>
1058 ! FIR: %[[ld:.*]] = fir.load %[[cnv]] : !fir.ref<i64>
1059 ! FIR: %[[vsplt:.*]] = vector.splat %[[ld]] : vector<2xi64>
1060 ! FIR: %[[res:.*]] = fir.convert %[[vsplt]] : (vector<2xi64>) -> !fir.vector<2:i64>
1061 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<2:i64>>
1063 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
1064 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[arg1]]
1065 ! LLVMIR: %[[ld:.*]] = load i64, ptr %[[addr]], align 8
1066 ! LLVMIR: %[[insrt:.*]] = insertelement <2 x i64> undef, i64 %[[ld]], i32 0
1067 ! LLVMIR: %[[shfl:.*]] = shufflevector <2 x i64> %[[insrt]], <2 x i64> undef, <2 x i32> zeroinitializer
1068 ! LLVMIR: store <2 x i64> %[[shfl]], ptr %2, align 16
1069 end subroutine vec_xlds_testi64a
1071 ! CHECK-LABEL: @vec_xlds_testf64a
1072 subroutine vec_xlds_testf64a(arg1, arg2, res)
1073 integer(8) :: arg1
1074 vector(real(8)) :: arg2(4)
1075 vector(real(8)) :: res
1076 res = vec_xlds(arg1, arg2)
1078 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
1079 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4x!fir.vector<2:f64>>>) -> !fir.ref<!fir.array<?xi8>>
1080 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
1081 ! FIR: %[[cnv:.*]] = fir.convert %[[addr]] : (!fir.ref<!fir.array<?xi8>>) -> !fir.ref<i64>
1082 ! FIR: %[[ld:.*]] = fir.load %[[cnv]] : !fir.ref<i64>
1083 ! FIR: %[[vsplt:.*]] = vector.splat %[[ld]] : vector<2xi64>
1084 ! FIR: %[[bc:.*]] = vector.bitcast %[[vsplt]] : vector<2xi64> to vector<2xf64>
1085 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<2xf64>) -> !fir.vector<2:f64>
1086 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<2:f64>>
1088 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
1089 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[arg1]]
1090 ! LLVMIR: %[[ld:.*]] = load i64, ptr %[[addr]], align 8
1091 ! LLVMIR: %[[insrt:.*]] = insertelement <2 x i64> undef, i64 %[[ld]], i32 0
1092 ! LLVMIR: %[[shfl:.*]] = shufflevector <2 x i64> %[[insrt]], <2 x i64> undef, <2 x i32> zeroinitializer
1093 ! LLVMIR: %[[bc:.*]] = bitcast <2 x i64> %[[shfl]] to <2 x double>
1094 ! LLVMIR: store <2 x double> %[[bc]], ptr %2, align 16
1095 end subroutine vec_xlds_testf64a
1097 !----------------------
1098 ! vec_xl_be
1099 !----------------------
1101 ! CHECK-LABEL: @vec_xl_be_testi8a
1102 subroutine vec_xl_be_testi8a(arg1, arg2, res)
1103 integer(1) :: arg1
1104 integer(1) :: arg2(2, 4, 8)
1105 vector(integer(1)) :: res
1106 res = vec_xl_be(arg1, arg2)
1108 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i8>
1109 ! FIR: %[[uarr:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x4x8xi8>>) -> !fir.ref<!fir.array<?xi8>>
1110 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[uarr]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i8) -> !fir.ref<!fir.array<?xi8>>
1111 ! FIR: %[[ld:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
1112 ! FIR: %[[uv:.*]] = fir.undefined vector<16xi8>
1113 ! FIR: %[[shff:.*]] = vector.shuffle %[[ld]], %[[uv]] [15, 14, 13, 12, 11, 10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0] : vector<16xi8>, vector<16xi8>
1114 ! FIR: %[[res:.*]] = fir.convert %[[shff]] : (vector<16xi8>) -> !fir.vector<16:i8>
1115 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:i8>>
1117 ! LLVMIR: %[[arg1:.*]] = load i8, ptr %0, align 1
1118 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i8 %[[arg1]]
1119 ! LLVMIR: %[[ld:.*]] = load <16 x i8>, ptr %[[addr]], align 1
1120 ! LLVMIR: %[[shff:.*]] = shufflevector <16 x i8> %[[ld]], <16 x i8> undef, <16 x i32> <i32 15, i32 14, i32 13, i32 12, i32 11, i32 10, i32 9, i32 8, i32 7, i32 6, i32 5, i32 4, i32 3, i32 2, i32 1, i32 0>
1121 ! LLVMIR: store <16 x i8> %[[shff]], ptr %2, align 16
1122 end subroutine vec_xl_be_testi8a
1124 ! CHECK-LABEL: @vec_xl_be_testi16a
1125 subroutine vec_xl_be_testi16a(arg1, arg2, res)
1126 integer(2) :: arg1
1127 integer(2) :: arg2(2, 4, 8)
1128 vector(integer(2)) :: res
1129 res = vec_xl_be(arg1, arg2)
1131 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
1132 ! FIR: %[[uarr:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x4x8xi16>>) -> !fir.ref<!fir.array<?xi8>>
1133 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[uarr]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
1134 ! FIR: %[[ld:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
1135 ! FIR: %[[uv:.*]] = fir.undefined vector<8xi16>
1136 ! FIR: %[[shff:.*]] = vector.shuffle %[[ld]], %[[uv]] [7, 6, 5, 4, 3, 2, 1, 0] : vector<8xi16>, vector<8xi16>
1137 ! FIR: %[[res:.*]] = fir.convert %[[shff]] : (vector<8xi16>) -> !fir.vector<8:i16>
1138 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<8:i16>>
1140 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
1141 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[arg1]]
1142 ! LLVMIR: %[[ld:.*]] = load <8 x i16>, ptr %[[addr]], align 1
1143 ! LLVMIR: %[[shff:.*]] = shufflevector <8 x i16> %[[ld]], <8 x i16> undef, <8 x i32> <i32 7, i32 6, i32 5, i32 4, i32 3, i32 2, i32 1, i32 0>
1144 ! LLVMIR: store <8 x i16> %[[shff]], ptr %2, align 16
1145 end subroutine vec_xl_be_testi16a
1147 ! CHECK-LABEL: @vec_xl_be_testi32a
1148 subroutine vec_xl_be_testi32a(arg1, arg2, res)
1149 integer(4) :: arg1
1150 integer(4) :: arg2(2, 4, 8)
1151 vector(integer(4)) :: res
1152 res = vec_xl_be(arg1, arg2)
1154 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i32>
1155 ! FIR: %[[uarr:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x4x8xi32>>) -> !fir.ref<!fir.array<?xi8>>
1156 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[uarr]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
1157 ! FIR: %[[ld:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
1158 ! FIR: %[[uv:.*]] = fir.undefined vector<4xi32>
1159 ! FIR: %[[shff:.*]] = vector.shuffle %[[ld]], %[[uv]] [3, 2, 1, 0] : vector<4xi32>, vector<4xi32>
1160 ! FIR: %[[res:.*]] = fir.convert %[[shff]] : (vector<4xi32>) -> !fir.vector<4:i32>
1161 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:i32>>
1163 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
1164 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1]]
1165 ! LLVMIR: %[[ld:.*]] = load <4 x i32>, ptr %[[addr]], align 1
1166 ! LLVMIR: %[[shff:.*]] = shufflevector <4 x i32> %[[ld]], <4 x i32> undef, <4 x i32> <i32 3, i32 2, i32 1, i32 0>
1167 ! LLVMIR: store <4 x i32> %[[shff]], ptr %2, align 16
1168 end subroutine vec_xl_be_testi32a
1170 ! CHECK-LABEL: @vec_xl_be_testi64a
1171 subroutine vec_xl_be_testi64a(arg1, arg2, res)
1172 integer(8) :: arg1
1173 integer(8) :: arg2(2, 4, 8)
1174 vector(integer(8)) :: res
1175 res = vec_xl_be(arg1, arg2)
1177 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
1178 ! FIR: %[[uarr:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x4x8xi64>>) -> !fir.ref<!fir.array<?xi8>>
1179 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[uarr]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
1180 ! FIR: %[[ld:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
1181 ! FIR: %[[uv:.*]] = fir.undefined vector<2xi64>
1182 ! FIR: %[[shff:.*]] = vector.shuffle %[[ld]], %[[uv]] [1, 0] : vector<2xi64>, vector<2xi64>
1183 ! FIR: %[[res:.*]] = fir.convert %[[shff]] : (vector<2xi64>) -> !fir.vector<2:i64>
1184 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<2:i64>>
1186 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
1187 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[arg1]]
1188 ! LLVMIR: %[[ld:.*]] = load <2 x i64>, ptr %[[addr]], align 1
1189 ! LLVMIR: %[[shff:.*]] = shufflevector <2 x i64> %[[ld]], <2 x i64> undef, <2 x i32> <i32 1, i32 0>
1190 ! LLVMIR: store <2 x i64> %[[shff]], ptr %2, align 16
1191 end subroutine vec_xl_be_testi64a
1193 ! CHECK-LABEL: @vec_xl_be_testf32a
1194 subroutine vec_xl_be_testf32a(arg1, arg2, res)
1195 integer(2) :: arg1
1196 real(4) :: arg2(4)
1197 vector(real(4)) :: res
1198 res = vec_xl_be(arg1, arg2)
1200 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
1201 ! FIR: %[[uarr:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4xf32>>) -> !fir.ref<!fir.array<?xi8>>
1202 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[uarr]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
1203 ! FIR: %[[ld:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
1204 ! FIR: %[[uv:.*]] = fir.undefined vector<4xf32>
1205 ! FIR: %[[shff:.*]] = vector.shuffle %[[ld]], %[[uv]] [3, 2, 1, 0] : vector<4xf32>, vector<4xf32>
1206 ! FIR: %[[res:.*]] = fir.convert %[[shff]] : (vector<4xf32>) -> !fir.vector<4:f32>
1207 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:f32>>
1209 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
1210 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[arg1]]
1211 ! LLVMIR: %[[ld:.*]] = load <4 x float>, ptr %[[addr]], align 1
1212 ! LLVMIR: %[[shff:.*]] = shufflevector <4 x float> %[[ld]], <4 x float> undef, <4 x i32> <i32 3, i32 2, i32 1, i32 0>
1213 ! LLVMIR: store <4 x float> %[[shff]], ptr %2, align 16
1214 end subroutine vec_xl_be_testf32a
1216 ! CHECK-LABEL: @vec_xl_be_testf64a
1217 subroutine vec_xl_be_testf64a(arg1, arg2, res)
1218 integer(8) :: arg1
1219 real(8) :: arg2(7)
1220 vector(real(8)) :: res
1221 res = vec_xl_be(arg1, arg2)
1223 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
1224 ! FIR: %[[uarr:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<7xf64>>) -> !fir.ref<!fir.array<?xi8>>
1225 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[uarr]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
1226 ! FIR: %[[ld:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
1227 ! FIR: %[[uv:.*]] = fir.undefined vector<2xf64>
1228 ! FIR: %[[shff:.*]] = vector.shuffle %[[ld]], %[[uv]] [1, 0] : vector<2xf64>, vector<2xf64>
1229 ! FIR: %[[res:.*]] = fir.convert %[[shff]] : (vector<2xf64>) -> !fir.vector<2:f64>
1230 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<2:f64>>
1232 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
1233 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[arg1]]
1234 ! LLVMIR: %[[ld:.*]] = load <2 x double>, ptr %[[addr]], align 1
1235 ! LLVMIR: %[[shff:.*]] = shufflevector <2 x double> %[[ld]], <2 x double> undef, <2 x i32> <i32 1, i32 0>
1236 ! LLVMIR: store <2 x double> %[[shff]], ptr %2, align 16
1237 end subroutine vec_xl_be_testf64a
1239 !----------------------
1240 ! vec_xlw4
1241 !----------------------
1243 ! CHECK-LABEL: @vec_xlw4_testi8a
1244 subroutine vec_xlw4_testi8a(arg1, arg2, res)
1245 integer(1) :: arg1
1246 vector(integer(1)) :: arg2(2, 4, 8)
1247 vector(integer(1)) :: res
1248 res = vec_xlw4(arg1, arg2)
1250 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i8>
1251 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x4x8x!fir.vector<16:i8>>>) -> !fir.ref<!fir.array<?xi8>>
1252 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i8) -> !fir.ref<!fir.array<?xi8>>
1253 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvw4x(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
1254 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<4xi32> to vector<16xi8>
1255 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<16xi8>) -> !fir.vector<16:i8>
1256 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:i8>>
1258 ! LLVMIR: %[[arg1:.*]] = load i8, ptr %0, align 1
1259 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i8 %[[arg1]]
1260 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.vsx.lxvw4x(ptr %[[addr]])
1261 ! LLVMIR: %[[res:.*]] = bitcast <4 x i32> %[[ld]] to <16 x i8>
1262 ! LLVMIR: store <16 x i8> %[[res]], ptr %2, align 16
1263 end subroutine vec_xlw4_testi8a
1265 ! CHECK-LABEL: @vec_xlw4_testi16a
1266 subroutine vec_xlw4_testi16a(arg1, arg2, res)
1267 integer(2) :: arg1
1268 vector(integer(2)) :: arg2(2, 4, 8)
1269 vector(integer(2)) :: res
1270 res = vec_xlw4(arg1, arg2)
1272 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
1273 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x4x8x!fir.vector<8:i16>>>) -> !fir.ref<!fir.array<?xi8>>
1274 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
1275 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvw4x(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
1276 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<4xi32> to vector<8xi16>
1277 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<8xi16>) -> !fir.vector<8:i16>
1278 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<8:i16>>
1280 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
1281 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[arg1]]
1282 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.vsx.lxvw4x(ptr %[[addr]])
1283 ! LLVMIR: %[[res:.*]] = bitcast <4 x i32> %[[ld]] to <8 x i16>
1284 ! LLVMIR: store <8 x i16> %[[res]], ptr %2, align 16
1285 end subroutine vec_xlw4_testi16a
1287 ! CHECK-LABEL: @vec_xlw4_testu32a
1288 subroutine vec_xlw4_testu32a(arg1, arg2, res)
1289 integer(4) :: arg1
1290 vector(unsigned(4)) :: arg2(2, 4, 8)
1291 vector(unsigned(4)) :: res
1292 res = vec_xlw4(arg1, arg2)
1294 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i32>
1295 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x4x8x!fir.vector<4:ui32>>>) -> !fir.ref<!fir.array<?xi8>>
1296 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
1297 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvw4x(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
1298 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<4xi32>) -> !fir.vector<4:ui32>
1299 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:ui32>>
1301 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
1302 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1]]
1303 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.vsx.lxvw4x(ptr %[[addr]])
1304 ! LLVMIR: store <4 x i32> %[[ld]], ptr %2, align 16
1305 end subroutine vec_xlw4_testu32a
1307 ! CHECK-LABEL: @vec_xlw4_testf32a
1308 subroutine vec_xlw4_testf32a(arg1, arg2, res)
1309 integer(2) :: arg1
1310 vector(real(4)) :: arg2(4)
1311 vector(real(4)) :: res
1312 res = vec_xlw4(arg1, arg2)
1314 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
1315 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4x!fir.vector<4:f32>>>) -> !fir.ref<!fir.array<?xi8>>
1316 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
1317 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvw4x(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
1318 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<4xi32> to vector<4xf32>
1319 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<4xf32>) -> !fir.vector<4:f32>
1320 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:f32>>
1322 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
1323 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[arg1]]
1324 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.vsx.lxvw4x(ptr %[[addr]])
1325 ! LLVMIR: %[[res:.*]] = bitcast <4 x i32> %[[ld]] to <4 x float>
1326 ! LLVMIR: store <4 x float> %[[res]], ptr %2, align 16
1327 end subroutine vec_xlw4_testf32a