[flang][openacc] Use OpenACC terminator instead of fir.unreachable after Stop stmt...
[llvm-project.git] / flang / test / Lower / PowerPC / ppc-vec-load-elem-order.f90
blobf4e7f7b1db41dcf555d44fb4362532844447cf65
1 ! RUN: %flang_fc1 -emit-fir %s -fno-ppc-native-vector-element-order -triple ppc64le-unknown-linux -o - | FileCheck --check-prefixes="FIR" %s
2 ! RUN: %flang_fc1 -emit-llvm %s -fno-ppc-native-vector-element-order -triple ppc64le-unknown-linux -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 %arg0 : !fir.ref<i8>
16 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!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: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
19 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<4xi32> to vector<16xi8>
20 ! FIR: %[[undefv:.*]] = fir.undefined vector<16xi8>
21 ! FIR: %[[shflv:.*]] = vector.shuffle %[[bc]], %[[undefv]] [15, 14, 13, 12, 11, 10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0] : vector<16xi8>, vector<16xi8>
22 ! FIR: %[[res:.*]] = fir.convert %[[shflv]] : (vector<16xi8>) -> !fir.vector<16:i8>
23 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:i8>>
25 ! LLVMIR: %[[arg1:.*]] = load i8, ptr %0, align 1
26 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i8 %[[arg1]]
27 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.altivec.lvx(ptr %[[addr]])
28 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[ld]] to <16 x i8>
29 ! LLVMIR: %[[shflv:.*]] = shufflevector <16 x i8> %[[bc]], <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>
30 ! LLVMIR: store <16 x i8> %[[shflv]], ptr %2, align 16
31 end subroutine vec_ld_testi8
33 ! CHECK-LABEL: @vec_ld_testi16
34 subroutine vec_ld_testi16(arg1, arg2, res)
35 integer(2) :: arg1
36 vector(integer(2)) :: arg2, res
37 res = vec_ld(arg1, arg2)
39 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
40 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.vector<8:i16>>) -> !fir.ref<!fir.array<?xi8>>
41 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
42 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
43 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<4xi32> to vector<8xi16>
44 ! FIR: %[[undefv:.*]] = fir.undefined vector<8xi16>
45 ! FIR: %[[shflv:.*]] = vector.shuffle %[[bc]], %[[undefv]] [7, 6, 5, 4, 3, 2, 1, 0] : vector<8xi16>, vector<8xi16>
46 ! FIR: %[[res:.*]] = fir.convert %[[shflv]] : (vector<8xi16>) -> !fir.vector<8:i16>
47 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<8:i16>>
49 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
50 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[arg1]]
51 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.altivec.lvx(ptr %[[addr]])
52 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[ld]] to <8 x i16>
53 ! LLVMIR: %[[shflv:.*]] = shufflevector <8 x i16> %[[bc]], <8 x i16> undef, <8 x i32> <i32 7, i32 6, i32 5, i32 4, i32 3, i32 2, i32 1, i32 0>
54 ! LLVMIR: store <8 x i16> %[[shflv]], ptr %2, align 16
55 end subroutine vec_ld_testi16
57 ! CHECK-LABEL: @vec_ld_testi32
58 subroutine vec_ld_testi32(arg1, arg2, res)
59 integer(4) :: arg1
60 vector(integer(4)) :: arg2, res
61 res = vec_ld(arg1, arg2)
63 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i32>
64 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.vector<4:i32>>) -> !fir.ref<!fir.array<?xi8>>
65 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
66 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
67 ! FIR: %[[undefv:.*]] = fir.undefined vector<4xi32>
68 ! FIR: %[[shflv:.*]] = vector.shuffle %[[ld]], %[[undefv]] [3, 2, 1, 0] : vector<4xi32>, vector<4xi32>
69 ! FIR: %[[res:.*]] = fir.convert %[[shflv]] : (vector<4xi32>) -> !fir.vector<4:i32>
70 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:i32>>
72 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
73 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1]]
74 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.altivec.lvx(ptr %[[addr]])
75 ! LLVMIR: %[[shflv:.*]] = shufflevector <4 x i32> %[[ld]], <4 x i32> undef, <4 x i32> <i32 3, i32 2, i32 1, i32 0>
76 ! LLVMIR: store <4 x i32> %[[shflv]], ptr %2, align 16
77 end subroutine vec_ld_testi32
79 ! CHECK-LABEL: @vec_ld_testf32
80 subroutine vec_ld_testf32(arg1, arg2, res)
81 integer(8) :: arg1
82 vector(real(4)) :: arg2, res
83 res = vec_ld(arg1, arg2)
85 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
86 ! FIR: %[[i4:.*]] = fir.convert %[[arg1]] : (i64) -> i32
87 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.vector<4:f32>>) -> !fir.ref<!fir.array<?xi8>>
88 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[i4]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
89 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
90 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<4xi32> to vector<4xf32>
91 ! FIR: %[[undefv:.*]] = fir.undefined vector<4xf32>
92 ! FIR: %[[shflv:.*]] = vector.shuffle %[[bc]], %[[undefv]] [3, 2, 1, 0] : vector<4xf32>, vector<4xf32>
93 ! FIR: %[[res:.*]] = fir.convert %[[shflv]] : (vector<4xf32>) -> !fir.vector<4:f32>
94 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:f32>>
96 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
97 ! LLVMIR: %[[i4:.*]] = trunc i64 %[[arg1]] to i32
98 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[i4]]
99 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.altivec.lvx(ptr %[[addr]])
100 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[ld]] to <4 x float>
101 ! LLVMIR: %[[shflv:.*]] = shufflevector <4 x float> %[[bc]], <4 x float> undef, <4 x i32> <i32 3, i32 2, i32 1, i32 0>
102 ! LLVMIR: store <4 x float> %[[shflv]], ptr %2, align 16
103 end subroutine vec_ld_testf32
105 ! CHECK-LABEL: @vec_ld_testu32
106 subroutine vec_ld_testu32(arg1, arg2, res)
107 integer(1) :: arg1
108 vector(unsigned(4)) :: arg2, res
109 res = vec_ld(arg1, arg2)
111 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i8>
112 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.vector<4:ui32>>) -> !fir.ref<!fir.array<?xi8>>
113 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i8) -> !fir.ref<!fir.array<?xi8>>
114 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
115 ! FIR: %[[undefv:.*]] = fir.undefined vector<4xi32>
116 ! FIR: %[[shflv:.*]] = vector.shuffle %[[ld]], %[[undefv]] [3, 2, 1, 0] : vector<4xi32>, vector<4xi32>
117 ! FIR: %[[res:.*]] = fir.convert %[[shflv]] : (vector<4xi32>) -> !fir.vector<4:ui32>
118 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:ui32>>
120 ! LLVMIR: %[[arg1:.*]] = load i8, ptr %0, align 1
121 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i8 %[[arg1]]
122 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.altivec.lvx(ptr %[[addr]])
123 ! LLVMIR: %[[shflv:.*]] = shufflevector <4 x i32> %[[ld]], <4 x i32> undef, <4 x i32> <i32 3, i32 2, i32 1, i32 0>
124 ! LLVMIR: store <4 x i32> %[[shflv]], ptr %2, align 16
125 end subroutine vec_ld_testu32
127 ! CHECK-LABEL: @vec_ld_testi32a
128 subroutine vec_ld_testi32a(arg1, arg2, res)
129 integer(4) :: arg1
130 integer(4) :: arg2(10)
131 vector(integer(4)) :: res
132 res = vec_ld(arg1, arg2)
134 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i32>
135 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<10xi32>>) -> !fir.ref<!fir.array<?xi8>>
136 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
137 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
138 ! FIR: %[[undefv:.*]] = fir.undefined vector<4xi32>
139 ! FIR: %[[shflv:.*]] = vector.shuffle %[[ld]], %[[undefv]] [3, 2, 1, 0] : vector<4xi32>, vector<4xi32>
140 ! FIR: %[[res:.*]] = fir.convert %[[shflv]] : (vector<4xi32>) -> !fir.vector<4:i32>
141 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:i32>>
143 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
144 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1]]
145 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.altivec.lvx(ptr %[[addr]])
146 ! LLVMIR: %[[shflv:.*]] = shufflevector <4 x i32> %[[ld]], <4 x i32> undef, <4 x i32> <i32 3, i32 2, i32 1, i32 0>
147 ! LLVMIR: store <4 x i32> %[[shflv]], ptr %2, align 16
148 end subroutine vec_ld_testi32a
150 ! CHECK-LABEL: @vec_ld_testf32av
151 subroutine vec_ld_testf32av(arg1, arg2, res)
152 integer(8) :: arg1
153 vector(real(4)) :: arg2(2, 4, 8)
154 vector(real(4)) :: res
155 res = vec_ld(arg1, arg2)
157 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
158 ! FIR: %[[i4:.*]] = fir.convert %[[arg1]] : (i64) -> i32
159 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x4x8x!fir.vector<4:f32>>>) -> !fir.ref<!fir.array<?xi8>>
160 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[i4]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
161 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
162 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<4xi32> to vector<4xf32>
163 ! FIR: %[[undefv:.*]] = fir.undefined vector<4xf32>
164 ! FIR: %[[shflv:.*]] = vector.shuffle %[[bc]], %[[undefv]] [3, 2, 1, 0] : vector<4xf32>, vector<4xf32>
165 ! FIR: %[[res:.*]] = fir.convert %[[shflv]] : (vector<4xf32>) -> !fir.vector<4:f32>
166 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:f32>>
168 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
169 ! LLVMIR: %[[i4:.*]] = trunc i64 %[[arg1]] to i32
170 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[i4]]
171 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.altivec.lvx(ptr %[[addr]])
172 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[ld]] to <4 x float>
173 ! LLVMIR: %[[shflv:.*]] = shufflevector <4 x float> %[[bc]], <4 x float> undef, <4 x i32> <i32 3, i32 2, i32 1, i32 0>
174 ! LLVMIR: store <4 x float> %[[shflv]], ptr %2, align 16
175 end subroutine vec_ld_testf32av
177 ! CHECK-LABEL: @vec_ld_testi32s
178 subroutine vec_ld_testi32s(arg1, arg2, res)
179 integer(4) :: arg1
180 real(4) :: arg2
181 vector(real(4)) :: res
182 res = vec_ld(arg1, arg2)
184 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i32>
185 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<f32>) -> !fir.ref<!fir.array<?xi8>>
186 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
187 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
188 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<4xi32> to vector<4xf32>
189 ! FIR: %[[undefv:.*]] = fir.undefined vector<4xf32>
190 ! FIR: %[[shflv:.*]] = vector.shuffle %[[bc]], %[[undefv]] [3, 2, 1, 0] : vector<4xf32>, vector<4xf32>
191 ! FIR: %[[res:.*]] = fir.convert %[[shflv]] : (vector<4xf32>) -> !fir.vector<4:f32>
192 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:f32>>
194 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
195 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1]]
196 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.altivec.lvx(ptr %[[addr]])
197 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[ld]] to <4 x float>
198 ! LLVMIR: %[[shflv:.*]] = shufflevector <4 x float> %[[bc]], <4 x float> undef, <4 x i32> <i32 3, i32 2, i32 1, i32 0>
199 ! LLVMIR: store <4 x float> %[[shflv]], ptr %2, align 16
200 end subroutine vec_ld_testi32s
202 !-------------------
203 ! vec_lde
204 !-------------------
206 ! CHECK-LABEL: @vec_lde_testi8s
207 subroutine vec_lde_testi8s(arg1, arg2, res)
208 integer(1) :: arg1
209 integer(1) :: arg2
210 vector(integer(1)) :: res
211 res = vec_lde(arg1, arg2)
213 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i8>
214 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<i8>) -> !fir.ref<!fir.array<?xi8>>
215 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i8) -> !fir.ref<!fir.array<?xi8>>
216 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvebx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<16xi8>
217 ! FIR: %[[undefv:.*]] = fir.undefined vector<16xi8>
218 ! FIR: %[[shflv:.*]] = vector.shuffle %[[ld]], %[[undefv]] [15, 14, 13, 12, 11, 10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0] : vector<16xi8>, vector<16xi8>
219 ! FIR: %[[res:.*]] = fir.convert %[[shflv]] : (vector<16xi8>) -> !fir.vector<16:i8>
220 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:i8>>
222 ! LLVMIR: %[[arg1:.*]] = load i8, ptr %0, align 1
223 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i8 %[[arg1]]
224 ! LLVMIR: %[[ld:.*]] = call <16 x i8> @llvm.ppc.altivec.lvebx(ptr %[[addr]])
225 ! LLVMIR: %[[shflv:.*]] = 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>
226 ! LLVMIR: store <16 x i8> %[[shflv]], ptr %2, align 16
227 end subroutine vec_lde_testi8s
229 ! CHECK-LABEL: @vec_lde_testi16a
230 subroutine vec_lde_testi16a(arg1, arg2, res)
231 integer(2) :: arg1
232 integer(2) :: arg2(2, 11, 7)
233 vector(integer(2)) :: res
234 res = vec_lde(arg1, arg2)
236 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
237 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x11x7xi16>>) -> !fir.ref<!fir.array<?xi8>>
238 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
239 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvehx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<8xi16>
240 ! FIR: %[[undefv:.*]] = fir.undefined vector<8xi16>
241 ! FIR: %[[shflv:.*]] = vector.shuffle %[[ld]], %[[undefv]] [7, 6, 5, 4, 3, 2, 1, 0] : vector<8xi16>, vector<8xi16>
242 ! FIR: %[[res:.*]] = fir.convert %[[shflv]] : (vector<8xi16>) -> !fir.vector<8:i16>
243 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<8:i16>>
245 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
246 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[arg1]]
247 ! LLVMIR: %[[ld:.*]] = call <8 x i16> @llvm.ppc.altivec.lvehx(ptr %[[addr]])
248 ! LLVMIR: %[[shflv:.*]] = 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>
249 ! LLVMIR: store <8 x i16> %[[shflv]], ptr %2, align 16
250 end subroutine vec_lde_testi16a
252 ! CHECK-LABEL: @vec_lde_testi32a
253 subroutine vec_lde_testi32a(arg1, arg2, res)
254 integer(4) :: arg1
255 integer(4) :: arg2(5)
256 vector(integer(4)) :: res
257 res = vec_lde(arg1, arg2)
259 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i32>
260 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<5xi32>>) -> !fir.ref<!fir.array<?xi8>>
261 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
262 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvewx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
263 ! FIR: %[[undefv:.*]] = fir.undefined vector<4xi32>
264 ! FIR: %[[shflv:.*]] = vector.shuffle %[[ld]], %[[undefv]] [3, 2, 1, 0] : vector<4xi32>, vector<4xi32>
265 ! FIR: %[[res:.*]] = fir.convert %[[shflv]] : (vector<4xi32>) -> !fir.vector<4:i32>
266 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:i32>>
268 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
269 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1]]
270 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.altivec.lvewx(ptr %[[addr]])
271 ! LLVMIR: %[[shflv:.*]] = shufflevector <4 x i32> %[[ld]], <4 x i32> undef, <4 x i32> <i32 3, i32 2, i32 1, i32 0>
272 ! LLVMIR: store <4 x i32> %[[shflv]], ptr %2, align 16
273 end subroutine vec_lde_testi32a
275 ! CHECK-LABEL: @vec_lde_testf32a
276 subroutine vec_lde_testf32a(arg1, arg2, res)
277 integer(8) :: arg1
278 real(4) :: arg2(11)
279 vector(real(4)) :: res
280 res = vec_lde(arg1, arg2)
282 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
283 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<11xf32>>) -> !fir.ref<!fir.array<?xi8>>
284 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
285 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvewx(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
286 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<4xi32> to vector<4xf32>
287 ! FIR: %[[undefv:.*]] = fir.undefined vector<4xf32>
288 ! FIR: %[[shflv:.*]] = vector.shuffle %[[bc]], %[[undefv]] [3, 2, 1, 0] : vector<4xf32>, vector<4xf32>
289 ! FIR: %[[res:.*]] = fir.convert %[[shflv]] : (vector<4xf32>) -> !fir.vector<4:f32>
290 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:f32>>
292 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
293 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[arg1]]
294 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.altivec.lvewx(ptr %[[addr]])
295 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[ld]] to <4 x float>
296 ! LLVMIR: %[[shflv:.*]] = shufflevector <4 x float> %[[bc]], <4 x float> undef, <4 x i32> <i32 3, i32 2, i32 1, i32 0>
297 ! LLVMIR: store <4 x float> %[[shflv]], ptr %2, align 16
298 end subroutine vec_lde_testf32a
300 !-------------------
301 ! vec_lvsl
302 !-------------------
304 ! CHECK-LABEL: @vec_lvsl_testi8s
305 subroutine vec_lvsl_testi8s(arg1, arg2, res)
306 integer(1) :: arg1
307 integer(1) :: arg2
308 vector(unsigned(1)) :: res
309 res = vec_lvsl(arg1, arg2)
311 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i8>
312 ! FIR: %[[arg1i64:.*]] = fir.convert %[[arg1]] : (i8) -> i64
313 ! FIR: %[[fiveSix:.*]] = arith.constant 56 : i64
314 ! FIR: %[[lshft:.*]] = arith.shli %[[arg1i64]], %[[fiveSix]] : i64
315 ! FIR: %[[rshft:.*]] = arith.shrsi %[[lshft]], %[[fiveSix]] : i64
316 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<i8>) -> !fir.ref<!fir.array<?xi8>>
317 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[rshft]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
318 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvsl(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<16xi8>
319 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<16xi8>) -> !fir.vector<16:ui8>
320 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:ui8>>
322 ! LLVMIR: %[[arg1:.*]] = load i8, ptr %0, align 1
323 ! LLVMIR: %[[iext:.*]] = sext i8 %[[arg1]] to i64
324 ! LLVMIR: %[[lshft:.*]] = shl i64 %[[iext]], 56
325 ! LLVMIR: %[[rshft:.*]] = ashr i64 %[[lshft]], 56
326 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[rshft]]
327 ! LLVMIR: %[[ld:.*]] = call <16 x i8> @llvm.ppc.altivec.lvsl(ptr %[[addr]])
328 ! LLVMIR: store <16 x i8> %[[ld]], ptr %2, align 16
329 end subroutine vec_lvsl_testi8s
331 ! CHECK-LABEL: @vec_lvsl_testi16a
332 subroutine vec_lvsl_testi16a(arg1, arg2, res)
333 integer(2) :: arg1
334 integer(2) :: arg2(4)
335 vector(unsigned(1)) :: res
336 res = vec_lvsl(arg1, arg2)
338 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
339 ! FIR: %[[arg1i64:.*]] = fir.convert %[[arg1]] : (i16) -> i64
340 ! FIR: %[[fiveSix:.*]] = arith.constant 56 : i64
341 ! FIR: %[[lshft:.*]] = arith.shli %[[arg1i64]], %[[fiveSix]] : i64
342 ! FIR: %[[rshft:.*]] = arith.shrsi %[[lshft]], %[[fiveSix]] : i64
343 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4xi16>>) -> !fir.ref<!fir.array<?xi8>>
344 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[rshft]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
345 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvsl(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<16xi8>
346 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<16xi8>) -> !fir.vector<16:ui8>
347 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:ui8>>
349 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
350 ! LLVMIR: %[[iext:.*]] = sext i16 %[[arg1]] to i64
351 ! LLVMIR: %[[lshft:.*]] = shl i64 %[[iext]], 56
352 ! LLVMIR: %[[rshft:.*]] = ashr i64 %[[lshft]], 56
353 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[rshft]]
354 ! LLVMIR: %[[ld:.*]] = call <16 x i8> @llvm.ppc.altivec.lvsl(ptr %[[addr]])
355 ! LLVMIR: store <16 x i8> %[[ld]], ptr %2, align 16
356 end subroutine vec_lvsl_testi16a
358 ! CHECK-LABEL: @vec_lvsl_testi32a
359 subroutine vec_lvsl_testi32a(arg1, arg2, res)
360 integer(4) :: arg1
361 integer(4) :: arg2(11, 3, 4)
362 vector(unsigned(1)) :: res
363 res = vec_lvsl(arg1, arg2)
365 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i32>
366 ! FIR: %[[arg1i64:.*]] = fir.convert %[[arg1]] : (i32) -> i64
367 ! FIR: %[[fiveSix:.*]] = arith.constant 56 : i64
368 ! FIR: %[[lshft:.*]] = arith.shli %[[arg1i64]], %[[fiveSix]] : i64
369 ! FIR: %[[rshft:.*]] = arith.shrsi %[[lshft]], %[[fiveSix]] : i64
370 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<11x3x4xi32>>) -> !fir.ref<!fir.array<?xi8>>
371 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[rshft]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
372 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvsl(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<16xi8>
373 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<16xi8>) -> !fir.vector<16:ui8>
374 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:ui8>>
376 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
377 ! LLVMIR: %[[iext:.*]] = sext i32 %[[arg1]] to i64
378 ! LLVMIR: %[[lshft:.*]] = shl i64 %[[iext]], 56
379 ! LLVMIR: %[[rshft:.*]] = ashr i64 %[[lshft]], 56
380 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[rshft]]
381 ! LLVMIR: %[[ld:.*]] = call <16 x i8> @llvm.ppc.altivec.lvsl(ptr %[[addr]])
382 ! LLVMIR: store <16 x i8> %[[ld]], ptr %2, align 16
383 end subroutine vec_lvsl_testi32a
385 ! CHECK-LABEL: @vec_lvsl_testf32a
386 subroutine vec_lvsl_testf32a(arg1, arg2, res)
387 integer(8) :: arg1
388 real(4) :: arg2(51)
389 vector(unsigned(1)) :: res
390 res = vec_lvsl(arg1, arg2)
392 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
393 ! FIR: %[[fiveSix:.*]] = arith.constant 56 : i64
394 ! FIR: %[[lshft:.*]] = arith.shli %[[arg1]], %[[fiveSix]] : i64
395 ! FIR: %[[rshft:.*]] = arith.shrsi %[[lshft]], %[[fiveSix]] : i64
396 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<51xf32>>) -> !fir.ref<!fir.array<?xi8>>
397 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[rshft]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
398 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvsl(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<16xi8>
399 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<16xi8>) -> !fir.vector<16:ui8>
400 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:ui8>>
402 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
403 ! LLVMIR: %[[lshft:.*]] = shl i64 %[[arg1]], 56
404 ! LLVMIR: %[[rshft:.*]] = ashr i64 %[[lshft]], 56
405 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[rshft]]
406 ! LLVMIR: %[[ld:.*]] = call <16 x i8> @llvm.ppc.altivec.lvsl(ptr %[[addr]])
407 ! LLVMIR: store <16 x i8> %[[ld]], ptr %2, align 16
408 end subroutine vec_lvsl_testf32a
410 !-------------------
411 ! vec_lvsr
412 !-------------------
414 ! CHECK-LABEL: @vec_lvsr_testi8s
415 subroutine vec_lvsr_testi8s(arg1, arg2, res)
416 integer(1) :: arg1
417 integer(1) :: arg2
418 vector(unsigned(1)) :: res
419 res = vec_lvsr(arg1, arg2)
421 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i8>
422 ! FIR: %[[arg1i64:.*]] = fir.convert %[[arg1]] : (i8) -> i64
423 ! FIR: %[[fiveSix:.*]] = arith.constant 56 : i64
424 ! FIR: %[[lshft:.*]] = arith.shli %[[arg1i64]], %[[fiveSix]] : i64
425 ! FIR: %[[rshft:.*]] = arith.shrsi %[[lshft]], %[[fiveSix]] : i64
426 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<i8>) -> !fir.ref<!fir.array<?xi8>>
427 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[rshft]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
428 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvsr(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<16xi8>
429 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<16xi8>) -> !fir.vector<16:ui8>
430 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:ui8>>
432 ! LLVMIR: %[[arg1:.*]] = load i8, ptr %0, align 1
433 ! LLVMIR: %[[iext:.*]] = sext i8 %[[arg1]] to i64
434 ! LLVMIR: %[[lshft:.*]] = shl i64 %[[iext]], 56
435 ! LLVMIR: %[[rshft:.*]] = ashr i64 %[[lshft]], 56
436 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[rshft]]
437 ! LLVMIR: %[[ld:.*]] = call <16 x i8> @llvm.ppc.altivec.lvsr(ptr %[[addr]])
438 ! LLVMIR: store <16 x i8> %[[ld]], ptr %2, align 16
439 end subroutine vec_lvsr_testi8s
441 ! CHECK-LABEL: @vec_lvsr_testi16a
442 subroutine vec_lvsr_testi16a(arg1, arg2, res)
443 integer(2) :: arg1
444 integer(2) :: arg2(41)
445 vector(unsigned(1)) :: res
446 res = vec_lvsr(arg1, arg2)
448 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
449 ! FIR: %[[arg1i64:.*]] = fir.convert %[[arg1]] : (i16) -> i64
450 ! FIR: %[[fiveSix:.*]] = arith.constant 56 : i64
451 ! FIR: %[[lshft:.*]] = arith.shli %[[arg1i64]], %[[fiveSix]] : i64
452 ! FIR: %[[rshft:.*]] = arith.shrsi %[[lshft]], %[[fiveSix]] : i64
453 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<41xi16>>) -> !fir.ref<!fir.array<?xi8>>
454 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[rshft]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
455 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvsr(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<16xi8>
456 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<16xi8>) -> !fir.vector<16:ui8>
457 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:ui8>>
459 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
460 ! LLVMIR: %[[iext:.*]] = sext i16 %[[arg1]] to i64
461 ! LLVMIR: %[[lshft:.*]] = shl i64 %[[iext]], 56
462 ! LLVMIR: %[[rshft:.*]] = ashr i64 %[[lshft]], 56
463 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[rshft]]
464 ! LLVMIR: %[[ld:.*]] = call <16 x i8> @llvm.ppc.altivec.lvsr(ptr %[[addr]])
465 ! LLVMIR: store <16 x i8> %[[ld]], ptr %2, align 16
466 end subroutine vec_lvsr_testi16a
468 ! CHECK-LABEL: @vec_lvsr_testi32a
469 subroutine vec_lvsr_testi32a(arg1, arg2, res)
470 integer(4) :: arg1
471 integer(4) :: arg2(23, 31, 47)
472 vector(unsigned(1)) :: res
473 res = vec_lvsr(arg1, arg2)
475 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i32>
476 ! FIR: %[[arg1i64:.*]] = fir.convert %[[arg1]] : (i32) -> i64
477 ! FIR: %[[fiveSix:.*]] = arith.constant 56 : i64
478 ! FIR: %[[lshft:.*]] = arith.shli %[[arg1i64]], %[[fiveSix]] : i64
479 ! FIR: %[[rshft:.*]] = arith.shrsi %[[lshft]], %[[fiveSix]] : i64
480 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<23x31x47xi32>>) -> !fir.ref<!fir.array<?xi8>>
481 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[rshft]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
482 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvsr(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<16xi8>
483 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<16xi8>) -> !fir.vector<16:ui8>
484 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:ui8>>
486 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
487 ! LLVMIR: %[[iext:.*]] = sext i32 %[[arg1]] to i64
488 ! LLVMIR: %[[lshft:.*]] = shl i64 %[[iext]], 56
489 ! LLVMIR: %[[rshft:.*]] = ashr i64 %[[lshft]], 56
490 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[rshft]]
491 ! LLVMIR: %[[ld:.*]] = call <16 x i8> @llvm.ppc.altivec.lvsr(ptr %[[addr]])
492 ! LLVMIR: store <16 x i8> %[[ld]], ptr %2, align 16
493 end subroutine vec_lvsr_testi32a
495 ! CHECK-LABEL: @vec_lvsr_testf32a
496 subroutine vec_lvsr_testf32a(arg1, arg2, res)
497 integer(8) :: arg1
498 real(4) :: arg2
499 vector(unsigned(1)) :: res
500 res = vec_lvsr(arg1, arg2)
502 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
503 ! FIR: %[[fiveSix:.*]] = arith.constant 56 : i64
504 ! FIR: %[[lshft:.*]] = arith.shli %[[arg1]], %[[fiveSix]] : i64
505 ! FIR: %[[rshft:.*]] = arith.shrsi %[[lshft]], %[[fiveSix]] : i64
506 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<f32>) -> !fir.ref<!fir.array<?xi8>>
507 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[rshft]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
508 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.altivec.lvsr(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<16xi8>
509 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<16xi8>) -> !fir.vector<16:ui8>
510 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:ui8>>
512 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
513 ! LLVMIR: %[[lshft:.*]] = shl i64 %[[arg1]], 56
514 ! LLVMIR: %[[rshft:.*]] = ashr i64 %[[lshft]], 56
515 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[rshft]]
516 ! LLVMIR: %[[ld:.*]] = call <16 x i8> @llvm.ppc.altivec.lvsr(ptr %[[addr]])
517 ! LLVMIR: store <16 x i8> %[[ld]], ptr %2, align 16
518 end subroutine vec_lvsr_testf32a
520 !-------------------
521 ! vec_lxv
522 !-------------------
524 ! CHECK-LABEL: @vec_lxv_testi8a
525 subroutine vec_lxv_testi8a(arg1, arg2, res)
526 integer(1) :: arg1
527 integer(1) :: arg2(4)
528 vector(integer(1)) :: res
529 res = vec_lxv(arg1, arg2)
531 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i8>
532 ! FIR: %[[ref:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4xi8>>) -> !fir.ref<!fir.array<?xi8>>
533 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[ref]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i8) -> !fir.ref<!fir.array<?xi8>>
534 ! FIR: %[[ld:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
535 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<16xi8>) -> !fir.vector<16:i8>
536 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:i8>>
538 ! LLVMIR: %[[offset:.*]] = load i8, ptr %0, align 1
539 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i8 %[[offset]]
540 ! LLVMIR: %[[res:.*]] = load <16 x i8>, ptr %[[addr]], align 1
541 ! LLVMIR: store <16 x i8> %[[res]], ptr %2, align 16
542 end subroutine vec_lxv_testi8a
544 ! CHECK-LABEL: @vec_lxv_testi16a
545 subroutine vec_lxv_testi16a(arg1, arg2, res)
546 integer(2) :: arg1
547 integer(2) :: arg2(2, 4, 8)
548 vector(integer(2)) :: res
549 res = vec_lxv(arg1, arg2)
551 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
552 ! FIR: %[[ref:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x4x8xi16>>) -> !fir.ref<!fir.array<?xi8>>
553 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[ref]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
554 ! FIR: %[[ld:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
555 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<8xi16>) -> !fir.vector<8:i16>
556 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<8:i16>>
558 ! LLVMIR: %[[offset:.*]] = load i16, ptr %0, align 2
559 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[offset]]
560 ! LLVMIR: %[[res:.*]] = load <8 x i16>, ptr %[[addr]], align 1
561 ! LLVMIR: store <8 x i16> %[[res]], ptr %2, align 16
562 end subroutine vec_lxv_testi16a
564 ! CHECK-LABEL: @vec_lxv_testi32a
565 subroutine vec_lxv_testi32a(arg1, arg2, res)
566 integer(4) :: arg1
567 integer(4) :: arg2(2, 4, 8)
568 vector(integer(4)) :: res
569 res = vec_lxv(arg1, arg2)
571 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i32>
572 ! FIR: %[[ref:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x4x8xi32>>) -> !fir.ref<!fir.array<?xi8>>
573 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[ref]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
574 ! FIR: %[[ld:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
575 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<4xi32>) -> !fir.vector<4:i32>
576 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:i32>>
578 ! LLVMIR: %[[offset:.*]] = load i32, ptr %0, align 4
579 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[offset]]
580 ! LLVMIR: %[[res:.*]] = load <4 x i32>, ptr %[[addr]], align 1
581 ! LLVMIR: store <4 x i32> %[[res]], ptr %2, align 16
582 end subroutine vec_lxv_testi32a
584 ! CHECK-LABEL: @vec_lxv_testf32a
585 subroutine vec_lxv_testf32a(arg1, arg2, res)
586 integer(2) :: arg1
587 real(4) :: arg2(4)
588 vector(real(4)) :: res
589 res = vec_lxv(arg1, arg2)
591 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
592 ! FIR: %[[ref:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4xf32>>) -> !fir.ref<!fir.array<?xi8>>
593 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[ref]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
594 ! FIR: %[[ld:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
595 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<4xf32>) -> !fir.vector<4:f32>
596 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:f32>>
598 ! LLVMIR: %[[offset:.*]] = load i16, ptr %0, align 2
599 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[offset]]
600 ! LLVMIR: %[[res:.*]] = load <4 x float>, ptr %[[addr]], align 1
601 ! LLVMIR: store <4 x float> %[[res]], ptr %2, align 16
602 end subroutine vec_lxv_testf32a
604 ! CHECK-LABEL: @vec_lxv_testf64a
605 subroutine vec_lxv_testf64a(arg1, arg2, res)
606 integer(8) :: arg1
607 real(8) :: arg2(4)
608 vector(real(8)) :: res
609 res = vec_lxv(arg1, arg2)
611 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
612 ! FIR: %[[ref:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4xf64>>) -> !fir.ref<!fir.array<?xi8>>
613 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[ref]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
614 ! FIR: %[[ld:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
615 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<2xf64>) -> !fir.vector<2:f64>
616 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<2:f64>>
618 ! LLVMIR: %[[offset:.*]] = load i64, ptr %0, align 8
619 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[offset]]
620 ! LLVMIR: %[[res:.*]] = load <2 x double>, ptr %[[addr]], align 1
621 ! LLVMIR: store <2 x double> %[[res]], ptr %2, align 16
622 end subroutine vec_lxv_testf64a
624 !-------------------
625 ! vec_xl
626 !-------------------
628 ! CHECK-LABEL: @vec_xl_testi8a
629 subroutine vec_xl_testi8a(arg1, arg2, res)
630 integer(1) :: arg1
631 integer(1) :: arg2
632 vector(integer(1)) :: res
633 res = vec_xl(arg1, arg2)
635 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i8>
636 ! FIR: %[[ref:.*]] = fir.convert %arg1 : (!fir.ref<i8>) -> !fir.ref<!fir.array<?xi8>>
637 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[ref]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i8) -> !fir.ref<!fir.array<?xi8>>
638 ! FIR: %[[ref2:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
639 ! FIR: %[[undefv:.*]] = fir.undefined vector<16xi8>
640 ! FIR: %[[shflv:.*]] = vector.shuffle %[[ref2]], %[[undefv]] [15, 14, 13, 12, 11, 10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0] : vector<16xi8>, vector<16xi8>
641 ! FIR: %[[res:.*]] = fir.convert %[[shflv]] : (vector<16xi8>) -> !fir.vector<16:i8>
642 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:i8>>
644 ! LLVMIR: %[[arg1:.*]] = load i8, ptr %0, align 1
645 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i8 %[[arg1]]
646 ! LLVMIR: %[[ld:.*]] = load <16 x i8>, ptr %[[addr]], align 1
647 ! LLVMIR: %[[shflv:.*]] = 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>
648 ! LLVMIR: store <16 x i8> %[[shflv]], ptr %2, align 16
649 end subroutine vec_xl_testi8a
651 ! CHECK-LABEL: @vec_xl_testi16a
652 subroutine vec_xl_testi16a(arg1, arg2, res)
653 integer(2) :: arg1
654 integer(2) :: arg2(2, 8)
655 vector(integer(2)) :: res
656 res = vec_xl(arg1, arg2)
658 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
659 ! FIR: %[[ref:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x8xi16>>) -> !fir.ref<!fir.array<?xi8>>
660 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[ref]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
661 ! FIR: %[[ref2:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
662 ! FIR: %[[undefv:.*]] = fir.undefined vector<8xi16>
663 ! FIR: %[[shflv:.*]] = vector.shuffle %[[ref2]], %[[undefv]] [7, 6, 5, 4, 3, 2, 1, 0] : vector<8xi16>, vector<8xi16>
664 ! FIR: %[[res:.*]] = fir.convert %[[shflv]] : (vector<8xi16>) -> !fir.vector<8:i16>
665 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<8:i16>>
667 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
668 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[arg1]]
669 ! LLVMIR: %[[ld:.*]] = load <8 x i16>, ptr %[[addr]], align 1
670 ! LLVMIR: %[[shflv:.*]] = 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>
671 ! LLVMIR: store <8 x i16> %[[shflv]], ptr %2, align 16
672 end subroutine vec_xl_testi16a
674 ! CHECK-LABEL: @vec_xl_testi32a
675 subroutine vec_xl_testi32a(arg1, arg2, res)
676 integer(4) :: arg1
677 integer(4) :: arg2(2, 4, 8)
678 vector(integer(4)) :: res
679 res = vec_xl(arg1, arg2)
681 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i32>
682 ! FIR: %[[ref:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x4x8xi32>>) -> !fir.ref<!fir.array<?xi8>>
683 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[ref]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
684 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvw4x.be(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
685 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<4xi32>) -> !fir.vector<4:i32>
686 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:i32>>
688 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
689 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1]]
690 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.vsx.lxvw4x.be(ptr %[[addr]])
691 ! LLVMIR: store <4 x i32> %[[ld]], ptr %2, align 16
692 end subroutine vec_xl_testi32a
694 ! CHECK-LABEL: @vec_xl_testi64a
695 subroutine vec_xl_testi64a(arg1, arg2, res)
696 integer(8) :: arg1
697 integer(8) :: arg2(2, 4, 1)
698 vector(integer(8)) :: res
699 res = vec_xl(arg1, arg2)
701 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
702 ! FIR: %[[ref:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x4x1xi64>>) -> !fir.ref<!fir.array<?xi8>>
703 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[ref]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
704 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvd2x.be(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<2xf64>
705 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<2xf64> to vector<2xi64>
706 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<2xi64>) -> !fir.vector<2:i64>
707 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<2:i64>>
709 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
710 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[arg1]]
711 ! LLVMIR: %[[ld:.*]] = call contract <2 x double> @llvm.ppc.vsx.lxvd2x.be(ptr %[[addr]])
712 ! LLVMIR: %[[bc:.*]] = bitcast <2 x double> %[[ld]] to <2 x i64>
713 ! LLVMIR: store <2 x i64> %[[bc]], ptr %2, align 16
714 end subroutine vec_xl_testi64a
716 ! CHECK-LABEL: @vec_xl_testf32a
717 subroutine vec_xl_testf32a(arg1, arg2, res)
718 integer(2) :: arg1
719 real(4) :: arg2(4)
720 vector(real(4)) :: res
721 res = vec_xl(arg1, arg2)
723 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
724 ! FIR: %[[ref:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4xf32>>) -> !fir.ref<!fir.array<?xi8>>
725 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[ref]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
726 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvw4x.be(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
727 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<4xi32> to vector<4xf32>
728 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<4xf32>) -> !fir.vector<4:f32>
729 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:f32>>
731 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
732 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[arg1]]
733 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.vsx.lxvw4x.be(ptr %[[addr]])
734 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[ld]] to <4 x float>
735 ! LLVMIR: store <4 x float> %[[bc]], ptr %2, align 16
736 end subroutine vec_xl_testf32a
738 ! CHECK-LABEL: @vec_xl_testf64a
739 subroutine vec_xl_testf64a(arg1, arg2, res)
740 integer(8) :: arg1
741 real(8) :: arg2(2)
742 vector(real(8)) :: res
743 res = vec_xl(arg1, arg2)
745 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
746 ! FIR: %[[ref:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2xf64>>) -> !fir.ref<!fir.array<?xi8>>
747 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[ref]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
748 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvd2x.be(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<2xf64>
749 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<2xf64>) -> !fir.vector<2:f64>
750 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<2:f64>>
752 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
753 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[arg1]]
754 ! LLVMIR: %[[ld:.*]] = call contract <2 x double> @llvm.ppc.vsx.lxvd2x.be(ptr %[[addr]])
755 ! LLVMIR: store <2 x double> %[[ld]], ptr %2, align 16
756 end subroutine vec_xl_testf64a
758 !-------------------
759 ! vec_xl_be
760 !-------------------
762 ! CHECK-LABEL: @vec_xl_be_testi8a
763 subroutine vec_xl_be_testi8a(arg1, arg2, res)
764 integer(1) :: arg1
765 integer(1) :: arg2(2, 4, 8)
766 vector(integer(1)) :: res
767 res = vec_xl_be(arg1, arg2)
769 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i8>
770 ! FIR: %[[ref:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x4x8xi8>>) -> !fir.ref<!fir.array<?xi8>>
771 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[ref]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i8) -> !fir.ref<!fir.array<?xi8>>
772 ! FIR: %[[ref2:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
773 ! FIR: %[[undefv:.*]] = fir.undefined vector<16xi8>
774 ! FIR: %[[shflv:.*]] = vector.shuffle %[[ref2]], %[[undefv]] [15, 14, 13, 12, 11, 10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0] : vector<16xi8>, vector<16xi8>
775 ! FIR: %[[res:.*]] = fir.convert %[[shflv]] : (vector<16xi8>) -> !fir.vector<16:i8>
776 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:i8>>
778 ! LLVMIR: %4 = load i8, ptr %0, align 1
779 ! LLVMIR: %5 = getelementptr i8, ptr %1, i8 %4
780 ! LLVMIR: %6 = load <16 x i8>, ptr %5, align 1
781 ! LLVMIR: %7 = shufflevector <16 x i8> %6, <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>
782 ! LLVMIR: store <16 x i8> %7, ptr %2, align 16
783 end subroutine vec_xl_be_testi8a
785 ! CHECK-LABEL: @vec_xl_be_testi16a
786 subroutine vec_xl_be_testi16a(arg1, arg2, res)
787 integer(2) :: arg1
788 integer(2) :: arg2(8,2)
789 vector(integer(2)) :: res
790 res = vec_xl_be(arg1, arg2)
792 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
793 ! FIR: %[[ref:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<8x2xi16>>) -> !fir.ref<!fir.array<?xi8>>
794 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[ref]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
795 ! FIR: %[[ref2:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
796 ! FIR: %[[undefv:.*]] = fir.undefined vector<8xi16>
797 ! FIR: %[[shflv:.*]] = vector.shuffle %[[ref2]], %[[undefv]] [7, 6, 5, 4, 3, 2, 1, 0] : vector<8xi16>, vector<8xi16>
798 ! FIR: %[[res:.*]] = fir.convert %[[shflv]] : (vector<8xi16>) -> !fir.vector<8:i16>
799 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<8:i16>>
801 ! LLVMIR: %4 = load i16, ptr %0, align 2
802 ! LLVMIR: %5 = getelementptr i8, ptr %1, i16 %4
803 ! LLVMIR: %6 = load <8 x i16>, ptr %5, align 1
804 ! LLVMIR: %7 = shufflevector <8 x i16> %6, <8 x i16> undef, <8 x i32> <i32 7, i32 6, i32 5, i32 4, i32 3, i32 2, i32 1, i32 0>
805 ! LLVMIR: store <8 x i16> %7, ptr %2, align 16
806 end subroutine vec_xl_be_testi16a
808 ! CHECK-LABEL: @vec_xl_be_testi32a
809 subroutine vec_xl_be_testi32a(arg1, arg2, res)
810 integer(4) :: arg1
811 integer(4) :: arg2(2, 4)
812 vector(integer(4)) :: res
813 res = vec_xl_be(arg1, arg2)
815 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i32>
816 ! FIR: %[[ref:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x4xi32>>) -> !fir.ref<!fir.array<?xi8>>
817 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[ref]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
818 ! FIR: %[[ref2:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
819 ! FIR: %[[undefv:.*]] = fir.undefined vector<4xi32>
820 ! FIR: %[[shflv:.*]] = vector.shuffle %[[ref2]], %[[undefv]] [3, 2, 1, 0] : vector<4xi32>, vector<4xi32>
821 ! FIR: %[[res:.*]] = fir.convert %[[shflv]] : (vector<4xi32>) -> !fir.vector<4:i32>
822 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:i32>>
824 ! LLVMIR: %4 = load i32, ptr %0, align 4
825 ! LLVMIR: %5 = getelementptr i8, ptr %1, i32 %4
826 ! LLVMIR: %6 = load <4 x i32>, ptr %5, align 1
827 ! LLVMIR: %7 = shufflevector <4 x i32> %6, <4 x i32> undef, <4 x i32> <i32 3, i32 2, i32 1, i32 0>
828 ! LLVMIR: store <4 x i32> %7, ptr %2, align 16
829 end subroutine vec_xl_be_testi32a
831 ! CHECK-LABEL: @vec_xl_be_testi64a
832 subroutine vec_xl_be_testi64a(arg1, arg2, res)
833 integer(8) :: arg1
834 integer(8) :: arg2(2, 4, 8)
835 vector(integer(8)) :: res
836 res = vec_xl_be(arg1, arg2)
838 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
839 ! FIR: %[[ref:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x4x8xi64>>) -> !fir.ref<!fir.array<?xi8>>
840 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[ref]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
841 ! FIR: %[[ref2:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
842 ! FIR: %[[undefv:.*]] = fir.undefined vector<2xi64>
843 ! FIR: %[[shflv:.*]] = vector.shuffle %[[ref2]], %[[undefv]] [1, 0] : vector<2xi64>, vector<2xi64>
844 ! FIR: %[[res:.*]] = fir.convert %[[shflv]] : (vector<2xi64>) -> !fir.vector<2:i64>
845 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<2:i64>>
847 ! LLVMIR: %4 = load i64, ptr %0, align 8
848 ! LLVMIR: %5 = getelementptr i8, ptr %1, i64 %4
849 ! LLVMIR: %6 = load <2 x i64>, ptr %5, align 1
850 ! LLVMIR: %7 = shufflevector <2 x i64> %6, <2 x i64> undef, <2 x i32> <i32 1, i32 0>
851 ! LLVMIR: store <2 x i64> %7, ptr %2, align 16
852 end subroutine vec_xl_be_testi64a
854 ! CHECK-LABEL: @vec_xl_be_testf32a
855 subroutine vec_xl_be_testf32a(arg1, arg2, res)
856 integer(2) :: arg1
857 real(4) :: arg2(4)
858 vector(real(4)) :: res
859 res = vec_xl_be(arg1, arg2)
861 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
862 ! FIR: %[[ref:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4xf32>>) -> !fir.ref<!fir.array<?xi8>>
863 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[ref]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
864 ! FIR: %[[ref2:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
865 ! FIR: %[[undefv:.*]] = fir.undefined vector<4xf32>
866 ! FIR: %[[shflv:.*]] = vector.shuffle %[[ref2]], %[[undefv]] [3, 2, 1, 0] : vector<4xf32>, vector<4xf32>
867 ! FIR: %[[res:.*]] = fir.convert %[[shflv]] : (vector<4xf32>) -> !fir.vector<4:f32>
868 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:f32>>
870 ! LLVMIR: %4 = load i16, ptr %0, align 2
871 ! LLVMIR: %5 = getelementptr i8, ptr %1, i16 %4
872 ! LLVMIR: %6 = load <4 x float>, ptr %5, align 1
873 ! LLVMIR: %7 = shufflevector <4 x float> %6, <4 x float> undef, <4 x i32> <i32 3, i32 2, i32 1, i32 0>
874 ! LLVMIR: store <4 x float> %7, ptr %2, align 16
875 end subroutine vec_xl_be_testf32a
877 ! CHECK-LABEL: @vec_xl_be_testf64a
878 subroutine vec_xl_be_testf64a(arg1, arg2, res)
879 integer(8) :: arg1
880 real(8) :: arg2(4)
881 vector(real(8)) :: res
882 res = vec_xl_be(arg1, arg2)
884 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
885 ! FIR: %[[ref:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4xf64>>) -> !fir.ref<!fir.array<?xi8>>
886 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[ref]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
887 ! FIR: %[[ref2:.*]] = fir.load %[[addr]] {alignment = 1 : i64} : !fir.ref<!fir.array<?xi8>>
888 ! FIR: %[[undefv:.*]] = fir.undefined vector<2xf64>
889 ! FIR: %[[shflv:.*]] = vector.shuffle %[[ref2]], %[[undefv]] [1, 0] : vector<2xf64>, vector<2xf64>
890 ! FIR: %[[res:.*]] = fir.convert %[[shflv]] : (vector<2xf64>) -> !fir.vector<2:f64>
891 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<2:f64>>
893 ! LLVMIR: %4 = load i64, ptr %0, align 8
894 ! LLVMIR: %5 = getelementptr i8, ptr %1, i64 %4
895 ! LLVMIR: %6 = load <2 x double>, ptr %5, align 1
896 ! LLVMIR: %7 = shufflevector <2 x double> %6, <2 x double> undef, <2 x i32> <i32 1, i32 0>
897 ! LLVMIR: store <2 x double> %7, ptr %2, align 16
898 end subroutine vec_xl_be_testf64a
900 !-------------------
901 ! vec_xld2
902 !-------------------
904 ! CHECK-LABEL: @vec_xld2_testi8a
905 subroutine vec_xld2_testi8a(arg1, arg2, res)
906 integer(1) :: arg1
907 vector(integer(1)) :: arg2(4)
908 vector(integer(1)) :: res
909 res = vec_xld2(arg1, arg2)
911 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i8>
912 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4x!fir.vector<16:i8>>>) -> !fir.ref<!fir.array<?xi8>>
913 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i8) -> !fir.ref<!fir.array<?xi8>>
914 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvd2x.be(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<2xf64>
915 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<2xf64> to vector<16xi8>
916 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<16xi8>) -> !fir.vector<16:i8>
917 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:i8>>
919 ! LLVMIR: %[[arg1:.*]] = load i8, ptr %0, align 1
920 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i8 %[[arg1]]
921 ! LLVMIR: %[[ld:.*]] = call contract <2 x double> @llvm.ppc.vsx.lxvd2x.be(ptr %[[addr]])
922 ! LLVMIR: %[[bc:.*]] = bitcast <2 x double> %[[ld]] to <16 x i8>
923 ! LLVMIR: store <16 x i8> %[[bc]], ptr %2, align 16
924 end subroutine vec_xld2_testi8a
926 ! CHECK-LABEL: @vec_xld2_testi16a
927 subroutine vec_xld2_testi16a(arg1, arg2, res)
928 integer(2) :: arg1
929 vector(integer(2)) :: arg2(4)
930 vector(integer(2)) :: res
931 res = vec_xld2(arg1, arg2)
933 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
934 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4x!fir.vector<8:i16>>>) -> !fir.ref<!fir.array<?xi8>>
935 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
936 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvd2x.be(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<2xf64>
937 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<2xf64> to vector<8xi16>
938 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<8xi16>) -> !fir.vector<8:i16>
939 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<8:i16>>
941 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
942 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[arg1]]
943 ! LLVMIR: %[[ld:.*]] = call contract <2 x double> @llvm.ppc.vsx.lxvd2x.be(ptr %[[addr]])
944 ! LLVMIR: %[[bc:.*]] = bitcast <2 x double> %[[ld]] to <8 x i16>
945 ! LLVMIR: store <8 x i16> %[[bc]], ptr %2, align 16
946 end subroutine vec_xld2_testi16a
948 ! CHECK-LABEL: @vec_xld2_testi32a
949 subroutine vec_xld2_testi32a(arg1, arg2, res)
950 integer(4) :: arg1
951 vector(integer(4)) :: arg2(11)
952 vector(integer(4)) :: res
953 res = vec_xld2(arg1, arg2)
955 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i32>
956 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<11x!fir.vector<4:i32>>>) -> !fir.ref<!fir.array<?xi8>>
957 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
958 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvd2x.be(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<2xf64>
959 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<2xf64> to vector<4xi32>
960 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<4xi32>) -> !fir.vector<4:i32>
961 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:i32>>
963 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
964 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1]]
965 ! LLVMIR: %[[ld:.*]] = call contract <2 x double> @llvm.ppc.vsx.lxvd2x.be(ptr %[[addr]])
966 ! LLVMIR: %[[bc:.*]] = bitcast <2 x double> %[[ld]] to <4 x i32>
967 ! LLVMIR: store <4 x i32> %[[bc]], ptr %2, align 16
968 end subroutine vec_xld2_testi32a
970 ! CHECK-LABEL: @vec_xld2_testi64a
971 subroutine vec_xld2_testi64a(arg1, arg2, res)
972 integer(8) :: arg1
973 vector(integer(8)) :: arg2(31,7)
974 vector(integer(8)) :: res
975 res = vec_xld2(arg1, arg2)
977 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
978 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<31x7x!fir.vector<2:i64>>>) -> !fir.ref<!fir.array<?xi8>>
979 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
980 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvd2x.be(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<2xf64>
981 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<2xf64> to vector<2xi64>
982 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<2xi64>) -> !fir.vector<2:i64>
983 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<2:i64>>
985 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
986 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[arg1]]
987 ! LLVMIR: %[[ld:.*]] = call contract <2 x double> @llvm.ppc.vsx.lxvd2x.be(ptr %[[addr]])
988 ! LLVMIR: %[[bc:.*]] = bitcast <2 x double> %[[ld]] to <2 x i64>
989 ! LLVMIR: store <2 x i64> %[[bc]], ptr %2, align 16
990 end subroutine vec_xld2_testi64a
992 ! CHECK-LABEL: @vec_xld2_testf32a
993 subroutine vec_xld2_testf32a(arg1, arg2, res)
994 integer(2) :: arg1
995 vector(real(4)) :: arg2(5)
996 vector(real(4)) :: res
997 res = vec_xld2(arg1, arg2)
999 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
1000 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<5x!fir.vector<4:f32>>>) -> !fir.ref<!fir.array<?xi8>>
1001 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
1002 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvd2x.be(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<2xf64>
1003 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<2xf64> to vector<4xf32>
1004 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<4xf32>) -> !fir.vector<4:f32>
1005 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:f32>>
1007 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
1008 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[arg1]]
1009 ! LLVMIR: %[[ld:.*]] = call contract <2 x double> @llvm.ppc.vsx.lxvd2x.be(ptr %[[addr]])
1010 ! LLVMIR: %[[bc:.*]] = bitcast <2 x double> %[[ld]] to <4 x float>
1011 ! LLVMIR: store <4 x float> %[[bc]], ptr %2, align 16
1012 end subroutine vec_xld2_testf32a
1014 ! CHECK-LABEL: @vec_xld2_testf64a
1015 subroutine vec_xld2_testf64a(arg1, arg2, res)
1016 integer(8) :: arg1
1017 vector(real(8)) :: arg2(4)
1018 vector(real(8)) :: res
1019 res = vec_xld2(arg1, arg2)
1021 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
1022 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4x!fir.vector<2:f64>>>) -> !fir.ref<!fir.array<?xi8>>
1023 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
1024 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvd2x.be(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<2xf64>
1025 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<2xf64>) -> !fir.vector<2:f64>
1026 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<2:f64>>
1028 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
1029 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[arg1]]
1030 ! LLVMIR: %[[ld:.*]] = call contract <2 x double> @llvm.ppc.vsx.lxvd2x.be(ptr %[[addr]])
1031 ! LLVMIR: store <2 x double> %[[ld]], ptr %2, align 16
1032 end subroutine vec_xld2_testf64a
1034 !-------------------
1035 ! vec_xlw4
1036 !-------------------
1038 ! CHECK-LABEL: @vec_xlw4_testi8a
1039 subroutine vec_xlw4_testi8a(arg1, arg2, res)
1040 integer(1) :: arg1
1041 vector(integer(1)) :: arg2(2, 11, 37)
1042 vector(integer(1)) :: res
1043 res = vec_xlw4(arg1, arg2)
1045 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i8>
1046 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x11x37x!fir.vector<16:i8>>>) -> !fir.ref<!fir.array<?xi8>>
1047 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i8) -> !fir.ref<!fir.array<?xi8>>
1048 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvw4x.be(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
1049 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<4xi32> to vector<16xi8>
1050 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<16xi8>) -> !fir.vector<16:i8>
1051 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<16:i8>>
1053 ! LLVMIR: %[[arg1:.*]] = load i8, ptr %0, align 1
1054 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i8 %[[arg1]]
1055 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.vsx.lxvw4x.be(ptr %[[addr]])
1056 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[ld]] to <16 x i8>
1057 ! LLVMIR: store <16 x i8> %[[bc]], ptr %2, align 16
1058 end subroutine vec_xlw4_testi8a
1060 ! CHECK-LABEL: @vec_xlw4_testi16a
1061 subroutine vec_xlw4_testi16a(arg1, arg2, res)
1062 integer(2) :: arg1
1063 vector(integer(2)) :: arg2(2, 8)
1064 vector(integer(2)) :: res
1065 res = vec_xlw4(arg1, arg2)
1067 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
1068 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<2x8x!fir.vector<8:i16>>>) -> !fir.ref<!fir.array<?xi8>>
1069 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
1070 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvw4x.be(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
1071 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<4xi32> to vector<8xi16>
1072 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<8xi16>) -> !fir.vector<8:i16>
1073 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<8:i16>>
1075 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
1076 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[arg1]]
1077 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.vsx.lxvw4x.be(ptr %[[addr]])
1078 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[ld]] to <8 x i16>
1079 ! LLVMIR: store <8 x i16> %[[bc]], ptr %2, align 16
1080 end subroutine vec_xlw4_testi16a
1082 ! CHECK-LABEL: @vec_xlw4_testu32a
1083 subroutine vec_xlw4_testu32a(arg1, arg2, res)
1084 integer(4) :: arg1
1085 vector(unsigned(4)) :: arg2(8, 4)
1086 vector(unsigned(4)) :: res
1087 res = vec_xlw4(arg1, arg2)
1089 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i32>
1090 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<8x4x!fir.vector<4:ui32>>>) -> !fir.ref<!fir.array<?xi8>>
1091 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i32) -> !fir.ref<!fir.array<?xi8>>
1092 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvw4x.be(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
1093 ! FIR: %[[res:.*]] = fir.convert %[[ld]] : (vector<4xi32>) -> !fir.vector<4:ui32>
1094 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:ui32>>
1096 ! LLVMIR: %[[arg1:.*]] = load i32, ptr %0, align 4
1097 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i32 %[[arg1]]
1098 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.vsx.lxvw4x.be(ptr %[[addr]])
1099 ! LLVMIR: store <4 x i32> %[[ld]], ptr %2, align 16
1100 end subroutine vec_xlw4_testu32a
1102 ! CHECK-LABEL: @vec_xlw4_testf32a
1103 subroutine vec_xlw4_testf32a(arg1, arg2, res)
1104 integer(2) :: arg1
1105 vector(real(4)) :: arg2
1106 vector(real(4)) :: res
1107 res = vec_xlw4(arg1, arg2)
1109 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i16>
1110 ! FIR: %[[arg2:.*]] = fir.convert %arg1 : (!fir.ref<!fir.vector<4:f32>>) -> !fir.ref<!fir.array<?xi8>>
1111 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[arg2]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i16) -> !fir.ref<!fir.array<?xi8>>
1112 ! FIR: %[[ld:.*]] = fir.call @llvm.ppc.vsx.lxvw4x.be(%[[addr]]) fastmath<contract> : (!fir.ref<!fir.array<?xi8>>) -> vector<4xi32>
1113 ! FIR: %[[bc:.*]] = vector.bitcast %[[ld]] : vector<4xi32> to vector<4xf32>
1114 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<4xf32>) -> !fir.vector<4:f32>
1115 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<4:f32>>
1117 ! LLVMIR: %[[arg1:.*]] = load i16, ptr %0, align 2
1118 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i16 %[[arg1]]
1119 ! LLVMIR: %[[ld:.*]] = call <4 x i32> @llvm.ppc.vsx.lxvw4x.be(ptr %[[addr]])
1120 ! LLVMIR: %[[bc:.*]] = bitcast <4 x i32> %[[ld]] to <4 x float>
1121 ! LLVMIR: store <4 x float> %[[bc]], ptr %2, align 16
1122 end subroutine vec_xlw4_testf32a
1124 !-------------------
1125 ! vec_xlds
1126 !-------------------
1128 ! CHECK-LABEL: @vec_xlds_testi64a
1129 subroutine vec_xlds_testi64a(arg1, arg2, res)
1130 integer(8) :: arg1
1131 vector(integer(8)) :: arg2(4)
1132 vector(integer(8)) :: res
1133 res = vec_xlds(arg1, arg2)
1135 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
1136 ! FIR: %[[aryref:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4x!fir.vector<2:i64>>>) -> !fir.ref<!fir.array<?xi8>>
1137 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[aryref]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
1138 ! FIR: %[[ref:.*]] = fir.convert %[[addr]] : (!fir.ref<!fir.array<?xi8>>) -> !fir.ref<i64>
1139 ! FIR: %[[val:.*]] = fir.load %[[ref]] : !fir.ref<i64>
1140 ! FIR: %[[vsplt:.*]] = vector.splat %[[val]] : vector<2xi64>
1141 ! FIR: %[[res:.*]] = fir.convert %[[vsplt]] : (vector<2xi64>) -> !fir.vector<2:i64>
1142 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<2:i64>>
1144 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
1145 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[arg1]]
1146 ! LLVMIR: %[[ld:.*]] = load i64, ptr %[[addr]], align 8
1147 ! LLVMIR: %[[insrt:.*]] = insertelement <2 x i64> undef, i64 %[[ld]], i32 0
1148 ! LLVMIR: %[[shflv:.*]] = shufflevector <2 x i64> %[[insrt]], <2 x i64> undef, <2 x i32> zeroinitializer
1149 ! LLVMIR: store <2 x i64> %[[shflv]], ptr %2, align 16
1150 end subroutine vec_xlds_testi64a
1152 ! CHECK-LABEL: @vec_xlds_testf64a
1153 subroutine vec_xlds_testf64a(arg1, arg2, res)
1154 integer(8) :: arg1
1155 vector(real(8)) :: arg2(4)
1156 vector(real(8)) :: res
1157 res = vec_xlds(arg1, arg2)
1159 ! FIR: %[[arg1:.*]] = fir.load %arg0 : !fir.ref<i64>
1160 ! FIR: %[[aryref:.*]] = fir.convert %arg1 : (!fir.ref<!fir.array<4x!fir.vector<2:f64>>>) -> !fir.ref<!fir.array<?xi8>>
1161 ! FIR: %[[addr:.*]] = fir.coordinate_of %[[aryref]], %[[arg1]] : (!fir.ref<!fir.array<?xi8>>, i64) -> !fir.ref<!fir.array<?xi8>>
1162 ! FIR: %[[ref:.*]] = fir.convert %[[addr]] : (!fir.ref<!fir.array<?xi8>>) -> !fir.ref<i64>
1163 ! FIR: %[[val:.*]] = fir.load %[[ref]] : !fir.ref<i64>
1164 ! FIR: %[[vsplt:.*]] = vector.splat %[[val]] : vector<2xi64>
1165 ! FIR: %[[bc:.*]] = vector.bitcast %[[vsplt]] : vector<2xi64> to vector<2xf64>
1166 ! FIR: %[[res:.*]] = fir.convert %[[bc]] : (vector<2xf64>) -> !fir.vector<2:f64>
1167 ! FIR: fir.store %[[res]] to %arg2 : !fir.ref<!fir.vector<2:f64>>
1169 ! LLVMIR: %[[arg1:.*]] = load i64, ptr %0, align 8
1170 ! LLVMIR: %[[addr:.*]] = getelementptr i8, ptr %1, i64 %[[arg1]]
1171 ! LLVMIR: %[[ld:.*]] = load i64, ptr %[[addr]], align 8
1172 ! LLVMIR: %[[insrt:.*]] = insertelement <2 x i64> undef, i64 %[[ld]], i32 0
1173 ! LLVMIR: %[[shflv:.*]] = shufflevector <2 x i64> %[[insrt]], <2 x i64> undef, <2 x i32> zeroinitializer
1174 ! LLVMIR: %[[bc:.*]] = bitcast <2 x i64> %[[shflv]] to <2 x double>
1175 ! LLVMIR: store <2 x double> %[[bc]], ptr %2, align 16
1176 end subroutine vec_xlds_testf64a