Begin to support some vector operations for AVX 256-bit intructions. The long
[oota-llvm.git] / lib / Target / X86 / X86InstrSSE.td
1 //====- X86InstrSSE.td - Describe the X86 Instruction Set --*- tablegen -*-===//
2 //
3 //                     The LLVM Compiler Infrastructure
4 //
5 // This file is distributed under the University of Illinois Open Source
6 // License. See LICENSE.TXT for details.
7 //
8 //===----------------------------------------------------------------------===//
9 //
10 // This file describes the X86 SSE instruction set, defining the instructions,
11 // and properties of the instructions which are needed for code generation,
12 // machine code emission, and analysis.
13 //
14 //===----------------------------------------------------------------------===//
15
16
17 //===----------------------------------------------------------------------===//
18 // SSE scalar FP Instructions
19 //===----------------------------------------------------------------------===//
20
21 // CMOV* - Used to implement the SSE SELECT DAG operation.  Expanded after
22 // instruction selection into a branch sequence.
23 let Uses = [EFLAGS], usesCustomInserter = 1 in {
24   def CMOV_FR32 : I<0, Pseudo,
25                     (outs FR32:$dst), (ins FR32:$t, FR32:$f, i8imm:$cond),
26                     "#CMOV_FR32 PSEUDO!",
27                     [(set FR32:$dst, (X86cmov FR32:$t, FR32:$f, imm:$cond,
28                                                   EFLAGS))]>;
29   def CMOV_FR64 : I<0, Pseudo,
30                     (outs FR64:$dst), (ins FR64:$t, FR64:$f, i8imm:$cond),
31                     "#CMOV_FR64 PSEUDO!",
32                     [(set FR64:$dst, (X86cmov FR64:$t, FR64:$f, imm:$cond,
33                                                   EFLAGS))]>;
34   def CMOV_V4F32 : I<0, Pseudo,
35                     (outs VR128:$dst), (ins VR128:$t, VR128:$f, i8imm:$cond),
36                     "#CMOV_V4F32 PSEUDO!",
37                     [(set VR128:$dst,
38                       (v4f32 (X86cmov VR128:$t, VR128:$f, imm:$cond,
39                                           EFLAGS)))]>;
40   def CMOV_V2F64 : I<0, Pseudo,
41                     (outs VR128:$dst), (ins VR128:$t, VR128:$f, i8imm:$cond),
42                     "#CMOV_V2F64 PSEUDO!",
43                     [(set VR128:$dst,
44                       (v2f64 (X86cmov VR128:$t, VR128:$f, imm:$cond,
45                                           EFLAGS)))]>;
46   def CMOV_V2I64 : I<0, Pseudo,
47                     (outs VR128:$dst), (ins VR128:$t, VR128:$f, i8imm:$cond),
48                     "#CMOV_V2I64 PSEUDO!",
49                     [(set VR128:$dst,
50                       (v2i64 (X86cmov VR128:$t, VR128:$f, imm:$cond,
51                                           EFLAGS)))]>;
52 }
53
54 //===----------------------------------------------------------------------===//
55 // SSE 1 & 2 Instructions Classes
56 //===----------------------------------------------------------------------===//
57
58 /// sse12_fp_scalar - SSE 1 & 2 scalar instructions class
59 multiclass sse12_fp_scalar<bits<8> opc, string OpcodeStr, SDNode OpNode,
60                            RegisterClass RC, X86MemOperand x86memop,
61                            bit Is2Addr = 1> {
62   let isCommutable = 1 in {
63     def rr : SI<opc, MRMSrcReg, (outs RC:$dst), (ins RC:$src1, RC:$src2),
64        !if(Is2Addr,
65            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
66            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
67        [(set RC:$dst, (OpNode RC:$src1, RC:$src2))]>;
68   }
69   def rm : SI<opc, MRMSrcMem, (outs RC:$dst), (ins RC:$src1, x86memop:$src2),
70        !if(Is2Addr,
71            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
72            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
73        [(set RC:$dst, (OpNode RC:$src1, (load addr:$src2)))]>;
74 }
75
76 /// sse12_fp_scalar_int - SSE 1 & 2 scalar instructions intrinsics class
77 multiclass sse12_fp_scalar_int<bits<8> opc, string OpcodeStr, RegisterClass RC,
78                              string asm, string SSEVer, string FPSizeStr,
79                              Operand memopr, ComplexPattern mem_cpat,
80                              bit Is2Addr = 1> {
81   def rr_Int : SI<opc, MRMSrcReg, (outs RC:$dst), (ins RC:$src1, RC:$src2),
82        !if(Is2Addr,
83            !strconcat(asm, "\t{$src2, $dst|$dst, $src2}"),
84            !strconcat(asm, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
85        [(set RC:$dst, (!nameconcat<Intrinsic>("int_x86_sse",
86                        !strconcat(SSEVer, !strconcat("_",
87                        !strconcat(OpcodeStr, FPSizeStr))))
88              RC:$src1, RC:$src2))]>;
89   def rm_Int : SI<opc, MRMSrcMem, (outs RC:$dst), (ins RC:$src1, memopr:$src2),
90        !if(Is2Addr,
91            !strconcat(asm, "\t{$src2, $dst|$dst, $src2}"),
92            !strconcat(asm, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
93        [(set RC:$dst, (!nameconcat<Intrinsic>("int_x86_sse",
94                        !strconcat(SSEVer, !strconcat("_",
95                        !strconcat(OpcodeStr, FPSizeStr))))
96              RC:$src1, mem_cpat:$src2))]>;
97 }
98
99 /// sse12_fp_packed - SSE 1 & 2 packed instructions class
100 multiclass sse12_fp_packed<bits<8> opc, string OpcodeStr, SDNode OpNode,
101                            RegisterClass RC, ValueType vt,
102                            X86MemOperand x86memop, PatFrag mem_frag,
103                            Domain d, bit Is2Addr = 1> {
104   let isCommutable = 1 in
105     def rr : PI<opc, MRMSrcReg, (outs RC:$dst), (ins RC:$src1, RC:$src2),
106        !if(Is2Addr,
107            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
108            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
109        [(set RC:$dst, (vt (OpNode RC:$src1, RC:$src2)))], d>;
110   let mayLoad = 1 in
111     def rm : PI<opc, MRMSrcMem, (outs RC:$dst), (ins RC:$src1, x86memop:$src2),
112        !if(Is2Addr,
113            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
114            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
115        [(set RC:$dst, (OpNode RC:$src1, (mem_frag addr:$src2)))], d>;
116 }
117
118 /// sse12_fp_packed_logical_rm - SSE 1 & 2 packed instructions class
119 multiclass sse12_fp_packed_logical_rm<bits<8> opc, RegisterClass RC, Domain d,
120                                       string OpcodeStr, X86MemOperand x86memop,
121                                       list<dag> pat_rr, list<dag> pat_rm,
122                                       bit Is2Addr = 1> {
123   let isCommutable = 1 in
124     def rr : PI<opc, MRMSrcReg, (outs RC:$dst), (ins RC:$src1, RC:$src2),
125        !if(Is2Addr,
126            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
127            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
128        pat_rr, d>;
129   def rm : PI<opc, MRMSrcMem, (outs RC:$dst), (ins RC:$src1, x86memop:$src2),
130        !if(Is2Addr,
131            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
132            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
133        pat_rm, d>;
134 }
135
136 /// sse12_fp_packed_int - SSE 1 & 2 packed instructions intrinsics class
137 multiclass sse12_fp_packed_int<bits<8> opc, string OpcodeStr, RegisterClass RC,
138                            string asm, string SSEVer, string FPSizeStr,
139                            X86MemOperand x86memop, PatFrag mem_frag,
140                            Domain d, bit Is2Addr = 1> {
141   def rr_Int : PI<opc, MRMSrcReg, (outs RC:$dst), (ins RC:$src1, RC:$src2),
142        !if(Is2Addr,
143            !strconcat(asm, "\t{$src2, $dst|$dst, $src2}"),
144            !strconcat(asm, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
145            [(set RC:$dst, (!nameconcat<Intrinsic>("int_x86_",
146                            !strconcat(SSEVer, !strconcat("_",
147                            !strconcat(OpcodeStr, FPSizeStr))))
148                  RC:$src1, RC:$src2))], d>;
149   def rm_Int : PI<opc, MRMSrcMem, (outs RC:$dst), (ins RC:$src1,x86memop:$src2),
150        !if(Is2Addr,
151            !strconcat(asm, "\t{$src2, $dst|$dst, $src2}"),
152            !strconcat(asm, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
153        [(set RC:$dst, (!nameconcat<Intrinsic>("int_x86_",
154                        !strconcat(SSEVer, !strconcat("_",
155                        !strconcat(OpcodeStr, FPSizeStr))))
156              RC:$src1, (mem_frag addr:$src2)))], d>;
157 }
158
159 //===----------------------------------------------------------------------===//
160 // SSE 1 & 2 - Move Instructions
161 //===----------------------------------------------------------------------===//
162
163 class sse12_move_rr<RegisterClass RC, ValueType vt, string asm> :
164       SI<0x10, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src1, RC:$src2), asm,
165       [(set (vt VR128:$dst), (movl VR128:$src1, (scalar_to_vector RC:$src2)))]>;
166
167 // Loading from memory automatically zeroing upper bits.
168 class sse12_move_rm<RegisterClass RC, X86MemOperand x86memop,
169                     PatFrag mem_pat, string OpcodeStr> :
170       SI<0x10, MRMSrcMem, (outs RC:$dst), (ins x86memop:$src),
171          !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"),
172                         [(set RC:$dst, (mem_pat addr:$src))]>;
173
174 // Move Instructions. Register-to-register movss/movsd is not used for FR32/64
175 // register copies because it's a partial register update; FsMOVAPSrr/FsMOVAPDrr
176 // is used instead. Register-to-register movss/movsd is not modeled as an
177 // INSERT_SUBREG because INSERT_SUBREG requires that the insert be implementable
178 // in terms of a copy, and just mentioned, we don't use movss/movsd for copies.
179 let isAsmParserOnly = 1 in {
180   def VMOVSSrr : sse12_move_rr<FR32, v4f32,
181                   "movss\t{$src2, $src1, $dst|$dst, $src1, $src2}">, XS, VEX_4V;
182   def VMOVSDrr : sse12_move_rr<FR64, v2f64,
183                   "movsd\t{$src2, $src1, $dst|$dst, $src1, $src2}">, XD, VEX_4V;
184
185   let canFoldAsLoad = 1, isReMaterializable = 1 in {
186     def VMOVSSrm : sse12_move_rm<FR32, f32mem, loadf32, "movss">, XS, VEX;
187
188     let AddedComplexity = 20 in
189       def VMOVSDrm : sse12_move_rm<FR64, f64mem, loadf64, "movsd">, XD, VEX;
190   }
191 }
192
193 let Constraints = "$src1 = $dst" in {
194   def MOVSSrr : sse12_move_rr<FR32, v4f32,
195                           "movss\t{$src2, $dst|$dst, $src2}">, XS;
196   def MOVSDrr : sse12_move_rr<FR64, v2f64,
197                           "movsd\t{$src2, $dst|$dst, $src2}">, XD;
198 }
199
200 let canFoldAsLoad = 1, isReMaterializable = 1 in {
201   def MOVSSrm : sse12_move_rm<FR32, f32mem, loadf32, "movss">, XS;
202
203   let AddedComplexity = 20 in
204     def MOVSDrm : sse12_move_rm<FR64, f64mem, loadf64, "movsd">, XD;
205 }
206
207 let AddedComplexity = 15 in {
208 // Extract the low 32-bit value from one vector and insert it into another.
209 def : Pat<(v4f32 (movl VR128:$src1, VR128:$src2)),
210           (MOVSSrr (v4f32 VR128:$src1),
211                    (EXTRACT_SUBREG (v4f32 VR128:$src2), sub_ss))>;
212 // Extract the low 64-bit value from one vector and insert it into another.
213 def : Pat<(v2f64 (movl VR128:$src1, VR128:$src2)),
214           (MOVSDrr (v2f64 VR128:$src1),
215                    (EXTRACT_SUBREG (v2f64 VR128:$src2), sub_sd))>;
216 }
217
218 // Implicitly promote a 32-bit scalar to a vector.
219 def : Pat<(v4f32 (scalar_to_vector FR32:$src)),
220           (INSERT_SUBREG (v4f32 (IMPLICIT_DEF)), FR32:$src, sub_ss)>;
221 // Implicitly promote a 64-bit scalar to a vector.
222 def : Pat<(v2f64 (scalar_to_vector FR64:$src)),
223           (INSERT_SUBREG (v2f64 (IMPLICIT_DEF)), FR64:$src, sub_sd)>;
224
225 let AddedComplexity = 20 in {
226 // MOVSSrm zeros the high parts of the register; represent this
227 // with SUBREG_TO_REG.
228 def : Pat<(v4f32 (X86vzmovl (v4f32 (scalar_to_vector (loadf32 addr:$src))))),
229           (SUBREG_TO_REG (i32 0), (MOVSSrm addr:$src), sub_ss)>;
230 def : Pat<(v4f32 (scalar_to_vector (loadf32 addr:$src))),
231           (SUBREG_TO_REG (i32 0), (MOVSSrm addr:$src), sub_ss)>;
232 def : Pat<(v4f32 (X86vzmovl (loadv4f32 addr:$src))),
233           (SUBREG_TO_REG (i32 0), (MOVSSrm addr:$src), sub_ss)>;
234 // MOVSDrm zeros the high parts of the register; represent this
235 // with SUBREG_TO_REG.
236 def : Pat<(v2f64 (X86vzmovl (v2f64 (scalar_to_vector (loadf64 addr:$src))))),
237           (SUBREG_TO_REG (i64 0), (MOVSDrm addr:$src), sub_sd)>;
238 def : Pat<(v2f64 (scalar_to_vector (loadf64 addr:$src))),
239           (SUBREG_TO_REG (i64 0), (MOVSDrm addr:$src), sub_sd)>;
240 def : Pat<(v2f64 (X86vzmovl (loadv2f64 addr:$src))),
241           (SUBREG_TO_REG (i64 0), (MOVSDrm addr:$src), sub_sd)>;
242 def : Pat<(v2f64 (X86vzmovl (bc_v2f64 (loadv4f32 addr:$src)))),
243           (SUBREG_TO_REG (i64 0), (MOVSDrm addr:$src), sub_sd)>;
244 def : Pat<(v2f64 (X86vzload addr:$src)),
245           (SUBREG_TO_REG (i64 0), (MOVSDrm addr:$src), sub_sd)>;
246 }
247
248 // Store scalar value to memory.
249 def MOVSSmr : SSI<0x11, MRMDestMem, (outs), (ins f32mem:$dst, FR32:$src),
250                   "movss\t{$src, $dst|$dst, $src}",
251                   [(store FR32:$src, addr:$dst)]>;
252 def MOVSDmr : SDI<0x11, MRMDestMem, (outs), (ins f64mem:$dst, FR64:$src),
253                   "movsd\t{$src, $dst|$dst, $src}",
254                   [(store FR64:$src, addr:$dst)]>;
255
256 let isAsmParserOnly = 1 in {
257 def VMOVSSmr : SI<0x11, MRMDestMem, (outs), (ins f32mem:$dst, FR32:$src),
258                   "movss\t{$src, $dst|$dst, $src}",
259                   [(store FR32:$src, addr:$dst)]>, XS, VEX;
260 def VMOVSDmr : SI<0x11, MRMDestMem, (outs), (ins f64mem:$dst, FR64:$src),
261                   "movsd\t{$src, $dst|$dst, $src}",
262                   [(store FR64:$src, addr:$dst)]>, XD, VEX;
263 }
264
265 // Extract and store.
266 def : Pat<(store (f32 (vector_extract (v4f32 VR128:$src), (iPTR 0))),
267                  addr:$dst),
268           (MOVSSmr addr:$dst,
269                    (EXTRACT_SUBREG (v4f32 VR128:$src), sub_ss))>;
270 def : Pat<(store (f64 (vector_extract (v2f64 VR128:$src), (iPTR 0))),
271                  addr:$dst),
272           (MOVSDmr addr:$dst,
273                    (EXTRACT_SUBREG (v2f64 VR128:$src), sub_sd))>;
274
275 // Move Aligned/Unaligned floating point values
276 multiclass sse12_mov_packed<bits<8> opc, RegisterClass RC,
277                             X86MemOperand x86memop, PatFrag ld_frag,
278                             string asm, Domain d,
279                             bit IsReMaterializable = 1> {
280 let neverHasSideEffects = 1 in
281   def rr : PI<opc, MRMSrcReg, (outs RC:$dst), (ins RC:$src),
282               !strconcat(asm, "\t{$src, $dst|$dst, $src}"), [], d>;
283 let canFoldAsLoad = 1, isReMaterializable = IsReMaterializable in
284   def rm : PI<opc, MRMSrcMem, (outs RC:$dst), (ins x86memop:$src),
285               !strconcat(asm, "\t{$src, $dst|$dst, $src}"),
286                    [(set RC:$dst, (ld_frag addr:$src))], d>;
287 }
288
289 let isAsmParserOnly = 1 in {
290 defm VMOVAPS : sse12_mov_packed<0x28, VR128, f128mem, alignedloadv4f32,
291                               "movaps", SSEPackedSingle>, VEX;
292 defm VMOVAPD : sse12_mov_packed<0x28, VR128, f128mem, alignedloadv2f64,
293                               "movapd", SSEPackedDouble>, OpSize, VEX;
294 defm VMOVUPS : sse12_mov_packed<0x10, VR128, f128mem, loadv4f32,
295                               "movups", SSEPackedSingle>, VEX;
296 defm VMOVUPD : sse12_mov_packed<0x10, VR128, f128mem, loadv2f64,
297                               "movupd", SSEPackedDouble, 0>, OpSize, VEX;
298
299 defm VMOVAPSY : sse12_mov_packed<0x28, VR256, f256mem, alignedloadv8f32,
300                               "movaps", SSEPackedSingle>, VEX;
301 defm VMOVAPDY : sse12_mov_packed<0x28, VR256, f256mem, alignedloadv4f64,
302                               "movapd", SSEPackedDouble>, OpSize, VEX;
303 defm VMOVUPSY : sse12_mov_packed<0x10, VR256, f256mem, loadv8f32,
304                               "movups", SSEPackedSingle>, VEX;
305 defm VMOVUPDY : sse12_mov_packed<0x10, VR256, f256mem, loadv4f64,
306                               "movupd", SSEPackedDouble, 0>, OpSize, VEX;
307 }
308 defm MOVAPS : sse12_mov_packed<0x28, VR128, f128mem, alignedloadv4f32,
309                               "movaps", SSEPackedSingle>, TB;
310 defm MOVAPD : sse12_mov_packed<0x28, VR128, f128mem, alignedloadv2f64,
311                               "movapd", SSEPackedDouble>, TB, OpSize;
312 defm MOVUPS : sse12_mov_packed<0x10, VR128, f128mem, loadv4f32,
313                               "movups", SSEPackedSingle>, TB;
314 defm MOVUPD : sse12_mov_packed<0x10, VR128, f128mem, loadv2f64,
315                               "movupd", SSEPackedDouble, 0>, TB, OpSize;
316
317 let isAsmParserOnly = 1 in {
318 def VMOVAPSmr : VPSI<0x29, MRMDestMem, (outs), (ins f128mem:$dst, VR128:$src),
319                    "movaps\t{$src, $dst|$dst, $src}",
320                    [(alignedstore (v4f32 VR128:$src), addr:$dst)]>, VEX;
321 def VMOVAPDmr : VPDI<0x29, MRMDestMem, (outs), (ins f128mem:$dst, VR128:$src),
322                    "movapd\t{$src, $dst|$dst, $src}",
323                    [(alignedstore (v2f64 VR128:$src), addr:$dst)]>, VEX;
324 def VMOVUPSmr : VPSI<0x11, MRMDestMem, (outs), (ins f128mem:$dst, VR128:$src),
325                    "movups\t{$src, $dst|$dst, $src}",
326                    [(store (v4f32 VR128:$src), addr:$dst)]>, VEX;
327 def VMOVUPDmr : VPDI<0x11, MRMDestMem, (outs), (ins f128mem:$dst, VR128:$src),
328                    "movupd\t{$src, $dst|$dst, $src}",
329                    [(store (v2f64 VR128:$src), addr:$dst)]>, VEX;
330 def VMOVAPSYmr : VPSI<0x29, MRMDestMem, (outs), (ins f256mem:$dst, VR256:$src),
331                    "movaps\t{$src, $dst|$dst, $src}",
332                    [(alignedstore (v8f32 VR256:$src), addr:$dst)]>, VEX;
333 def VMOVAPDYmr : VPDI<0x29, MRMDestMem, (outs), (ins f256mem:$dst, VR256:$src),
334                    "movapd\t{$src, $dst|$dst, $src}",
335                    [(alignedstore (v4f64 VR256:$src), addr:$dst)]>, VEX;
336 def VMOVUPSYmr : VPSI<0x11, MRMDestMem, (outs), (ins f256mem:$dst, VR256:$src),
337                    "movups\t{$src, $dst|$dst, $src}",
338                    [(store (v8f32 VR256:$src), addr:$dst)]>, VEX;
339 def VMOVUPDYmr : VPDI<0x11, MRMDestMem, (outs), (ins f256mem:$dst, VR256:$src),
340                    "movupd\t{$src, $dst|$dst, $src}",
341                    [(store (v4f64 VR256:$src), addr:$dst)]>, VEX;
342 }
343
344 def : Pat<(int_x86_avx_loadu_ps_256 addr:$src), (VMOVUPSYrm addr:$src)>;
345 def : Pat<(int_x86_avx_storeu_ps_256 addr:$dst, VR256:$src),
346           (VMOVUPSYmr addr:$dst, VR256:$src)>;
347
348 def : Pat<(int_x86_avx_loadu_pd_256 addr:$src), (VMOVUPDYrm addr:$src)>;
349 def : Pat<(int_x86_avx_storeu_pd_256 addr:$dst, VR256:$src),
350           (VMOVUPDYmr addr:$dst, VR256:$src)>;
351
352 def MOVAPSmr : PSI<0x29, MRMDestMem, (outs), (ins f128mem:$dst, VR128:$src),
353                    "movaps\t{$src, $dst|$dst, $src}",
354                    [(alignedstore (v4f32 VR128:$src), addr:$dst)]>;
355 def MOVAPDmr : PDI<0x29, MRMDestMem, (outs), (ins f128mem:$dst, VR128:$src),
356                    "movapd\t{$src, $dst|$dst, $src}",
357                    [(alignedstore (v2f64 VR128:$src), addr:$dst)]>;
358 def MOVUPSmr : PSI<0x11, MRMDestMem, (outs), (ins f128mem:$dst, VR128:$src),
359                    "movups\t{$src, $dst|$dst, $src}",
360                    [(store (v4f32 VR128:$src), addr:$dst)]>;
361 def MOVUPDmr : PDI<0x11, MRMDestMem, (outs), (ins f128mem:$dst, VR128:$src),
362                    "movupd\t{$src, $dst|$dst, $src}",
363                    [(store (v2f64 VR128:$src), addr:$dst)]>;
364
365 // Intrinsic forms of MOVUPS/D load and store
366 let isAsmParserOnly = 1 in {
367   let canFoldAsLoad = 1, isReMaterializable = 1 in
368   def VMOVUPSrm_Int : VPSI<0x10, MRMSrcMem, (outs VR128:$dst),
369              (ins f128mem:$src),
370              "movups\t{$src, $dst|$dst, $src}",
371              [(set VR128:$dst, (int_x86_sse_loadu_ps addr:$src))]>, VEX;
372   def VMOVUPDrm_Int : VPDI<0x10, MRMSrcMem, (outs VR128:$dst),
373              (ins f128mem:$src),
374              "movupd\t{$src, $dst|$dst, $src}",
375              [(set VR128:$dst, (int_x86_sse2_loadu_pd addr:$src))]>, VEX;
376   def VMOVUPSmr_Int : VPSI<0x11, MRMDestMem, (outs),
377              (ins f128mem:$dst, VR128:$src),
378              "movups\t{$src, $dst|$dst, $src}",
379              [(int_x86_sse_storeu_ps addr:$dst, VR128:$src)]>, VEX;
380   def VMOVUPDmr_Int : VPDI<0x11, MRMDestMem, (outs),
381              (ins f128mem:$dst, VR128:$src),
382              "movupd\t{$src, $dst|$dst, $src}",
383              [(int_x86_sse2_storeu_pd addr:$dst, VR128:$src)]>, VEX;
384 }
385 let canFoldAsLoad = 1, isReMaterializable = 1 in
386 def MOVUPSrm_Int : PSI<0x10, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
387                        "movups\t{$src, $dst|$dst, $src}",
388                        [(set VR128:$dst, (int_x86_sse_loadu_ps addr:$src))]>;
389 def MOVUPDrm_Int : PDI<0x10, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
390                        "movupd\t{$src, $dst|$dst, $src}",
391                        [(set VR128:$dst, (int_x86_sse2_loadu_pd addr:$src))]>;
392
393 def MOVUPSmr_Int : PSI<0x11, MRMDestMem, (outs), (ins f128mem:$dst, VR128:$src),
394                        "movups\t{$src, $dst|$dst, $src}",
395                        [(int_x86_sse_storeu_ps addr:$dst, VR128:$src)]>;
396 def MOVUPDmr_Int : PDI<0x11, MRMDestMem, (outs), (ins f128mem:$dst, VR128:$src),
397                        "movupd\t{$src, $dst|$dst, $src}",
398                        [(int_x86_sse2_storeu_pd addr:$dst, VR128:$src)]>;
399
400 // Move Low/High packed floating point values
401 multiclass sse12_mov_hilo_packed<bits<8>opc, RegisterClass RC,
402                                  PatFrag mov_frag, string base_opc,
403                                  string asm_opr> {
404   def PSrm : PI<opc, MRMSrcMem,
405          (outs VR128:$dst), (ins VR128:$src1, f64mem:$src2),
406          !strconcat(!strconcat(base_opc,"s"), asm_opr),
407      [(set RC:$dst,
408        (mov_frag RC:$src1,
409               (bc_v4f32 (v2f64 (scalar_to_vector (loadf64 addr:$src2))))))],
410               SSEPackedSingle>, TB;
411
412   def PDrm : PI<opc, MRMSrcMem,
413          (outs RC:$dst), (ins RC:$src1, f64mem:$src2),
414          !strconcat(!strconcat(base_opc,"d"), asm_opr),
415      [(set RC:$dst, (v2f64 (mov_frag RC:$src1,
416                               (scalar_to_vector (loadf64 addr:$src2)))))],
417               SSEPackedDouble>, TB, OpSize;
418 }
419
420 let isAsmParserOnly = 1, AddedComplexity = 20 in {
421   defm VMOVL : sse12_mov_hilo_packed<0x12, VR128, movlp, "movlp",
422                      "\t{$src2, $src1, $dst|$dst, $src1, $src2}">, VEX_4V;
423   defm VMOVH : sse12_mov_hilo_packed<0x16, VR128, movlhps, "movhp",
424                      "\t{$src2, $src1, $dst|$dst, $src1, $src2}">, VEX_4V;
425 }
426 let Constraints = "$src1 = $dst", AddedComplexity = 20 in {
427   defm MOVL : sse12_mov_hilo_packed<0x12, VR128, movlp, "movlp",
428                                    "\t{$src2, $dst|$dst, $src2}">;
429   defm MOVH : sse12_mov_hilo_packed<0x16, VR128, movlhps, "movhp",
430                                    "\t{$src2, $dst|$dst, $src2}">;
431 }
432
433 let isAsmParserOnly = 1 in {
434 def VMOVLPSmr : VPSI<0x13, MRMDestMem, (outs), (ins f64mem:$dst, VR128:$src),
435                    "movlps\t{$src, $dst|$dst, $src}",
436                    [(store (f64 (vector_extract (bc_v2f64 (v4f32 VR128:$src)),
437                                  (iPTR 0))), addr:$dst)]>, VEX;
438 def VMOVLPDmr : VPDI<0x13, MRMDestMem, (outs), (ins f64mem:$dst, VR128:$src),
439                    "movlpd\t{$src, $dst|$dst, $src}",
440                    [(store (f64 (vector_extract (v2f64 VR128:$src),
441                                  (iPTR 0))), addr:$dst)]>, VEX;
442 }
443 def MOVLPSmr : PSI<0x13, MRMDestMem, (outs), (ins f64mem:$dst, VR128:$src),
444                    "movlps\t{$src, $dst|$dst, $src}",
445                    [(store (f64 (vector_extract (bc_v2f64 (v4f32 VR128:$src)),
446                                  (iPTR 0))), addr:$dst)]>;
447 def MOVLPDmr : PDI<0x13, MRMDestMem, (outs), (ins f64mem:$dst, VR128:$src),
448                    "movlpd\t{$src, $dst|$dst, $src}",
449                    [(store (f64 (vector_extract (v2f64 VR128:$src),
450                                  (iPTR 0))), addr:$dst)]>;
451
452 // v2f64 extract element 1 is always custom lowered to unpack high to low
453 // and extract element 0 so the non-store version isn't too horrible.
454 let isAsmParserOnly = 1 in {
455 def VMOVHPSmr : VPSI<0x17, MRMDestMem, (outs), (ins f64mem:$dst, VR128:$src),
456                    "movhps\t{$src, $dst|$dst, $src}",
457                    [(store (f64 (vector_extract
458                                  (unpckh (bc_v2f64 (v4f32 VR128:$src)),
459                                          (undef)), (iPTR 0))), addr:$dst)]>,
460                    VEX;
461 def VMOVHPDmr : VPDI<0x17, MRMDestMem, (outs), (ins f64mem:$dst, VR128:$src),
462                    "movhpd\t{$src, $dst|$dst, $src}",
463                    [(store (f64 (vector_extract
464                                  (v2f64 (unpckh VR128:$src, (undef))),
465                                  (iPTR 0))), addr:$dst)]>,
466                    VEX;
467 }
468 def MOVHPSmr : PSI<0x17, MRMDestMem, (outs), (ins f64mem:$dst, VR128:$src),
469                    "movhps\t{$src, $dst|$dst, $src}",
470                    [(store (f64 (vector_extract
471                                  (unpckh (bc_v2f64 (v4f32 VR128:$src)),
472                                          (undef)), (iPTR 0))), addr:$dst)]>;
473 def MOVHPDmr : PDI<0x17, MRMDestMem, (outs), (ins f64mem:$dst, VR128:$src),
474                    "movhpd\t{$src, $dst|$dst, $src}",
475                    [(store (f64 (vector_extract
476                                  (v2f64 (unpckh VR128:$src, (undef))),
477                                  (iPTR 0))), addr:$dst)]>;
478
479 let isAsmParserOnly = 1, AddedComplexity = 20 in {
480   def VMOVLHPSrr : VPSI<0x16, MRMSrcReg, (outs VR128:$dst),
481                                        (ins VR128:$src1, VR128:$src2),
482                       "movlhps\t{$src2, $src1, $dst|$dst, $src1, $src2}",
483                       [(set VR128:$dst,
484                         (v4f32 (movlhps VR128:$src1, VR128:$src2)))]>,
485                       VEX_4V;
486   def VMOVHLPSrr : VPSI<0x12, MRMSrcReg, (outs VR128:$dst),
487                                        (ins VR128:$src1, VR128:$src2),
488                       "movhlps\t{$src2, $src1, $dst|$dst, $src1, $src2}",
489                       [(set VR128:$dst,
490                         (v4f32 (movhlps VR128:$src1, VR128:$src2)))]>,
491                       VEX_4V;
492 }
493 let Constraints = "$src1 = $dst", AddedComplexity = 20 in {
494   def MOVLHPSrr : PSI<0x16, MRMSrcReg, (outs VR128:$dst),
495                                        (ins VR128:$src1, VR128:$src2),
496                       "movlhps\t{$src2, $dst|$dst, $src2}",
497                       [(set VR128:$dst,
498                         (v4f32 (movlhps VR128:$src1, VR128:$src2)))]>;
499   def MOVHLPSrr : PSI<0x12, MRMSrcReg, (outs VR128:$dst),
500                                        (ins VR128:$src1, VR128:$src2),
501                       "movhlps\t{$src2, $dst|$dst, $src2}",
502                       [(set VR128:$dst,
503                         (v4f32 (movhlps VR128:$src1, VR128:$src2)))]>;
504 }
505
506 def : Pat<(movlhps VR128:$src1, (bc_v4i32 (v2i64 (X86vzload addr:$src2)))),
507           (MOVHPSrm (v4i32 VR128:$src1), addr:$src2)>;
508 let AddedComplexity = 20 in {
509   def : Pat<(v4f32 (movddup VR128:$src, (undef))),
510             (MOVLHPSrr (v4f32 VR128:$src), (v4f32 VR128:$src))>;
511   def : Pat<(v2i64 (movddup VR128:$src, (undef))),
512             (MOVLHPSrr (v2i64 VR128:$src), (v2i64 VR128:$src))>;
513 }
514
515 //===----------------------------------------------------------------------===//
516 // SSE 1 & 2 - Conversion Instructions
517 //===----------------------------------------------------------------------===//
518
519 multiclass sse12_cvt_s<bits<8> opc, RegisterClass SrcRC, RegisterClass DstRC,
520                      SDNode OpNode, X86MemOperand x86memop, PatFrag ld_frag,
521                      string asm> {
522   def rr : SI<opc, MRMSrcReg, (outs DstRC:$dst), (ins SrcRC:$src), asm,
523                         [(set DstRC:$dst, (OpNode SrcRC:$src))]>;
524   def rm : SI<opc, MRMSrcMem, (outs DstRC:$dst), (ins x86memop:$src), asm,
525                         [(set DstRC:$dst, (OpNode (ld_frag addr:$src)))]>;
526 }
527
528 multiclass sse12_cvt_s_np<bits<8> opc, RegisterClass SrcRC, RegisterClass DstRC,
529                           X86MemOperand x86memop, string asm> {
530   def rr : SI<opc, MRMSrcReg, (outs DstRC:$dst), (ins SrcRC:$src), asm,
531                         []>;
532   def rm : SI<opc, MRMSrcMem, (outs DstRC:$dst), (ins x86memop:$src), asm,
533                         []>;
534 }
535
536 multiclass sse12_cvt_p<bits<8> opc, RegisterClass SrcRC, RegisterClass DstRC,
537                          SDNode OpNode, X86MemOperand x86memop, PatFrag ld_frag,
538                          string asm, Domain d> {
539   def rr : PI<opc, MRMSrcReg, (outs DstRC:$dst), (ins SrcRC:$src), asm,
540                         [(set DstRC:$dst, (OpNode SrcRC:$src))], d>;
541   def rm : PI<opc, MRMSrcMem, (outs DstRC:$dst), (ins x86memop:$src), asm,
542                         [(set DstRC:$dst, (OpNode (ld_frag addr:$src)))], d>;
543 }
544
545 multiclass sse12_vcvt_avx<bits<8> opc, RegisterClass SrcRC, RegisterClass DstRC,
546                           X86MemOperand x86memop, string asm> {
547   def rr : SI<opc, MRMSrcReg, (outs DstRC:$dst), (ins DstRC:$src1, SrcRC:$src),
548               !strconcat(asm,"\t{$src, $src1, $dst|$dst, $src1, $src}"), []>;
549   def rm : SI<opc, MRMSrcMem, (outs DstRC:$dst),
550               (ins DstRC:$src1, x86memop:$src),
551               !strconcat(asm,"\t{$src, $src1, $dst|$dst, $src1, $src}"), []>;
552 }
553
554 let isAsmParserOnly = 1 in {
555 defm VCVTTSS2SI   : sse12_cvt_s<0x2C, FR32, GR32, fp_to_sint, f32mem, loadf32,
556                                 "cvttss2si\t{$src, $dst|$dst, $src}">, XS, VEX;
557 defm VCVTTSS2SI64 : sse12_cvt_s<0x2C, FR32, GR64, fp_to_sint, f32mem, loadf32,
558                                 "cvttss2si\t{$src, $dst|$dst, $src}">, XS, VEX,
559                                 VEX_W;
560 defm VCVTTSD2SI   : sse12_cvt_s<0x2C, FR64, GR32, fp_to_sint, f64mem, loadf64,
561                                 "cvttsd2si\t{$src, $dst|$dst, $src}">, XD, VEX;
562 defm VCVTTSD2SI64 : sse12_cvt_s<0x2C, FR64, GR64, fp_to_sint, f64mem, loadf64,
563                                 "cvttsd2si\t{$src, $dst|$dst, $src}">, XD,
564                                 VEX, VEX_W;
565
566 // The assembler can recognize rr 64-bit instructions by seeing a rxx
567 // register, but the same isn't true when only using memory operands,
568 // provide other assembly "l" and "q" forms to address this explicitly
569 // where appropriate to do so.
570 defm VCVTSI2SS   : sse12_vcvt_avx<0x2A, GR32, FR32, i32mem, "cvtsi2ss">, XS,
571                                   VEX_4V;
572 defm VCVTSI2SS64 : sse12_vcvt_avx<0x2A, GR64, FR32, i64mem, "cvtsi2ss{q}">, XS,
573                                   VEX_4V, VEX_W;
574 defm VCVTSI2SD   : sse12_vcvt_avx<0x2A, GR32, FR64, i32mem, "cvtsi2sd">, XD,
575                                   VEX_4V;
576 defm VCVTSI2SDL  : sse12_vcvt_avx<0x2A, GR32, FR64, i32mem, "cvtsi2sd{l}">, XD,
577                                   VEX_4V;
578 defm VCVTSI2SD64 : sse12_vcvt_avx<0x2A, GR64, FR64, i64mem, "cvtsi2sd{q}">, XD,
579                                   VEX_4V, VEX_W;
580 }
581
582 defm CVTTSS2SI : sse12_cvt_s<0x2C, FR32, GR32, fp_to_sint, f32mem, loadf32,
583                       "cvttss2si\t{$src, $dst|$dst, $src}">, XS;
584 defm CVTTSS2SI64 : sse12_cvt_s<0x2C, FR32, GR64, fp_to_sint, f32mem, loadf32,
585                       "cvttss2si{q}\t{$src, $dst|$dst, $src}">, XS, REX_W;
586 defm CVTTSD2SI : sse12_cvt_s<0x2C, FR64, GR32, fp_to_sint, f64mem, loadf64,
587                       "cvttsd2si\t{$src, $dst|$dst, $src}">, XD;
588 defm CVTTSD2SI64 : sse12_cvt_s<0x2C, FR64, GR64, fp_to_sint, f64mem, loadf64,
589                       "cvttsd2si{q}\t{$src, $dst|$dst, $src}">, XD, REX_W;
590 defm CVTSI2SS  : sse12_cvt_s<0x2A, GR32, FR32, sint_to_fp, i32mem, loadi32,
591                       "cvtsi2ss\t{$src, $dst|$dst, $src}">, XS;
592 defm CVTSI2SS64 : sse12_cvt_s<0x2A, GR64, FR32, sint_to_fp, i64mem, loadi64,
593                       "cvtsi2ss{q}\t{$src, $dst|$dst, $src}">, XS, REX_W;
594 defm CVTSI2SD  : sse12_cvt_s<0x2A, GR32, FR64, sint_to_fp, i32mem, loadi32,
595                       "cvtsi2sd\t{$src, $dst|$dst, $src}">, XD;
596 defm CVTSI2SD64 : sse12_cvt_s<0x2A, GR64, FR64, sint_to_fp, i64mem, loadi64,
597                       "cvtsi2sd{q}\t{$src, $dst|$dst, $src}">, XD, REX_W;
598
599 // Conversion Instructions Intrinsics - Match intrinsics which expect MM
600 // and/or XMM operand(s).
601 multiclass sse12_cvt_pint<bits<8> opc, RegisterClass SrcRC, RegisterClass DstRC,
602                          Intrinsic Int, X86MemOperand x86memop, PatFrag ld_frag,
603                          string asm, Domain d> {
604   def rr : PI<opc, MRMSrcReg, (outs DstRC:$dst), (ins SrcRC:$src), asm,
605                         [(set DstRC:$dst, (Int SrcRC:$src))], d>;
606   def rm : PI<opc, MRMSrcMem, (outs DstRC:$dst), (ins x86memop:$src), asm,
607                         [(set DstRC:$dst, (Int (ld_frag addr:$src)))], d>;
608 }
609
610 multiclass sse12_cvt_sint<bits<8> opc, RegisterClass SrcRC, RegisterClass DstRC,
611                          Intrinsic Int, X86MemOperand x86memop, PatFrag ld_frag,
612                          string asm> {
613   def rr : SI<opc, MRMSrcReg, (outs DstRC:$dst), (ins SrcRC:$src),
614               !strconcat(asm, "\t{$src, $dst|$dst, $src}"),
615               [(set DstRC:$dst, (Int SrcRC:$src))]>;
616   def rm : SI<opc, MRMSrcMem, (outs DstRC:$dst), (ins x86memop:$src),
617               !strconcat(asm, "\t{$src, $dst|$dst, $src}"),
618               [(set DstRC:$dst, (Int (ld_frag addr:$src)))]>;
619 }
620
621 multiclass sse12_cvt_pint_3addr<bits<8> opc, RegisterClass SrcRC,
622                     RegisterClass DstRC, Intrinsic Int, X86MemOperand x86memop,
623                     PatFrag ld_frag, string asm, Domain d> {
624   def rr : PI<opc, MRMSrcReg, (outs DstRC:$dst), (ins DstRC:$src1, SrcRC:$src2),
625               asm, [(set DstRC:$dst, (Int DstRC:$src1, SrcRC:$src2))], d>;
626   def rm : PI<opc, MRMSrcMem, (outs DstRC:$dst),
627                    (ins DstRC:$src1, x86memop:$src2), asm,
628               [(set DstRC:$dst, (Int DstRC:$src1, (ld_frag addr:$src2)))], d>;
629 }
630
631 multiclass sse12_cvt_sint_3addr<bits<8> opc, RegisterClass SrcRC,
632                     RegisterClass DstRC, Intrinsic Int, X86MemOperand x86memop,
633                     PatFrag ld_frag, string asm, bit Is2Addr = 1> {
634   def rr : SI<opc, MRMSrcReg, (outs DstRC:$dst), (ins DstRC:$src1, SrcRC:$src2),
635               !if(Is2Addr,
636                   !strconcat(asm, "\t{$src2, $dst|$dst, $src2}"),
637                   !strconcat(asm, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
638               [(set DstRC:$dst, (Int DstRC:$src1, SrcRC:$src2))]>;
639   def rm : SI<opc, MRMSrcMem, (outs DstRC:$dst),
640               (ins DstRC:$src1, x86memop:$src2),
641               !if(Is2Addr,
642                   !strconcat(asm, "\t{$src2, $dst|$dst, $src2}"),
643                   !strconcat(asm, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
644               [(set DstRC:$dst, (Int DstRC:$src1, (ld_frag addr:$src2)))]>;
645 }
646
647 let isAsmParserOnly = 1 in {
648   defm Int_VCVTSS2SI : sse12_cvt_sint<0x2D, VR128, GR32, int_x86_sse_cvtss2si,
649                         f32mem, load, "cvtss2si">, XS, VEX;
650   defm Int_VCVTSS2SI64 : sse12_cvt_sint<0x2D, VR128, GR64,
651                           int_x86_sse_cvtss2si64, f32mem, load, "cvtss2si">,
652                           XS, VEX, VEX_W;
653   defm Int_VCVTSD2SI : sse12_cvt_sint<0x2D, VR128, GR32, int_x86_sse2_cvtsd2si,
654                         f128mem, load, "cvtsd2si">, XD, VEX;
655   defm Int_VCVTSD2SI64 : sse12_cvt_sint<0x2D, VR128, GR64,
656                         int_x86_sse2_cvtsd2si64, f128mem, load, "cvtsd2si">,
657                         XD, VEX, VEX_W;
658
659   // FIXME: The asm matcher has a hack to ignore instructions with _Int and Int_
660   // Get rid of this hack or rename the intrinsics, there are several
661   // intructions that only match with the intrinsic form, why create duplicates
662   // to let them be recognized by the assembler?
663   defm VCVTSD2SI_alt : sse12_cvt_s_np<0x2D, FR64, GR32, f64mem,
664                         "cvtsd2si\t{$src, $dst|$dst, $src}">, XD, VEX;
665   defm VCVTSD2SI64   : sse12_cvt_s_np<0x2D, FR64, GR64, f64mem,
666                         "cvtsd2si\t{$src, $dst|$dst, $src}">, XD, VEX, VEX_W;
667 }
668 defm Int_CVTSS2SI : sse12_cvt_sint<0x2D, VR128, GR32, int_x86_sse_cvtss2si,
669                       f32mem, load, "cvtss2si">, XS;
670 defm Int_CVTSS2SI64 : sse12_cvt_sint<0x2D, VR128, GR64, int_x86_sse_cvtss2si64,
671                       f32mem, load, "cvtss2si{q}">, XS, REX_W;
672 defm Int_CVTSD2SI : sse12_cvt_sint<0x2D, VR128, GR32, int_x86_sse2_cvtsd2si,
673                       f128mem, load, "cvtsd2si">, XD;
674 defm Int_CVTSD2SI64 : sse12_cvt_sint<0x2D, VR128, GR64, int_x86_sse2_cvtsd2si64,
675                         f128mem, load, "cvtsd2si">, XD, REX_W;
676
677 defm CVTSD2SI64 : sse12_cvt_s_np<0x2D, VR128, GR64, f64mem, "cvtsd2si{q}">, XD,
678                         REX_W;
679
680 let isAsmParserOnly = 1 in {
681   defm Int_VCVTSI2SS : sse12_cvt_sint_3addr<0x2A, GR32, VR128,
682             int_x86_sse_cvtsi2ss, i32mem, loadi32, "cvtsi2ss", 0>, XS, VEX_4V;
683   defm Int_VCVTSI2SS64 : sse12_cvt_sint_3addr<0x2A, GR64, VR128,
684             int_x86_sse_cvtsi642ss, i64mem, loadi64, "cvtsi2ss", 0>, XS, VEX_4V,
685             VEX_W;
686   defm Int_VCVTSI2SD : sse12_cvt_sint_3addr<0x2A, GR32, VR128,
687             int_x86_sse2_cvtsi2sd, i32mem, loadi32, "cvtsi2sd", 0>, XD, VEX_4V;
688   defm Int_VCVTSI2SD64 : sse12_cvt_sint_3addr<0x2A, GR64, VR128,
689             int_x86_sse2_cvtsi642sd, i64mem, loadi64, "cvtsi2sd", 0>, XD,
690             VEX_4V, VEX_W;
691 }
692
693 let Constraints = "$src1 = $dst" in {
694   defm Int_CVTSI2SS : sse12_cvt_sint_3addr<0x2A, GR32, VR128,
695                         int_x86_sse_cvtsi2ss, i32mem, loadi32,
696                         "cvtsi2ss">, XS;
697   defm Int_CVTSI2SS64 : sse12_cvt_sint_3addr<0x2A, GR64, VR128,
698                         int_x86_sse_cvtsi642ss, i64mem, loadi64,
699                         "cvtsi2ss{q}">, XS, REX_W;
700   defm Int_CVTSI2SD : sse12_cvt_sint_3addr<0x2A, GR32, VR128,
701                         int_x86_sse2_cvtsi2sd, i32mem, loadi32,
702                         "cvtsi2sd">, XD;
703   defm Int_CVTSI2SD64 : sse12_cvt_sint_3addr<0x2A, GR64, VR128,
704                         int_x86_sse2_cvtsi642sd, i64mem, loadi64,
705                         "cvtsi2sd">, XD, REX_W;
706 }
707
708 // Instructions below don't have an AVX form.
709 defm Int_CVTPS2PI : sse12_cvt_pint<0x2D, VR128, VR64, int_x86_sse_cvtps2pi,
710                       f64mem, load, "cvtps2pi\t{$src, $dst|$dst, $src}",
711                       SSEPackedSingle>, TB;
712 defm Int_CVTPD2PI : sse12_cvt_pint<0x2D, VR128, VR64, int_x86_sse_cvtpd2pi,
713                       f128mem, memop, "cvtpd2pi\t{$src, $dst|$dst, $src}",
714                       SSEPackedDouble>, TB, OpSize;
715 defm Int_CVTTPS2PI : sse12_cvt_pint<0x2C, VR128, VR64, int_x86_sse_cvttps2pi,
716                        f64mem, load, "cvttps2pi\t{$src, $dst|$dst, $src}",
717                        SSEPackedSingle>, TB;
718 defm Int_CVTTPD2PI : sse12_cvt_pint<0x2C, VR128, VR64, int_x86_sse_cvttpd2pi,
719                        f128mem, memop, "cvttpd2pi\t{$src, $dst|$dst, $src}",
720                        SSEPackedDouble>, TB, OpSize;
721 defm Int_CVTPI2PD : sse12_cvt_pint<0x2A, VR64, VR128, int_x86_sse_cvtpi2pd,
722                          i64mem, load, "cvtpi2pd\t{$src, $dst|$dst, $src}",
723                          SSEPackedDouble>, TB, OpSize;
724 let Constraints = "$src1 = $dst" in {
725   defm Int_CVTPI2PS : sse12_cvt_pint_3addr<0x2A, VR64, VR128,
726                          int_x86_sse_cvtpi2ps,
727                          i64mem, load, "cvtpi2ps\t{$src2, $dst|$dst, $src2}",
728                          SSEPackedSingle>, TB;
729 }
730
731 /// SSE 1 Only
732
733 // Aliases for intrinsics
734 let isAsmParserOnly = 1 in {
735 defm Int_VCVTTSS2SI : sse12_cvt_sint<0x2C, VR128, GR32, int_x86_sse_cvttss2si,
736                                     f32mem, load, "cvttss2si">, XS, VEX;
737 defm Int_VCVTTSS2SI64 : sse12_cvt_sint<0x2C, VR128, GR64,
738                                     int_x86_sse_cvttss2si64, f32mem, load,
739                                     "cvttss2si">, XS, VEX, VEX_W;
740 defm Int_VCVTTSD2SI : sse12_cvt_sint<0x2C, VR128, GR32, int_x86_sse2_cvttsd2si,
741                                     f128mem, load, "cvttss2si">, XD, VEX;
742 defm Int_VCVTTSD2SI64 : sse12_cvt_sint<0x2C, VR128, GR64,
743                                     int_x86_sse2_cvttsd2si64, f128mem, load,
744                                     "cvttss2si">, XD, VEX, VEX_W;
745 }
746 defm Int_CVTTSS2SI : sse12_cvt_sint<0x2C, VR128, GR32, int_x86_sse_cvttss2si,
747                                     f32mem, load, "cvttss2si">, XS;
748 defm Int_CVTTSS2SI64 : sse12_cvt_sint<0x2C, VR128, GR64,
749                                     int_x86_sse_cvttss2si64, f32mem, load,
750                                     "cvttss2si{q}">, XS, REX_W;
751 defm Int_CVTTSD2SI : sse12_cvt_sint<0x2C, VR128, GR32, int_x86_sse2_cvttsd2si,
752                                     f128mem, load, "cvttss2si">, XD;
753 defm Int_CVTTSD2SI64 : sse12_cvt_sint<0x2C, VR128, GR64,
754                                     int_x86_sse2_cvttsd2si64, f128mem, load,
755                                     "cvttss2si{q}">, XD, REX_W;
756
757 let isAsmParserOnly = 1, Pattern = []<dag> in {
758 defm VCVTSS2SI   : sse12_cvt_s<0x2D, FR32, GR32, undef, f32mem, load,
759                                "cvtss2si{l}\t{$src, $dst|$dst, $src}">, XS, VEX;
760 defm VCVTSS2SI64 : sse12_cvt_s<0x2D, FR32, GR64, undef, f32mem, load,
761                                "cvtss2si\t{$src, $dst|$dst, $src}">, XS, VEX,
762                                VEX_W;
763 defm VCVTDQ2PS   : sse12_cvt_p<0x5B, VR128, VR128, undef, i128mem, load,
764                                "cvtdq2ps\t{$src, $dst|$dst, $src}",
765                                SSEPackedSingle>, TB, VEX;
766 defm VCVTDQ2PSY  : sse12_cvt_p<0x5B, VR256, VR256, undef, i256mem, load,
767                                "cvtdq2ps\t{$src, $dst|$dst, $src}",
768                                SSEPackedSingle>, TB, VEX;
769 }
770 let Pattern = []<dag> in {
771 defm CVTSS2SI : sse12_cvt_s<0x2D, FR32, GR32, undef, f32mem, load /*dummy*/,
772                           "cvtss2si{l}\t{$src, $dst|$dst, $src}">, XS;
773 defm CVTSS2SI64 : sse12_cvt_s<0x2D, FR32, GR64, undef, f32mem, load /*dummy*/,
774                           "cvtss2si{q}\t{$src, $dst|$dst, $src}">, XS, REX_W;
775 defm CVTDQ2PS : sse12_cvt_p<0x5B, VR128, VR128, undef, i128mem, load /*dummy*/,
776                             "cvtdq2ps\t{$src, $dst|$dst, $src}",
777                             SSEPackedSingle>, TB; /* PD SSE3 form is avaiable */
778 }
779
780 /// SSE 2 Only
781
782 // Convert scalar double to scalar single
783 let isAsmParserOnly = 1 in {
784 def VCVTSD2SSrr  : VSDI<0x5A, MRMSrcReg, (outs FR32:$dst),
785                        (ins FR64:$src1, FR64:$src2),
786                       "cvtsd2ss\t{$src2, $src1, $dst|$dst, $src1, $src2}", []>,
787                       VEX_4V;
788 def VCVTSD2SSrm  : I<0x5A, MRMSrcMem, (outs FR32:$dst),
789                        (ins FR64:$src1, f64mem:$src2),
790                       "vcvtsd2ss\t{$src2, $src1, $dst|$dst, $src1, $src2}",
791                       []>, XD, Requires<[HasAVX, OptForSize]>, VEX_4V;
792 }
793 def CVTSD2SSrr  : SDI<0x5A, MRMSrcReg, (outs FR32:$dst), (ins FR64:$src),
794                       "cvtsd2ss\t{$src, $dst|$dst, $src}",
795                       [(set FR32:$dst, (fround FR64:$src))]>;
796 def CVTSD2SSrm  : I<0x5A, MRMSrcMem, (outs FR32:$dst), (ins f64mem:$src),
797                       "cvtsd2ss\t{$src, $dst|$dst, $src}",
798                       [(set FR32:$dst, (fround (loadf64 addr:$src)))]>, XD,
799                   Requires<[HasSSE2, OptForSize]>;
800
801 let isAsmParserOnly = 1 in
802 defm Int_VCVTSD2SS: sse12_cvt_sint_3addr<0x5A, VR128, VR128,
803                       int_x86_sse2_cvtsd2ss, f64mem, load, "cvtsd2ss", 0>,
804                       XS, VEX_4V;
805 let Constraints = "$src1 = $dst" in
806 defm Int_CVTSD2SS: sse12_cvt_sint_3addr<0x5A, VR128, VR128,
807                       int_x86_sse2_cvtsd2ss, f64mem, load, "cvtsd2ss">, XS;
808
809 // Convert scalar single to scalar double
810 let isAsmParserOnly = 1 in { // SSE2 instructions with XS prefix
811 def VCVTSS2SDrr : I<0x5A, MRMSrcReg, (outs FR64:$dst),
812                     (ins FR32:$src1, FR32:$src2),
813                     "vcvtss2sd\t{$src2, $src1, $dst|$dst, $src1, $src2}",
814                     []>, XS, Requires<[HasAVX]>, VEX_4V;
815 def VCVTSS2SDrm : I<0x5A, MRMSrcMem, (outs FR64:$dst),
816                     (ins FR32:$src1, f32mem:$src2),
817                     "vcvtss2sd\t{$src2, $src1, $dst|$dst, $src1, $src2}",
818                     []>, XS, VEX_4V, Requires<[HasAVX, OptForSize]>;
819 }
820 def CVTSS2SDrr : I<0x5A, MRMSrcReg, (outs FR64:$dst), (ins FR32:$src),
821                    "cvtss2sd\t{$src, $dst|$dst, $src}",
822                    [(set FR64:$dst, (fextend FR32:$src))]>, XS,
823                  Requires<[HasSSE2]>;
824 def CVTSS2SDrm : I<0x5A, MRMSrcMem, (outs FR64:$dst), (ins f32mem:$src),
825                    "cvtss2sd\t{$src, $dst|$dst, $src}",
826                    [(set FR64:$dst, (extloadf32 addr:$src))]>, XS,
827                  Requires<[HasSSE2, OptForSize]>;
828
829 let isAsmParserOnly = 1 in {
830 def Int_VCVTSS2SDrr: I<0x5A, MRMSrcReg,
831                       (outs VR128:$dst), (ins VR128:$src1, VR128:$src2),
832                     "vcvtss2sd\t{$src2, $src1, $dst|$dst, $src1, $src2}",
833                     [(set VR128:$dst, (int_x86_sse2_cvtss2sd VR128:$src1,
834                                        VR128:$src2))]>, XS, VEX_4V,
835                     Requires<[HasAVX]>;
836 def Int_VCVTSS2SDrm: I<0x5A, MRMSrcMem,
837                       (outs VR128:$dst), (ins VR128:$src1, f32mem:$src2),
838                     "vcvtss2sd\t{$src2, $src1, $dst|$dst, $src1, $src2}",
839                     [(set VR128:$dst, (int_x86_sse2_cvtss2sd VR128:$src1,
840                                        (load addr:$src2)))]>, XS, VEX_4V,
841                     Requires<[HasAVX]>;
842 }
843 let Constraints = "$src1 = $dst" in { // SSE2 instructions with XS prefix
844 def Int_CVTSS2SDrr: I<0x5A, MRMSrcReg,
845                       (outs VR128:$dst), (ins VR128:$src1, VR128:$src2),
846                     "cvtss2sd\t{$src2, $dst|$dst, $src2}",
847                     [(set VR128:$dst, (int_x86_sse2_cvtss2sd VR128:$src1,
848                                        VR128:$src2))]>, XS,
849                     Requires<[HasSSE2]>;
850 def Int_CVTSS2SDrm: I<0x5A, MRMSrcMem,
851                       (outs VR128:$dst), (ins VR128:$src1, f32mem:$src2),
852                     "cvtss2sd\t{$src2, $dst|$dst, $src2}",
853                     [(set VR128:$dst, (int_x86_sse2_cvtss2sd VR128:$src1,
854                                        (load addr:$src2)))]>, XS,
855                     Requires<[HasSSE2]>;
856 }
857
858 def : Pat<(extloadf32 addr:$src),
859           (CVTSS2SDrr (MOVSSrm addr:$src))>,
860       Requires<[HasSSE2, OptForSpeed]>;
861
862 // Convert doubleword to packed single/double fp
863 let isAsmParserOnly = 1 in { // SSE2 instructions without OpSize prefix
864 def Int_VCVTDQ2PSrr : I<0x5B, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
865                        "vcvtdq2ps\t{$src, $dst|$dst, $src}",
866                        [(set VR128:$dst, (int_x86_sse2_cvtdq2ps VR128:$src))]>,
867                      TB, VEX, Requires<[HasAVX]>;
868 def Int_VCVTDQ2PSrm : I<0x5B, MRMSrcMem, (outs VR128:$dst), (ins i128mem:$src),
869                       "vcvtdq2ps\t{$src, $dst|$dst, $src}",
870                       [(set VR128:$dst, (int_x86_sse2_cvtdq2ps
871                                         (bitconvert (memopv2i64 addr:$src))))]>,
872                      TB, VEX, Requires<[HasAVX]>;
873 }
874 def Int_CVTDQ2PSrr : I<0x5B, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
875                        "cvtdq2ps\t{$src, $dst|$dst, $src}",
876                        [(set VR128:$dst, (int_x86_sse2_cvtdq2ps VR128:$src))]>,
877                      TB, Requires<[HasSSE2]>;
878 def Int_CVTDQ2PSrm : I<0x5B, MRMSrcMem, (outs VR128:$dst), (ins i128mem:$src),
879                       "cvtdq2ps\t{$src, $dst|$dst, $src}",
880                       [(set VR128:$dst, (int_x86_sse2_cvtdq2ps
881                                         (bitconvert (memopv2i64 addr:$src))))]>,
882                      TB, Requires<[HasSSE2]>;
883
884 // FIXME: why the non-intrinsic version is described as SSE3?
885 let isAsmParserOnly = 1 in { // SSE2 instructions with XS prefix
886 def Int_VCVTDQ2PDrr : I<0xE6, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
887                        "vcvtdq2pd\t{$src, $dst|$dst, $src}",
888                        [(set VR128:$dst, (int_x86_sse2_cvtdq2pd VR128:$src))]>,
889                      XS, VEX, Requires<[HasAVX]>;
890 def Int_VCVTDQ2PDrm : I<0xE6, MRMSrcMem, (outs VR128:$dst), (ins i64mem:$src),
891                        "vcvtdq2pd\t{$src, $dst|$dst, $src}",
892                        [(set VR128:$dst, (int_x86_sse2_cvtdq2pd
893                                         (bitconvert (memopv2i64 addr:$src))))]>,
894                      XS, VEX, Requires<[HasAVX]>;
895 }
896 def Int_CVTDQ2PDrr : I<0xE6, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
897                        "cvtdq2pd\t{$src, $dst|$dst, $src}",
898                        [(set VR128:$dst, (int_x86_sse2_cvtdq2pd VR128:$src))]>,
899                      XS, Requires<[HasSSE2]>;
900 def Int_CVTDQ2PDrm : I<0xE6, MRMSrcMem, (outs VR128:$dst), (ins i64mem:$src),
901                      "cvtdq2pd\t{$src, $dst|$dst, $src}",
902                      [(set VR128:$dst, (int_x86_sse2_cvtdq2pd
903                                         (bitconvert (memopv2i64 addr:$src))))]>,
904                      XS, Requires<[HasSSE2]>;
905
906
907 // Convert packed single/double fp to doubleword
908 let isAsmParserOnly = 1 in {
909 def VCVTPS2DQrr : VPDI<0x5B, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
910                        "cvtps2dq\t{$src, $dst|$dst, $src}", []>, VEX;
911 def VCVTPS2DQrm : VPDI<0x5B, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
912                        "cvtps2dq\t{$src, $dst|$dst, $src}", []>, VEX;
913 def VCVTPS2DQYrr : VPDI<0x5B, MRMSrcReg, (outs VR256:$dst), (ins VR256:$src),
914                         "cvtps2dq\t{$src, $dst|$dst, $src}", []>, VEX;
915 def VCVTPS2DQYrm : VPDI<0x5B, MRMSrcMem, (outs VR256:$dst), (ins f256mem:$src),
916                         "cvtps2dq\t{$src, $dst|$dst, $src}", []>, VEX;
917 }
918 def CVTPS2DQrr : PDI<0x5B, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
919                      "cvtps2dq\t{$src, $dst|$dst, $src}", []>;
920 def CVTPS2DQrm : PDI<0x5B, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
921                      "cvtps2dq\t{$src, $dst|$dst, $src}", []>;
922
923 let isAsmParserOnly = 1 in {
924 def Int_VCVTPS2DQrr : VPDI<0x5B, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
925                         "cvtps2dq\t{$src, $dst|$dst, $src}",
926                         [(set VR128:$dst, (int_x86_sse2_cvtps2dq VR128:$src))]>,
927                         VEX;
928 def Int_VCVTPS2DQrm : VPDI<0x5B, MRMSrcMem, (outs VR128:$dst),
929                          (ins f128mem:$src),
930                          "cvtps2dq\t{$src, $dst|$dst, $src}",
931                          [(set VR128:$dst, (int_x86_sse2_cvtps2dq
932                                             (memop addr:$src)))]>, VEX;
933 }
934 def Int_CVTPS2DQrr : PDI<0x5B, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
935                         "cvtps2dq\t{$src, $dst|$dst, $src}",
936                         [(set VR128:$dst, (int_x86_sse2_cvtps2dq VR128:$src))]>;
937 def Int_CVTPS2DQrm : PDI<0x5B, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
938                          "cvtps2dq\t{$src, $dst|$dst, $src}",
939                          [(set VR128:$dst, (int_x86_sse2_cvtps2dq
940                                             (memop addr:$src)))]>;
941
942 let isAsmParserOnly = 1 in { // SSE2 packed instructions with XD prefix
943 def Int_VCVTPD2DQrr : I<0xE6, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
944                        "vcvtpd2dq\t{$src, $dst|$dst, $src}",
945                        [(set VR128:$dst, (int_x86_sse2_cvtpd2dq VR128:$src))]>,
946                      XD, VEX, Requires<[HasAVX]>;
947 def Int_VCVTPD2DQrm : I<0xE6, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
948                        "vcvtpd2dq\t{$src, $dst|$dst, $src}",
949                        [(set VR128:$dst, (int_x86_sse2_cvtpd2dq
950                                           (memop addr:$src)))]>,
951                      XD, VEX, Requires<[HasAVX]>;
952 }
953 def Int_CVTPD2DQrr : I<0xE6, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
954                        "cvtpd2dq\t{$src, $dst|$dst, $src}",
955                        [(set VR128:$dst, (int_x86_sse2_cvtpd2dq VR128:$src))]>,
956                      XD, Requires<[HasSSE2]>;
957 def Int_CVTPD2DQrm : I<0xE6, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
958                        "cvtpd2dq\t{$src, $dst|$dst, $src}",
959                        [(set VR128:$dst, (int_x86_sse2_cvtpd2dq
960                                           (memop addr:$src)))]>,
961                      XD, Requires<[HasSSE2]>;
962
963
964 // Convert with truncation packed single/double fp to doubleword
965 let isAsmParserOnly = 1 in { // SSE2 packed instructions with XS prefix
966 def VCVTTPS2DQrr : VSSI<0x5B, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
967                       "cvttps2dq\t{$src, $dst|$dst, $src}", []>, VEX;
968 def VCVTTPS2DQrm : VSSI<0x5B, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
969                       "cvttps2dq\t{$src, $dst|$dst, $src}", []>, VEX;
970 def VCVTTPS2DQYrr : VSSI<0x5B, MRMSrcReg, (outs VR256:$dst), (ins VR256:$src),
971                       "cvttps2dq\t{$src, $dst|$dst, $src}", []>, VEX;
972 def VCVTTPS2DQYrm : VSSI<0x5B, MRMSrcMem, (outs VR256:$dst), (ins f256mem:$src),
973                       "cvttps2dq\t{$src, $dst|$dst, $src}", []>, VEX;
974 }
975 def CVTTPS2DQrr : SSI<0x5B, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
976                       "cvttps2dq\t{$src, $dst|$dst, $src}", []>;
977 def CVTTPS2DQrm : SSI<0x5B, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
978                       "cvttps2dq\t{$src, $dst|$dst, $src}", []>;
979
980
981 let isAsmParserOnly = 1 in {
982 def Int_VCVTTPS2DQrr : I<0x5B, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
983                         "vcvttps2dq\t{$src, $dst|$dst, $src}",
984                         [(set VR128:$dst,
985                               (int_x86_sse2_cvttps2dq VR128:$src))]>,
986                       XS, VEX, Requires<[HasAVX]>;
987 def Int_VCVTTPS2DQrm : I<0x5B, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
988                         "vcvttps2dq\t{$src, $dst|$dst, $src}",
989                         [(set VR128:$dst, (int_x86_sse2_cvttps2dq
990                                            (memop addr:$src)))]>,
991                       XS, VEX, Requires<[HasAVX]>;
992 }
993 def Int_CVTTPS2DQrr : I<0x5B, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
994                         "cvttps2dq\t{$src, $dst|$dst, $src}",
995                         [(set VR128:$dst,
996                               (int_x86_sse2_cvttps2dq VR128:$src))]>,
997                       XS, Requires<[HasSSE2]>;
998 def Int_CVTTPS2DQrm : I<0x5B, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
999                         "cvttps2dq\t{$src, $dst|$dst, $src}",
1000                         [(set VR128:$dst, (int_x86_sse2_cvttps2dq
1001                                            (memop addr:$src)))]>,
1002                       XS, Requires<[HasSSE2]>;
1003
1004 let isAsmParserOnly = 1 in {
1005 def Int_VCVTTPD2DQrr : VPDI<0xE6, MRMSrcReg, (outs VR128:$dst),
1006                             (ins VR128:$src),
1007                           "cvttpd2dq\t{$src, $dst|$dst, $src}",
1008                        [(set VR128:$dst, (int_x86_sse2_cvttpd2dq VR128:$src))]>,
1009                        VEX;
1010 def Int_VCVTTPD2DQrm : VPDI<0xE6, MRMSrcMem, (outs VR128:$dst),
1011                           (ins f128mem:$src),
1012                           "cvttpd2dq\t{$src, $dst|$dst, $src}",
1013                           [(set VR128:$dst, (int_x86_sse2_cvttpd2dq
1014                                              (memop addr:$src)))]>, VEX;
1015 }
1016 def Int_CVTTPD2DQrr : PDI<0xE6, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
1017                           "cvttpd2dq\t{$src, $dst|$dst, $src}",
1018                        [(set VR128:$dst, (int_x86_sse2_cvttpd2dq VR128:$src))]>;
1019 def Int_CVTTPD2DQrm : PDI<0xE6, MRMSrcMem, (outs VR128:$dst),(ins f128mem:$src),
1020                           "cvttpd2dq\t{$src, $dst|$dst, $src}",
1021                           [(set VR128:$dst, (int_x86_sse2_cvttpd2dq
1022                                              (memop addr:$src)))]>;
1023
1024 let isAsmParserOnly = 1 in {
1025 // The assembler can recognize rr 256-bit instructions by seeing a ymm
1026 // register, but the same isn't true when using memory operands instead.
1027 // Provide other assembly rr and rm forms to address this explicitly.
1028 def VCVTTPD2DQrr : VPDI<0xE6, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
1029                         "cvttpd2dq\t{$src, $dst|$dst, $src}", []>, VEX;
1030 def VCVTTPD2DQXrYr : VPDI<0xE6, MRMSrcReg, (outs VR128:$dst), (ins VR256:$src),
1031                           "cvttpd2dq\t{$src, $dst|$dst, $src}", []>, VEX;
1032
1033 // XMM only
1034 def VCVTTPD2DQXrr : VPDI<0xE6, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
1035                          "cvttpd2dqx\t{$src, $dst|$dst, $src}", []>, VEX;
1036 def VCVTTPD2DQXrm : VPDI<0xE6, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
1037                          "cvttpd2dqx\t{$src, $dst|$dst, $src}", []>, VEX;
1038
1039 // YMM only
1040 def VCVTTPD2DQYrr : VPDI<0xE6, MRMSrcReg, (outs VR128:$dst), (ins VR256:$src),
1041                          "cvttpd2dqy\t{$src, $dst|$dst, $src}", []>, VEX;
1042 def VCVTTPD2DQYrm : VPDI<0xE6, MRMSrcMem, (outs VR128:$dst), (ins f256mem:$src),
1043                          "cvttpd2dqy\t{$src, $dst|$dst, $src}", []>, VEX, VEX_L;
1044 }
1045
1046 // Convert packed single to packed double
1047 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
1048                   // SSE2 instructions without OpSize prefix
1049 def VCVTPS2PDrr : I<0x5A, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
1050                      "vcvtps2pd\t{$src, $dst|$dst, $src}", []>, VEX;
1051 def VCVTPS2PDrm : I<0x5A, MRMSrcMem, (outs VR128:$dst), (ins f64mem:$src),
1052                      "vcvtps2pd\t{$src, $dst|$dst, $src}", []>, VEX;
1053 def VCVTPS2PDYrr : I<0x5A, MRMSrcReg, (outs VR256:$dst), (ins VR128:$src),
1054                      "vcvtps2pd\t{$src, $dst|$dst, $src}", []>, VEX;
1055 def VCVTPS2PDYrm : I<0x5A, MRMSrcMem, (outs VR256:$dst), (ins f128mem:$src),
1056                      "vcvtps2pd\t{$src, $dst|$dst, $src}", []>, VEX;
1057 }
1058 def CVTPS2PDrr : I<0x5A, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
1059                        "cvtps2pd\t{$src, $dst|$dst, $src}", []>, TB;
1060 def CVTPS2PDrm : I<0x5A, MRMSrcMem, (outs VR128:$dst), (ins f64mem:$src),
1061                        "cvtps2pd\t{$src, $dst|$dst, $src}", []>, TB;
1062
1063 let isAsmParserOnly = 1 in {
1064 def Int_VCVTPS2PDrr : I<0x5A, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
1065                        "vcvtps2pd\t{$src, $dst|$dst, $src}",
1066                        [(set VR128:$dst, (int_x86_sse2_cvtps2pd VR128:$src))]>,
1067                      VEX, Requires<[HasAVX]>;
1068 def Int_VCVTPS2PDrm : I<0x5A, MRMSrcMem, (outs VR128:$dst), (ins f64mem:$src),
1069                        "vcvtps2pd\t{$src, $dst|$dst, $src}",
1070                        [(set VR128:$dst, (int_x86_sse2_cvtps2pd
1071                                           (load addr:$src)))]>,
1072                      VEX, Requires<[HasAVX]>;
1073 }
1074 def Int_CVTPS2PDrr : I<0x5A, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
1075                        "cvtps2pd\t{$src, $dst|$dst, $src}",
1076                        [(set VR128:$dst, (int_x86_sse2_cvtps2pd VR128:$src))]>,
1077                      TB, Requires<[HasSSE2]>;
1078 def Int_CVTPS2PDrm : I<0x5A, MRMSrcMem, (outs VR128:$dst), (ins f64mem:$src),
1079                        "cvtps2pd\t{$src, $dst|$dst, $src}",
1080                        [(set VR128:$dst, (int_x86_sse2_cvtps2pd
1081                                           (load addr:$src)))]>,
1082                      TB, Requires<[HasSSE2]>;
1083
1084 // Convert packed double to packed single
1085 let isAsmParserOnly = 1 in {
1086 // The assembler can recognize rr 256-bit instructions by seeing a ymm
1087 // register, but the same isn't true when using memory operands instead.
1088 // Provide other assembly rr and rm forms to address this explicitly.
1089 def VCVTPD2PSrr : VPDI<0x5A, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
1090                        "cvtpd2ps\t{$src, $dst|$dst, $src}", []>, VEX;
1091 def VCVTPD2PSXrYr : VPDI<0x5A, MRMSrcReg, (outs VR128:$dst), (ins VR256:$src),
1092                          "cvtpd2ps\t{$src, $dst|$dst, $src}", []>, VEX;
1093
1094 // XMM only
1095 def VCVTPD2PSXrr : VPDI<0x5A, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
1096                         "cvtpd2psx\t{$src, $dst|$dst, $src}", []>, VEX;
1097 def VCVTPD2PSXrm : VPDI<0x5A, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
1098                         "cvtpd2psx\t{$src, $dst|$dst, $src}", []>, VEX;
1099
1100 // YMM only
1101 def VCVTPD2PSYrr : VPDI<0x5A, MRMSrcReg, (outs VR128:$dst), (ins VR256:$src),
1102                         "cvtpd2psy\t{$src, $dst|$dst, $src}", []>, VEX;
1103 def VCVTPD2PSYrm : VPDI<0x5A, MRMSrcMem, (outs VR128:$dst), (ins f256mem:$src),
1104                         "cvtpd2psy\t{$src, $dst|$dst, $src}", []>, VEX, VEX_L;
1105 }
1106 def CVTPD2PSrr : PDI<0x5A, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
1107                      "cvtpd2ps\t{$src, $dst|$dst, $src}", []>;
1108 def CVTPD2PSrm : PDI<0x5A, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
1109                      "cvtpd2ps\t{$src, $dst|$dst, $src}", []>;
1110
1111
1112 let isAsmParserOnly = 1 in {
1113 def Int_VCVTPD2PSrr : VPDI<0x5A, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
1114                          "cvtpd2ps\t{$src, $dst|$dst, $src}",
1115                         [(set VR128:$dst, (int_x86_sse2_cvtpd2ps VR128:$src))]>;
1116 def Int_VCVTPD2PSrm : VPDI<0x5A, MRMSrcMem, (outs VR128:$dst),
1117                          (ins f128mem:$src),
1118                          "cvtpd2ps\t{$src, $dst|$dst, $src}",
1119                          [(set VR128:$dst, (int_x86_sse2_cvtpd2ps
1120                                             (memop addr:$src)))]>;
1121 }
1122 def Int_CVTPD2PSrr : PDI<0x5A, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
1123                          "cvtpd2ps\t{$src, $dst|$dst, $src}",
1124                         [(set VR128:$dst, (int_x86_sse2_cvtpd2ps VR128:$src))]>;
1125 def Int_CVTPD2PSrm : PDI<0x5A, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
1126                          "cvtpd2ps\t{$src, $dst|$dst, $src}",
1127                          [(set VR128:$dst, (int_x86_sse2_cvtpd2ps
1128                                             (memop addr:$src)))]>;
1129
1130 // AVX 256-bit register conversion intrinsics
1131 // FIXME: Migrate SSE conversion intrinsics matching to use patterns as below
1132 // whenever possible to avoid declaring two versions of each one.
1133 def : Pat<(int_x86_avx_cvtdq2_ps_256 VR256:$src),
1134           (VCVTDQ2PSYrr VR256:$src)>;
1135 def : Pat<(int_x86_avx_cvtdq2_ps_256 (memopv8i32 addr:$src)),
1136           (VCVTDQ2PSYrm addr:$src)>;
1137
1138 def : Pat<(int_x86_avx_cvt_pd2_ps_256 VR256:$src),
1139           (VCVTPD2PSYrr VR256:$src)>;
1140 def : Pat<(int_x86_avx_cvt_pd2_ps_256 (memopv4f64 addr:$src)),
1141           (VCVTPD2PSYrm addr:$src)>;
1142
1143 def : Pat<(int_x86_avx_cvt_ps2dq_256 VR256:$src),
1144           (VCVTPS2DQYrr VR256:$src)>;
1145 def : Pat<(int_x86_avx_cvt_ps2dq_256 (memopv8f32 addr:$src)),
1146           (VCVTPS2DQYrm addr:$src)>;
1147
1148 def : Pat<(int_x86_avx_cvt_ps2_pd_256 VR128:$src),
1149           (VCVTPS2PDYrr VR128:$src)>;
1150 def : Pat<(int_x86_avx_cvt_ps2_pd_256 (memopv4f32 addr:$src)),
1151           (VCVTPS2PDYrm addr:$src)>;
1152
1153 def : Pat<(int_x86_avx_cvtt_pd2dq_256 VR256:$src),
1154           (VCVTTPD2DQYrr VR256:$src)>;
1155 def : Pat<(int_x86_avx_cvtt_pd2dq_256 (memopv4f64 addr:$src)),
1156           (VCVTTPD2DQYrm addr:$src)>;
1157
1158 def : Pat<(int_x86_avx_cvtt_ps2dq_256 VR256:$src),
1159           (VCVTTPS2DQYrr VR256:$src)>;
1160 def : Pat<(int_x86_avx_cvtt_ps2dq_256 (memopv8f32 addr:$src)),
1161           (VCVTTPS2DQYrm addr:$src)>;
1162
1163 //===----------------------------------------------------------------------===//
1164 // SSE 1 & 2 - Compare Instructions
1165 //===----------------------------------------------------------------------===//
1166
1167 // sse12_cmp_scalar - sse 1 & 2 compare scalar instructions
1168 multiclass sse12_cmp_scalar<RegisterClass RC, X86MemOperand x86memop,
1169                             string asm, string asm_alt> {
1170   def rr : SIi8<0xC2, MRMSrcReg,
1171                     (outs RC:$dst), (ins RC:$src1, RC:$src, SSECC:$cc),
1172                     asm, []>;
1173   let mayLoad = 1 in
1174   def rm : SIi8<0xC2, MRMSrcMem,
1175                     (outs RC:$dst), (ins RC:$src1, x86memop:$src, SSECC:$cc),
1176                     asm, []>;
1177   // Accept explicit immediate argument form instead of comparison code.
1178   let isAsmParserOnly = 1 in {
1179     def rr_alt : SIi8<0xC2, MRMSrcReg,
1180                   (outs RC:$dst), (ins RC:$src1, RC:$src, i8imm:$src2),
1181                   asm_alt, []>;
1182     let mayLoad = 1 in
1183     def rm_alt : SIi8<0xC2, MRMSrcMem,
1184                   (outs RC:$dst), (ins RC:$src1, x86memop:$src, i8imm:$src2),
1185                   asm_alt, []>;
1186   }
1187 }
1188
1189 let neverHasSideEffects = 1, isAsmParserOnly = 1 in {
1190   defm VCMPSS  : sse12_cmp_scalar<FR32, f32mem,
1191                   "cmp${cc}ss\t{$src, $src1, $dst|$dst, $src1, $src}",
1192                   "cmpss\t{$src2, $src, $src1, $dst|$dst, $src1, $src, $src2}">,
1193                   XS, VEX_4V;
1194   defm VCMPSD  : sse12_cmp_scalar<FR64, f64mem,
1195                   "cmp${cc}sd\t{$src, $src1, $dst|$dst, $src1, $src}",
1196                   "cmpsd\t{$src2, $src, $src1, $dst|$dst, $src1, $src, $src2}">,
1197                   XD, VEX_4V;
1198 }
1199
1200 let Constraints = "$src1 = $dst", neverHasSideEffects = 1 in {
1201   defm CMPSS  : sse12_cmp_scalar<FR32, f32mem,
1202                     "cmp${cc}ss\t{$src, $dst|$dst, $src}",
1203                     "cmpss\t{$src2, $src, $dst|$dst, $src, $src2}">, XS;
1204   defm CMPSD  : sse12_cmp_scalar<FR64, f64mem,
1205                     "cmp${cc}sd\t{$src, $dst|$dst, $src}",
1206                     "cmpsd\t{$src2, $src, $dst|$dst, $src, $src2}">, XD;
1207 }
1208
1209 multiclass sse12_cmp_scalar_int<RegisterClass RC, Operand memopr,
1210                          ComplexPattern mem_cpat, Intrinsic Int, string asm> {
1211   def rr : SIi8<0xC2, MRMSrcReg, (outs VR128:$dst),
1212                       (ins VR128:$src1, VR128:$src, SSECC:$cc), asm,
1213                         [(set VR128:$dst, (Int VR128:$src1,
1214                                                VR128:$src, imm:$cc))]>;
1215   def rm : SIi8<0xC2, MRMSrcMem, (outs VR128:$dst),
1216                       (ins VR128:$src1, memopr:$src, SSECC:$cc), asm,
1217                         [(set VR128:$dst, (Int VR128:$src1,
1218                                               mem_cpat:$src, imm:$cc))]>;
1219 }
1220
1221 // Aliases to match intrinsics which expect XMM operand(s).
1222
1223 let isAsmParserOnly = 1 in {
1224   defm Int_VCMPSS  : sse12_cmp_scalar_int<VR128, ssmem, sse_load_f32, 
1225                        int_x86_sse_cmp_ss,
1226                        "cmp${cc}ss\t{$src, $src1, $dst|$dst, $src1, $src}">,
1227                        XS, VEX_4V;
1228   defm Int_VCMPSD  : sse12_cmp_scalar_int<VR128, sdmem, sse_load_f64,
1229                        int_x86_sse2_cmp_sd,
1230                        "cmp${cc}sd\t{$src, $src1, $dst|$dst, $src1, $src}">,
1231                        XD, VEX_4V;
1232 }
1233 let Constraints = "$src1 = $dst" in {
1234   defm Int_CMPSS  : sse12_cmp_scalar_int<VR128, ssmem, sse_load_f32,
1235                        int_x86_sse_cmp_ss,
1236                        "cmp${cc}ss\t{$src, $dst|$dst, $src}">, XS;
1237   defm Int_CMPSD  : sse12_cmp_scalar_int<VR128, sdmem, sse_load_f64,
1238                        int_x86_sse2_cmp_sd,
1239                        "cmp${cc}sd\t{$src, $dst|$dst, $src}">, XD;
1240 }
1241
1242
1243 // sse12_ord_cmp - Unordered/Ordered scalar fp compare and set EFLAGS
1244 multiclass sse12_ord_cmp<bits<8> opc, RegisterClass RC, SDNode OpNode,
1245                             ValueType vt, X86MemOperand x86memop,
1246                             PatFrag ld_frag, string OpcodeStr, Domain d> {
1247   def rr: PI<opc, MRMSrcReg, (outs), (ins RC:$src1, RC:$src2),
1248                      !strconcat(OpcodeStr, "\t{$src2, $src1|$src1, $src2}"),
1249                      [(set EFLAGS, (OpNode (vt RC:$src1), RC:$src2))], d>;
1250   def rm: PI<opc, MRMSrcMem, (outs), (ins RC:$src1, x86memop:$src2),
1251                      !strconcat(OpcodeStr, "\t{$src2, $src1|$src1, $src2}"),
1252                      [(set EFLAGS, (OpNode (vt RC:$src1),
1253                                            (ld_frag addr:$src2)))], d>;
1254 }
1255
1256 let Defs = [EFLAGS] in {
1257   let isAsmParserOnly = 1 in {
1258     defm VUCOMISS : sse12_ord_cmp<0x2E, FR32, X86cmp, f32, f32mem, loadf32,
1259                                     "ucomiss", SSEPackedSingle>, VEX;
1260     defm VUCOMISD : sse12_ord_cmp<0x2E, FR64, X86cmp, f64, f64mem, loadf64,
1261                                     "ucomisd", SSEPackedDouble>, OpSize, VEX;
1262     let Pattern = []<dag> in {
1263       defm VCOMISS  : sse12_ord_cmp<0x2F, VR128, undef, v4f32, f128mem, load,
1264                                       "comiss", SSEPackedSingle>, VEX;
1265       defm VCOMISD  : sse12_ord_cmp<0x2F, VR128, undef, v2f64, f128mem, load,
1266                                       "comisd", SSEPackedDouble>, OpSize, VEX;
1267     }
1268
1269     defm Int_VUCOMISS  : sse12_ord_cmp<0x2E, VR128, X86ucomi, v4f32, f128mem,
1270                               load, "ucomiss", SSEPackedSingle>, VEX;
1271     defm Int_VUCOMISD  : sse12_ord_cmp<0x2E, VR128, X86ucomi, v2f64, f128mem,
1272                               load, "ucomisd", SSEPackedDouble>, OpSize, VEX;
1273
1274     defm Int_VCOMISS  : sse12_ord_cmp<0x2F, VR128, X86comi, v4f32, f128mem,
1275                               load, "comiss", SSEPackedSingle>, VEX;
1276     defm Int_VCOMISD  : sse12_ord_cmp<0x2F, VR128, X86comi, v2f64, f128mem,
1277                               load, "comisd", SSEPackedDouble>, OpSize, VEX;
1278   }
1279   defm UCOMISS  : sse12_ord_cmp<0x2E, FR32, X86cmp, f32, f32mem, loadf32,
1280                                   "ucomiss", SSEPackedSingle>, TB;
1281   defm UCOMISD  : sse12_ord_cmp<0x2E, FR64, X86cmp, f64, f64mem, loadf64,
1282                                   "ucomisd", SSEPackedDouble>, TB, OpSize;
1283
1284   let Pattern = []<dag> in {
1285     defm COMISS  : sse12_ord_cmp<0x2F, VR128, undef, v4f32, f128mem, load,
1286                                     "comiss", SSEPackedSingle>, TB;
1287     defm COMISD  : sse12_ord_cmp<0x2F, VR128, undef, v2f64, f128mem, load,
1288                                     "comisd", SSEPackedDouble>, TB, OpSize;
1289   }
1290
1291   defm Int_UCOMISS  : sse12_ord_cmp<0x2E, VR128, X86ucomi, v4f32, f128mem,
1292                               load, "ucomiss", SSEPackedSingle>, TB;
1293   defm Int_UCOMISD  : sse12_ord_cmp<0x2E, VR128, X86ucomi, v2f64, f128mem,
1294                               load, "ucomisd", SSEPackedDouble>, TB, OpSize;
1295
1296   defm Int_COMISS  : sse12_ord_cmp<0x2F, VR128, X86comi, v4f32, f128mem, load,
1297                                   "comiss", SSEPackedSingle>, TB;
1298   defm Int_COMISD  : sse12_ord_cmp<0x2F, VR128, X86comi, v2f64, f128mem, load,
1299                                   "comisd", SSEPackedDouble>, TB, OpSize;
1300 } // Defs = [EFLAGS]
1301
1302 // sse12_cmp_packed - sse 1 & 2 compared packed instructions
1303 multiclass sse12_cmp_packed<RegisterClass RC, X86MemOperand x86memop,
1304                             Intrinsic Int, string asm, string asm_alt,
1305                             Domain d> {
1306   def rri : PIi8<0xC2, MRMSrcReg,
1307              (outs RC:$dst), (ins RC:$src1, RC:$src, SSECC:$cc), asm,
1308              [(set RC:$dst, (Int RC:$src1, RC:$src, imm:$cc))], d>;
1309   def rmi : PIi8<0xC2, MRMSrcMem,
1310              (outs RC:$dst), (ins RC:$src1, f128mem:$src, SSECC:$cc), asm,
1311              [(set RC:$dst, (Int RC:$src1, (memop addr:$src), imm:$cc))], d>;
1312   // Accept explicit immediate argument form instead of comparison code.
1313   let isAsmParserOnly = 1 in {
1314     def rri_alt : PIi8<0xC2, MRMSrcReg,
1315                (outs RC:$dst), (ins RC:$src1, RC:$src, i8imm:$src2),
1316                asm_alt, [], d>;
1317     def rmi_alt : PIi8<0xC2, MRMSrcMem,
1318                (outs RC:$dst), (ins RC:$src1, f128mem:$src, i8imm:$src2),
1319                asm_alt, [], d>;
1320   }
1321 }
1322
1323 let isAsmParserOnly = 1 in {
1324   defm VCMPPS : sse12_cmp_packed<VR128, f128mem, int_x86_sse_cmp_ps,
1325                  "cmp${cc}ps\t{$src, $src1, $dst|$dst, $src1, $src}",
1326                  "cmpps\t{$src2, $src, $src1, $dst|$dst, $src1, $src, $src2}",
1327                  SSEPackedSingle>, VEX_4V;
1328   defm VCMPPD : sse12_cmp_packed<VR128, f128mem, int_x86_sse2_cmp_pd,
1329                  "cmp${cc}pd\t{$src, $src1, $dst|$dst, $src1, $src}",
1330                  "cmppd\t{$src2, $src, $src1, $dst|$dst, $src1, $src, $src2}",
1331                  SSEPackedDouble>, OpSize, VEX_4V;
1332   defm VCMPPSY : sse12_cmp_packed<VR256, f256mem, int_x86_avx_cmp_ps_256,
1333                  "cmp${cc}ps\t{$src, $src1, $dst|$dst, $src1, $src}",
1334                  "cmpps\t{$src2, $src, $src1, $dst|$dst, $src1, $src, $src2}",
1335                  SSEPackedSingle>, VEX_4V;
1336   defm VCMPPDY : sse12_cmp_packed<VR256, f256mem, int_x86_avx_cmp_pd_256,
1337                  "cmp${cc}pd\t{$src, $src1, $dst|$dst, $src1, $src}",
1338                  "cmppd\t{$src2, $src, $src1, $dst|$dst, $src1, $src, $src2}",
1339                  SSEPackedDouble>, OpSize, VEX_4V;
1340 }
1341 let Constraints = "$src1 = $dst" in {
1342   defm CMPPS : sse12_cmp_packed<VR128, f128mem, int_x86_sse_cmp_ps,
1343                  "cmp${cc}ps\t{$src, $dst|$dst, $src}",
1344                  "cmpps\t{$src2, $src, $dst|$dst, $src, $src2}",
1345                  SSEPackedSingle>, TB;
1346   defm CMPPD : sse12_cmp_packed<VR128, f128mem, int_x86_sse2_cmp_pd,
1347                  "cmp${cc}pd\t{$src, $dst|$dst, $src}",
1348                  "cmppd\t{$src2, $src, $dst|$dst, $src, $src2}",
1349                  SSEPackedDouble>, TB, OpSize;
1350 }
1351
1352 def : Pat<(v4i32 (X86cmpps (v4f32 VR128:$src1), VR128:$src2, imm:$cc)),
1353           (CMPPSrri (v4f32 VR128:$src1), (v4f32 VR128:$src2), imm:$cc)>;
1354 def : Pat<(v4i32 (X86cmpps (v4f32 VR128:$src1), (memop addr:$src2), imm:$cc)),
1355           (CMPPSrmi (v4f32 VR128:$src1), addr:$src2, imm:$cc)>;
1356 def : Pat<(v2i64 (X86cmppd (v2f64 VR128:$src1), VR128:$src2, imm:$cc)),
1357           (CMPPDrri VR128:$src1, VR128:$src2, imm:$cc)>;
1358 def : Pat<(v2i64 (X86cmppd (v2f64 VR128:$src1), (memop addr:$src2), imm:$cc)),
1359           (CMPPDrmi VR128:$src1, addr:$src2, imm:$cc)>;
1360
1361 //===----------------------------------------------------------------------===//
1362 // SSE 1 & 2 - Shuffle Instructions
1363 //===----------------------------------------------------------------------===//
1364
1365 /// sse12_shuffle - sse 1 & 2 shuffle instructions
1366 multiclass sse12_shuffle<RegisterClass RC, X86MemOperand x86memop,
1367                          ValueType vt, string asm, PatFrag mem_frag,
1368                          Domain d, bit IsConvertibleToThreeAddress = 0> {
1369   def rmi : PIi8<0xC6, MRMSrcMem, (outs RC:$dst),
1370                    (ins RC:$src1, f128mem:$src2, i8imm:$src3), asm,
1371                    [(set RC:$dst, (vt (shufp:$src3
1372                             RC:$src1, (mem_frag addr:$src2))))], d>;
1373   let isConvertibleToThreeAddress = IsConvertibleToThreeAddress in
1374     def rri : PIi8<0xC6, MRMSrcReg, (outs RC:$dst),
1375                    (ins RC:$src1, RC:$src2, i8imm:$src3), asm,
1376                    [(set RC:$dst,
1377                             (vt (shufp:$src3 RC:$src1, RC:$src2)))], d>;
1378 }
1379
1380 let isAsmParserOnly = 1 in {
1381   defm VSHUFPS  : sse12_shuffle<VR128, f128mem, v4f32,
1382              "shufps\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}",
1383              memopv4f32, SSEPackedSingle>, VEX_4V;
1384   defm VSHUFPSY : sse12_shuffle<VR256, f256mem, v8f32,
1385              "shufps\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}",
1386              memopv8f32, SSEPackedSingle>, VEX_4V;
1387   defm VSHUFPD  : sse12_shuffle<VR128, f128mem, v2f64,
1388              "shufpd\t{$src3, $src2, $src1, $dst|$dst, $src2, $src2, $src3}",
1389              memopv2f64, SSEPackedDouble>, OpSize, VEX_4V;
1390   defm VSHUFPDY : sse12_shuffle<VR256, f256mem, v4f64,
1391              "shufpd\t{$src3, $src2, $src1, $dst|$dst, $src2, $src2, $src3}",
1392              memopv4f64, SSEPackedDouble>, OpSize, VEX_4V;
1393 }
1394
1395 let Constraints = "$src1 = $dst" in {
1396   defm SHUFPS : sse12_shuffle<VR128, f128mem, v4f32,
1397                     "shufps\t{$src3, $src2, $dst|$dst, $src2, $src3}",
1398                     memopv4f32, SSEPackedSingle, 1 /* cvt to pshufd */>,
1399                     TB;
1400   defm SHUFPD : sse12_shuffle<VR128, f128mem, v2f64,
1401                     "shufpd\t{$src3, $src2, $dst|$dst, $src2, $src3}",
1402                     memopv2f64, SSEPackedDouble>, TB, OpSize;
1403 }
1404
1405 //===----------------------------------------------------------------------===//
1406 // SSE 1 & 2 - Unpack Instructions
1407 //===----------------------------------------------------------------------===//
1408
1409 /// sse12_unpack_interleave - sse 1 & 2 unpack and interleave
1410 multiclass sse12_unpack_interleave<bits<8> opc, PatFrag OpNode, ValueType vt,
1411                                    PatFrag mem_frag, RegisterClass RC,
1412                                    X86MemOperand x86memop, string asm,
1413                                    Domain d> {
1414     def rr : PI<opc, MRMSrcReg,
1415                 (outs RC:$dst), (ins RC:$src1, RC:$src2),
1416                 asm, [(set RC:$dst,
1417                            (vt (OpNode RC:$src1, RC:$src2)))], d>;
1418     def rm : PI<opc, MRMSrcMem,
1419                 (outs RC:$dst), (ins RC:$src1, x86memop:$src2),
1420                 asm, [(set RC:$dst,
1421                            (vt (OpNode RC:$src1,
1422                                        (mem_frag addr:$src2))))], d>;
1423 }
1424
1425 let AddedComplexity = 10 in {
1426   let isAsmParserOnly = 1 in {
1427     defm VUNPCKHPS: sse12_unpack_interleave<0x15, unpckh, v4f32, memopv4f32,
1428           VR128, f128mem, "unpckhps\t{$src2, $src1, $dst|$dst, $src1, $src2}",
1429                          SSEPackedSingle>, VEX_4V;
1430     defm VUNPCKHPD: sse12_unpack_interleave<0x15, unpckh, v2f64, memopv2f64,
1431           VR128, f128mem, "unpckhpd\t{$src2, $src1, $dst|$dst, $src1, $src2}",
1432                          SSEPackedDouble>, OpSize, VEX_4V;
1433     defm VUNPCKLPS: sse12_unpack_interleave<0x14, unpckl, v4f32, memopv4f32,
1434           VR128, f128mem, "unpcklps\t{$src2, $src1, $dst|$dst, $src1, $src2}",
1435                          SSEPackedSingle>, VEX_4V;
1436     defm VUNPCKLPD: sse12_unpack_interleave<0x14, unpckl, v2f64, memopv2f64,
1437           VR128, f128mem, "unpcklpd\t{$src2, $src1, $dst|$dst, $src1, $src2}",
1438                          SSEPackedDouble>, OpSize, VEX_4V;
1439
1440     defm VUNPCKHPSY: sse12_unpack_interleave<0x15, unpckh, v8f32, memopv8f32,
1441           VR256, f256mem, "unpckhps\t{$src2, $src1, $dst|$dst, $src1, $src2}",
1442                          SSEPackedSingle>, VEX_4V;
1443     defm VUNPCKHPDY: sse12_unpack_interleave<0x15, unpckh, v4f64, memopv4f64,
1444           VR256, f256mem, "unpckhpd\t{$src2, $src1, $dst|$dst, $src1, $src2}",
1445                          SSEPackedDouble>, OpSize, VEX_4V;
1446     defm VUNPCKLPSY: sse12_unpack_interleave<0x14, unpckl, v8f32, memopv8f32,
1447           VR256, f256mem, "unpcklps\t{$src2, $src1, $dst|$dst, $src1, $src2}",
1448                          SSEPackedSingle>, VEX_4V;
1449     defm VUNPCKLPDY: sse12_unpack_interleave<0x14, unpckl, v4f64, memopv4f64,
1450           VR256, f256mem, "unpcklpd\t{$src2, $src1, $dst|$dst, $src1, $src2}",
1451                          SSEPackedDouble>, OpSize, VEX_4V;
1452   }
1453
1454   let Constraints = "$src1 = $dst" in {
1455     defm UNPCKHPS: sse12_unpack_interleave<0x15, unpckh, v4f32, memopv4f32,
1456           VR128, f128mem, "unpckhps\t{$src2, $dst|$dst, $src2}",
1457                          SSEPackedSingle>, TB;
1458     defm UNPCKHPD: sse12_unpack_interleave<0x15, unpckh, v2f64, memopv2f64,
1459           VR128, f128mem, "unpckhpd\t{$src2, $dst|$dst, $src2}",
1460                          SSEPackedDouble>, TB, OpSize;
1461     defm UNPCKLPS: sse12_unpack_interleave<0x14, unpckl, v4f32, memopv4f32,
1462           VR128, f128mem, "unpcklps\t{$src2, $dst|$dst, $src2}",
1463                          SSEPackedSingle>, TB;
1464     defm UNPCKLPD: sse12_unpack_interleave<0x14, unpckl, v2f64, memopv2f64,
1465           VR128, f128mem, "unpcklpd\t{$src2, $dst|$dst, $src2}",
1466                          SSEPackedDouble>, TB, OpSize;
1467   } // Constraints = "$src1 = $dst"
1468 } // AddedComplexity
1469
1470 //===----------------------------------------------------------------------===//
1471 // SSE 1 & 2 - Extract Floating-Point Sign mask
1472 //===----------------------------------------------------------------------===//
1473
1474 /// sse12_extr_sign_mask - sse 1 & 2 unpack and interleave
1475 multiclass sse12_extr_sign_mask<RegisterClass RC, Intrinsic Int, string asm,
1476                                 Domain d> {
1477   def rr : PI<0x50, MRMSrcReg, (outs GR32:$dst), (ins RC:$src),
1478               !strconcat(asm, "\t{$src, $dst|$dst, $src}"),
1479                      [(set GR32:$dst, (Int RC:$src))], d>;
1480 }
1481
1482 // Mask creation
1483 defm MOVMSKPS : sse12_extr_sign_mask<VR128, int_x86_sse_movmsk_ps, "movmskps",
1484                                      SSEPackedSingle>, TB;
1485 defm MOVMSKPD : sse12_extr_sign_mask<VR128, int_x86_sse2_movmsk_pd, "movmskpd",
1486                                      SSEPackedDouble>, TB, OpSize;
1487
1488 let isAsmParserOnly = 1 in {
1489   defm VMOVMSKPS : sse12_extr_sign_mask<VR128, int_x86_sse_movmsk_ps,
1490                                         "movmskps", SSEPackedSingle>, VEX;
1491   defm VMOVMSKPD : sse12_extr_sign_mask<VR128, int_x86_sse2_movmsk_pd,
1492                                         "movmskpd", SSEPackedDouble>, OpSize,
1493                                         VEX;
1494   defm VMOVMSKPSY : sse12_extr_sign_mask<VR256, int_x86_avx_movmsk_ps_256,
1495                                         "movmskps", SSEPackedSingle>, VEX;
1496   defm VMOVMSKPDY : sse12_extr_sign_mask<VR256, int_x86_avx_movmsk_pd_256,
1497                                         "movmskpd", SSEPackedDouble>, OpSize,
1498                                         VEX;
1499
1500   // Assembler Only
1501   def VMOVMSKPSr64r : PI<0x50, MRMSrcReg, (outs GR64:$dst), (ins VR128:$src),
1502              "movmskps\t{$src, $dst|$dst, $src}", [], SSEPackedSingle>, VEX;
1503   def VMOVMSKPDr64r : PI<0x50, MRMSrcReg, (outs GR64:$dst), (ins VR128:$src),
1504              "movmskpd\t{$src, $dst|$dst, $src}", [], SSEPackedDouble>, OpSize,
1505              VEX;
1506   def VMOVMSKPSYr64r : PI<0x50, MRMSrcReg, (outs GR64:$dst), (ins VR256:$src),
1507              "movmskps\t{$src, $dst|$dst, $src}", [], SSEPackedSingle>, VEX;
1508   def VMOVMSKPDYr64r : PI<0x50, MRMSrcReg, (outs GR64:$dst), (ins VR256:$src),
1509              "movmskpd\t{$src, $dst|$dst, $src}", [], SSEPackedDouble>, OpSize,
1510              VEX;
1511 }
1512
1513 //===----------------------------------------------------------------------===//
1514 // SSE 1 & 2 - Misc aliasing of packed SSE 1 & 2 instructions
1515 //===----------------------------------------------------------------------===//
1516
1517 // Aliases of packed SSE1 & SSE2 instructions for scalar use. These all have
1518 // names that start with 'Fs'.
1519
1520 // Alias instructions that map fld0 to pxor for sse.
1521 let isReMaterializable = 1, isAsCheapAsAMove = 1, isCodeGenOnly = 1,
1522     canFoldAsLoad = 1 in {
1523   // FIXME: Set encoding to pseudo!
1524 def FsFLD0SS : I<0xEF, MRMInitReg, (outs FR32:$dst), (ins), "",
1525                  [(set FR32:$dst, fp32imm0)]>,
1526                  Requires<[HasSSE1]>, TB, OpSize;
1527 def FsFLD0SD : I<0xEF, MRMInitReg, (outs FR64:$dst), (ins), "",
1528                  [(set FR64:$dst, fpimm0)]>,
1529                Requires<[HasSSE2]>, TB, OpSize;
1530 }
1531
1532 // Alias instruction to do FR32 or FR64 reg-to-reg copy using movaps. Upper
1533 // bits are disregarded.
1534 let neverHasSideEffects = 1 in {
1535 def FsMOVAPSrr : PSI<0x28, MRMSrcReg, (outs FR32:$dst), (ins FR32:$src),
1536                      "movaps\t{$src, $dst|$dst, $src}", []>;
1537 def FsMOVAPDrr : PDI<0x28, MRMSrcReg, (outs FR64:$dst), (ins FR64:$src),
1538                      "movapd\t{$src, $dst|$dst, $src}", []>;
1539 }
1540
1541 // Alias instruction to load FR32 or FR64 from f128mem using movaps. Upper
1542 // bits are disregarded.
1543 let canFoldAsLoad = 1, isReMaterializable = 1 in {
1544 def FsMOVAPSrm : PSI<0x28, MRMSrcMem, (outs FR32:$dst), (ins f128mem:$src),
1545                      "movaps\t{$src, $dst|$dst, $src}",
1546                      [(set FR32:$dst, (alignedloadfsf32 addr:$src))]>;
1547 def FsMOVAPDrm : PDI<0x28, MRMSrcMem, (outs FR64:$dst), (ins f128mem:$src),
1548                      "movapd\t{$src, $dst|$dst, $src}",
1549                      [(set FR64:$dst, (alignedloadfsf64 addr:$src))]>;
1550 }
1551
1552 //===----------------------------------------------------------------------===//
1553 // SSE 1 & 2 - Logical Instructions
1554 //===----------------------------------------------------------------------===//
1555
1556 /// sse12_fp_alias_pack_logical - SSE 1 & 2 aliased packed FP logical ops
1557 ///
1558 multiclass sse12_fp_alias_pack_logical<bits<8> opc, string OpcodeStr,
1559                                        SDNode OpNode> {
1560   let isAsmParserOnly = 1 in {
1561     defm V#NAME#PS : sse12_fp_packed<opc, !strconcat(OpcodeStr, "ps"), OpNode,
1562                 FR32, f32, f128mem, memopfsf32, SSEPackedSingle, 0>, VEX_4V;
1563
1564     defm V#NAME#PD : sse12_fp_packed<opc, !strconcat(OpcodeStr, "pd"), OpNode,
1565           FR64, f64, f128mem, memopfsf64, SSEPackedDouble, 0>, OpSize, VEX_4V;
1566   }
1567
1568   let Constraints = "$src1 = $dst" in {
1569     defm PS : sse12_fp_packed<opc, !strconcat(OpcodeStr, "ps"), OpNode, FR32,
1570                 f32, f128mem, memopfsf32, SSEPackedSingle>, TB;
1571
1572     defm PD : sse12_fp_packed<opc, !strconcat(OpcodeStr, "pd"), OpNode, FR64,
1573                 f64, f128mem, memopfsf64, SSEPackedDouble>, TB, OpSize;
1574   }
1575 }
1576
1577 // Alias bitwise logical operations using SSE logical ops on packed FP values.
1578 let mayLoad = 0 in {
1579   defm FsAND  : sse12_fp_alias_pack_logical<0x54, "and", X86fand>;
1580   defm FsOR   : sse12_fp_alias_pack_logical<0x56, "or", X86for>;
1581   defm FsXOR  : sse12_fp_alias_pack_logical<0x57, "xor", X86fxor>;
1582 }
1583
1584 let neverHasSideEffects = 1, Pattern = []<dag>, isCommutable = 0 in
1585   defm FsANDN : sse12_fp_alias_pack_logical<0x55, "andn", undef>;
1586
1587 /// sse12_fp_packed_logical - SSE 1 & 2 packed FP logical ops
1588 ///
1589 multiclass sse12_fp_packed_logical<bits<8> opc, string OpcodeStr,
1590                                  SDNode OpNode, int HasPat = 0,
1591                                  list<list<dag>> Pattern = []> {
1592   let isAsmParserOnly = 1, Pattern = []<dag> in {
1593     defm V#NAME#PS : sse12_fp_packed_logical_rm<opc, VR128, SSEPackedSingle,
1594          !strconcat(OpcodeStr, "ps"), f128mem,
1595          !if(HasPat, Pattern[0], // rr
1596                      [(set VR128:$dst, (v2i64 (OpNode VR128:$src1,
1597                                                       VR128:$src2)))]),
1598          !if(HasPat, Pattern[2], // rm
1599                      [(set VR128:$dst, (OpNode (bc_v2i64 (v4f32 VR128:$src1)),
1600                                                (memopv2i64 addr:$src2)))]), 0>,
1601                                                VEX_4V;
1602
1603     defm V#NAME#PD : sse12_fp_packed_logical_rm<opc, VR128, SSEPackedDouble,
1604          !strconcat(OpcodeStr, "pd"), f128mem,
1605          !if(HasPat, Pattern[1], // rr
1606                      [(set VR128:$dst, (OpNode (bc_v2i64 (v2f64 VR128:$src1)),
1607                                                (bc_v2i64 (v2f64
1608                                                VR128:$src2))))]),
1609          !if(HasPat, Pattern[3], // rm
1610                      [(set VR128:$dst, (OpNode (bc_v2i64 (v2f64 VR128:$src1)),
1611                                                (memopv2i64 addr:$src2)))]), 0>,
1612                                                                OpSize, VEX_4V;
1613   }
1614   let Constraints = "$src1 = $dst" in {
1615     defm PS : sse12_fp_packed_logical_rm<opc, VR128, SSEPackedSingle,
1616          !strconcat(OpcodeStr, "ps"), f128mem,
1617          !if(HasPat, Pattern[0], // rr
1618                      [(set VR128:$dst, (v2i64 (OpNode VR128:$src1,
1619                                                       VR128:$src2)))]),
1620          !if(HasPat, Pattern[2], // rm
1621                      [(set VR128:$dst, (OpNode (bc_v2i64 (v4f32 VR128:$src1)),
1622                                                (memopv2i64 addr:$src2)))])>, TB;
1623
1624     defm PD : sse12_fp_packed_logical_rm<opc, VR128, SSEPackedDouble,
1625          !strconcat(OpcodeStr, "pd"), f128mem,
1626          !if(HasPat, Pattern[1], // rr
1627                      [(set VR128:$dst, (OpNode (bc_v2i64 (v2f64 VR128:$src1)),
1628                                                (bc_v2i64 (v2f64
1629                                                VR128:$src2))))]),
1630          !if(HasPat, Pattern[3], // rm
1631                      [(set VR128:$dst, (OpNode (bc_v2i64 (v2f64 VR128:$src1)),
1632                                                (memopv2i64 addr:$src2)))])>,
1633                                                                     TB, OpSize;
1634   }
1635 }
1636
1637 /// sse12_fp_packed_logical_y - AVX 256-bit SSE 1 & 2 logical ops forms
1638 ///
1639 let isAsmParserOnly = 1 in {
1640 multiclass sse12_fp_packed_logical_y<bits<8> opc, string OpcodeStr> {
1641     defm PSY : sse12_fp_packed_logical_rm<opc, VR256, SSEPackedSingle,
1642           !strconcat(OpcodeStr, "ps"), f256mem, [], [], 0>, VEX_4V;
1643
1644     defm PDY : sse12_fp_packed_logical_rm<opc, VR256, SSEPackedDouble,
1645           !strconcat(OpcodeStr, "pd"), f256mem, [], [], 0>, OpSize, VEX_4V;
1646 }
1647 }
1648
1649 // AVX 256-bit packed logical ops forms
1650 defm VAND : sse12_fp_packed_logical_y<0x54, "and">;
1651 defm VOR  : sse12_fp_packed_logical_y<0x56, "or">;
1652 defm VXOR : sse12_fp_packed_logical_y<0x57, "xor">;
1653 let isCommutable = 0 in
1654   defm VANDN : sse12_fp_packed_logical_y<0x55, "andn">;
1655
1656 defm AND  : sse12_fp_packed_logical<0x54, "and", and>;
1657 defm OR   : sse12_fp_packed_logical<0x56, "or", or>;
1658 defm XOR  : sse12_fp_packed_logical<0x57, "xor", xor>;
1659 let isCommutable = 0 in
1660   defm ANDN : sse12_fp_packed_logical<0x55, "andn", undef /* dummy */, 1, [
1661     // single r+r
1662     [(set VR128:$dst, (v2i64 (and (xor VR128:$src1,
1663                                        (bc_v2i64 (v4i32 immAllOnesV))),
1664                                    VR128:$src2)))],
1665     // double r+r
1666     [(set VR128:$dst, (and (vnot (bc_v2i64 (v2f64 VR128:$src1))),
1667                                  (bc_v2i64 (v2f64 VR128:$src2))))],
1668     // single r+m
1669     [(set VR128:$dst, (v2i64 (and (xor (bc_v2i64 (v4f32 VR128:$src1)),
1670                                        (bc_v2i64 (v4i32 immAllOnesV))),
1671                                   (memopv2i64 addr:$src2))))],
1672     // double r+m
1673     [(set VR128:$dst, (and (vnot (bc_v2i64 (v2f64 VR128:$src1))),
1674                            (memopv2i64 addr:$src2)))]]>;
1675
1676 //===----------------------------------------------------------------------===//
1677 // SSE 1 & 2 - Arithmetic Instructions
1678 //===----------------------------------------------------------------------===//
1679
1680 /// basic_sse12_fp_binop_xxx - SSE 1 & 2 binops come in both scalar and
1681 /// vector forms.
1682 ///
1683 /// In addition, we also have a special variant of the scalar form here to
1684 /// represent the associated intrinsic operation.  This form is unlike the
1685 /// plain scalar form, in that it takes an entire vector (instead of a scalar)
1686 /// and leaves the top elements unmodified (therefore these cannot be commuted).
1687 ///
1688 /// These three forms can each be reg+reg or reg+mem.
1689 ///
1690
1691 /// FIXME: once all 256-bit intrinsics are matched, cleanup and refactor those
1692 /// classes below
1693 multiclass basic_sse12_fp_binop_s<bits<8> opc, string OpcodeStr, SDNode OpNode,
1694                                   bit Is2Addr = 1> {
1695   defm SS : sse12_fp_scalar<opc, !strconcat(OpcodeStr, "ss"),
1696                             OpNode, FR32, f32mem, Is2Addr>, XS;
1697   defm SD : sse12_fp_scalar<opc, !strconcat(OpcodeStr, "sd"),
1698                             OpNode, FR64, f64mem, Is2Addr>, XD;
1699 }
1700
1701 multiclass basic_sse12_fp_binop_p<bits<8> opc, string OpcodeStr, SDNode OpNode,
1702                                    bit Is2Addr = 1> {
1703   let mayLoad = 0 in {
1704   defm PS : sse12_fp_packed<opc, !strconcat(OpcodeStr, "ps"), OpNode, VR128,
1705               v4f32, f128mem, memopv4f32, SSEPackedSingle, Is2Addr>, TB;
1706   defm PD : sse12_fp_packed<opc, !strconcat(OpcodeStr, "pd"), OpNode, VR128,
1707               v2f64, f128mem, memopv2f64, SSEPackedDouble, Is2Addr>, TB, OpSize;
1708   }
1709 }
1710
1711 multiclass basic_sse12_fp_binop_p_y<bits<8> opc, string OpcodeStr,
1712                                     SDNode OpNode> {
1713   let mayLoad = 0 in {
1714     defm PSY : sse12_fp_packed<opc, !strconcat(OpcodeStr, "ps"), OpNode, VR256,
1715                 v8f32, f256mem, memopv8f32, SSEPackedSingle, 0>, TB;
1716     defm PDY : sse12_fp_packed<opc, !strconcat(OpcodeStr, "pd"), OpNode, VR256,
1717                 v4f64, f256mem, memopv4f64, SSEPackedDouble, 0>, TB, OpSize;
1718   }
1719 }
1720
1721 multiclass basic_sse12_fp_binop_s_int<bits<8> opc, string OpcodeStr,
1722                                       bit Is2Addr = 1> {
1723   defm SS : sse12_fp_scalar_int<opc, OpcodeStr, VR128,
1724      !strconcat(OpcodeStr, "ss"), "", "_ss", ssmem, sse_load_f32, Is2Addr>, XS;
1725   defm SD : sse12_fp_scalar_int<opc, OpcodeStr, VR128,
1726      !strconcat(OpcodeStr, "sd"), "2", "_sd", sdmem, sse_load_f64, Is2Addr>, XD;
1727 }
1728
1729 multiclass basic_sse12_fp_binop_p_int<bits<8> opc, string OpcodeStr,
1730                                       bit Is2Addr = 1> {
1731   defm PS : sse12_fp_packed_int<opc, OpcodeStr, VR128,
1732      !strconcat(OpcodeStr, "ps"), "sse", "_ps", f128mem, memopv4f32,
1733                                               SSEPackedSingle, Is2Addr>, TB;
1734
1735   defm PD : sse12_fp_packed_int<opc, OpcodeStr, VR128,
1736      !strconcat(OpcodeStr, "pd"), "sse2", "_pd", f128mem, memopv2f64,
1737                                       SSEPackedDouble, Is2Addr>, TB, OpSize;
1738 }
1739
1740 multiclass basic_sse12_fp_binop_p_y_int<bits<8> opc, string OpcodeStr> {
1741   defm PSY : sse12_fp_packed_int<opc, OpcodeStr, VR256,
1742      !strconcat(OpcodeStr, "ps"), "avx", "_ps_256", f256mem, memopv8f32,
1743       SSEPackedSingle, 0>, TB;
1744
1745   defm PDY : sse12_fp_packed_int<opc, OpcodeStr, VR256,
1746      !strconcat(OpcodeStr, "pd"), "avx", "_pd_256", f256mem, memopv4f64,
1747       SSEPackedDouble, 0>, TB, OpSize;
1748 }
1749
1750 // Binary Arithmetic instructions
1751 let isAsmParserOnly = 1 in {
1752   defm VADD : basic_sse12_fp_binop_s<0x58, "add", fadd, 0>,
1753               basic_sse12_fp_binop_s_int<0x58, "add", 0>,
1754               basic_sse12_fp_binop_p<0x58, "add", fadd, 0>,
1755               basic_sse12_fp_binop_p_y<0x58, "add", fadd>, VEX_4V;
1756   defm VMUL : basic_sse12_fp_binop_s<0x59, "mul", fmul, 0>,
1757               basic_sse12_fp_binop_s_int<0x59, "mul", 0>,
1758               basic_sse12_fp_binop_p<0x59, "mul", fmul, 0>,
1759               basic_sse12_fp_binop_p_y<0x59, "mul", fmul>, VEX_4V;
1760
1761   let isCommutable = 0 in {
1762     defm VSUB : basic_sse12_fp_binop_s<0x5C, "sub", fsub, 0>,
1763                 basic_sse12_fp_binop_s_int<0x5C, "sub", 0>,
1764                 basic_sse12_fp_binop_p<0x5C, "sub", fsub, 0>,
1765                 basic_sse12_fp_binop_p_y<0x5C, "sub", fsub>, VEX_4V;
1766     defm VDIV : basic_sse12_fp_binop_s<0x5E, "div", fdiv, 0>,
1767                 basic_sse12_fp_binop_s_int<0x5E, "div", 0>,
1768                 basic_sse12_fp_binop_p<0x5E, "div", fdiv, 0>,
1769                 basic_sse12_fp_binop_p_y<0x5E, "div", fdiv>, VEX_4V;
1770     defm VMAX : basic_sse12_fp_binop_s<0x5F, "max", X86fmax, 0>,
1771                 basic_sse12_fp_binop_s_int<0x5F, "max", 0>,
1772                 basic_sse12_fp_binop_p<0x5F, "max", X86fmax, 0>,
1773                 basic_sse12_fp_binop_p_int<0x5F, "max", 0>,
1774                 basic_sse12_fp_binop_p_y<0x5F, "max", X86fmax>,
1775                 basic_sse12_fp_binop_p_y_int<0x5F, "max">, VEX_4V;
1776     defm VMIN : basic_sse12_fp_binop_s<0x5D, "min", X86fmin, 0>,
1777                 basic_sse12_fp_binop_s_int<0x5D, "min", 0>,
1778                 basic_sse12_fp_binop_p<0x5D, "min", X86fmin, 0>,
1779                 basic_sse12_fp_binop_p_int<0x5D, "min", 0>,
1780                 basic_sse12_fp_binop_p_y_int<0x5D, "min">,
1781                 basic_sse12_fp_binop_p_y<0x5D, "min", X86fmin>, VEX_4V;
1782   }
1783 }
1784
1785 let Constraints = "$src1 = $dst" in {
1786   defm ADD : basic_sse12_fp_binop_s<0x58, "add", fadd>,
1787              basic_sse12_fp_binop_p<0x58, "add", fadd>,
1788              basic_sse12_fp_binop_s_int<0x58, "add">;
1789   defm MUL : basic_sse12_fp_binop_s<0x59, "mul", fmul>,
1790              basic_sse12_fp_binop_p<0x59, "mul", fmul>,
1791              basic_sse12_fp_binop_s_int<0x59, "mul">;
1792
1793   let isCommutable = 0 in {
1794     defm SUB : basic_sse12_fp_binop_s<0x5C, "sub", fsub>,
1795                basic_sse12_fp_binop_p<0x5C, "sub", fsub>,
1796                basic_sse12_fp_binop_s_int<0x5C, "sub">;
1797     defm DIV : basic_sse12_fp_binop_s<0x5E, "div", fdiv>,
1798                basic_sse12_fp_binop_p<0x5E, "div", fdiv>,
1799                basic_sse12_fp_binop_s_int<0x5E, "div">;
1800     defm MAX : basic_sse12_fp_binop_s<0x5F, "max", X86fmax>,
1801                basic_sse12_fp_binop_p<0x5F, "max", X86fmax>,
1802                basic_sse12_fp_binop_s_int<0x5F, "max">,
1803                basic_sse12_fp_binop_p_int<0x5F, "max">;
1804     defm MIN : basic_sse12_fp_binop_s<0x5D, "min", X86fmin>,
1805                basic_sse12_fp_binop_p<0x5D, "min", X86fmin>,
1806                basic_sse12_fp_binop_s_int<0x5D, "min">,
1807                basic_sse12_fp_binop_p_int<0x5D, "min">;
1808   }
1809 }
1810
1811 /// Unop Arithmetic
1812 /// In addition, we also have a special variant of the scalar form here to
1813 /// represent the associated intrinsic operation.  This form is unlike the
1814 /// plain scalar form, in that it takes an entire vector (instead of a
1815 /// scalar) and leaves the top elements undefined.
1816 ///
1817 /// And, we have a special variant form for a full-vector intrinsic form.
1818
1819 /// sse1_fp_unop_s - SSE1 unops in scalar form.
1820 multiclass sse1_fp_unop_s<bits<8> opc, string OpcodeStr,
1821                           SDNode OpNode, Intrinsic F32Int> {
1822   def SSr : SSI<opc, MRMSrcReg, (outs FR32:$dst), (ins FR32:$src),
1823                 !strconcat(OpcodeStr, "ss\t{$src, $dst|$dst, $src}"),
1824                 [(set FR32:$dst, (OpNode FR32:$src))]>;
1825   // For scalar unary operations, fold a load into the operation
1826   // only in OptForSize mode. It eliminates an instruction, but it also
1827   // eliminates a whole-register clobber (the load), so it introduces a
1828   // partial register update condition.
1829   def SSm : I<opc, MRMSrcMem, (outs FR32:$dst), (ins f32mem:$src),
1830                 !strconcat(OpcodeStr, "ss\t{$src, $dst|$dst, $src}"),
1831                 [(set FR32:$dst, (OpNode (load addr:$src)))]>, XS,
1832             Requires<[HasSSE1, OptForSize]>;
1833   def SSr_Int : SSI<opc, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
1834                     !strconcat(OpcodeStr, "ss\t{$src, $dst|$dst, $src}"),
1835                     [(set VR128:$dst, (F32Int VR128:$src))]>;
1836   def SSm_Int : SSI<opc, MRMSrcMem, (outs VR128:$dst), (ins ssmem:$src),
1837                     !strconcat(OpcodeStr, "ss\t{$src, $dst|$dst, $src}"),
1838                     [(set VR128:$dst, (F32Int sse_load_f32:$src))]>;
1839 }
1840
1841 /// sse1_fp_unop_s_avx - AVX SSE1 unops in scalar form.
1842 multiclass sse1_fp_unop_s_avx<bits<8> opc, string OpcodeStr,
1843                               SDNode OpNode, Intrinsic F32Int> {
1844   def SSr : SSI<opc, MRMSrcReg, (outs FR32:$dst), (ins FR32:$src1, FR32:$src2),
1845                 !strconcat(OpcodeStr,
1846                            "ss\t{$src2, $src1, $dst|$dst, $src1, $src2}"), []>;
1847   def SSm : I<opc, MRMSrcMem, (outs FR32:$dst), (ins FR32:$src1, f32mem:$src2),
1848                 !strconcat(OpcodeStr,
1849                            "ss\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
1850                 []>, XS, Requires<[HasAVX, OptForSize]>;
1851   def SSr_Int : SSI<opc, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
1852                 !strconcat(OpcodeStr,
1853                            "ss\t{$src, $dst, $dst|$dst, $dst, $src}"),
1854                 [(set VR128:$dst, (F32Int VR128:$src))]>;
1855   def SSm_Int : SSI<opc, MRMSrcMem, (outs VR128:$dst), (ins ssmem:$src),
1856                 !strconcat(OpcodeStr,
1857                            "ss\t{$src, $dst, $dst|$dst, $dst, $src}"),
1858                 [(set VR128:$dst, (F32Int sse_load_f32:$src))]>;
1859 }
1860
1861 /// sse1_fp_unop_p - SSE1 unops in packed form.
1862 multiclass sse1_fp_unop_p<bits<8> opc, string OpcodeStr, SDNode OpNode> {
1863   def PSr : PSI<opc, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
1864               !strconcat(OpcodeStr, "ps\t{$src, $dst|$dst, $src}"),
1865               [(set VR128:$dst, (v4f32 (OpNode VR128:$src)))]>;
1866   def PSm : PSI<opc, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
1867                 !strconcat(OpcodeStr, "ps\t{$src, $dst|$dst, $src}"),
1868                 [(set VR128:$dst, (OpNode (memopv4f32 addr:$src)))]>;
1869 }
1870
1871 /// sse1_fp_unop_p_y - AVX 256-bit SSE1 unops in packed form.
1872 multiclass sse1_fp_unop_p_y<bits<8> opc, string OpcodeStr, SDNode OpNode> {
1873   def PSYr : PSI<opc, MRMSrcReg, (outs VR256:$dst), (ins VR256:$src),
1874               !strconcat(OpcodeStr, "ps\t{$src, $dst|$dst, $src}"),
1875               [(set VR256:$dst, (v8f32 (OpNode VR256:$src)))]>;
1876   def PSYm : PSI<opc, MRMSrcMem, (outs VR256:$dst), (ins f256mem:$src),
1877                 !strconcat(OpcodeStr, "ps\t{$src, $dst|$dst, $src}"),
1878                 [(set VR256:$dst, (OpNode (memopv8f32 addr:$src)))]>;
1879 }
1880
1881 /// sse1_fp_unop_p_int - SSE1 intrinsics unops in packed forms.
1882 multiclass sse1_fp_unop_p_int<bits<8> opc, string OpcodeStr,
1883                               Intrinsic V4F32Int> {
1884   def PSr_Int : PSI<opc, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
1885                     !strconcat(OpcodeStr, "ps\t{$src, $dst|$dst, $src}"),
1886                     [(set VR128:$dst, (V4F32Int VR128:$src))]>;
1887   def PSm_Int : PSI<opc, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
1888                     !strconcat(OpcodeStr, "ps\t{$src, $dst|$dst, $src}"),
1889                     [(set VR128:$dst, (V4F32Int (memopv4f32 addr:$src)))]>;
1890 }
1891
1892 /// sse1_fp_unop_p_y_int - AVX 256-bit intrinsics unops in packed forms.
1893 multiclass sse1_fp_unop_p_y_int<bits<8> opc, string OpcodeStr,
1894                                 Intrinsic V4F32Int> {
1895   def PSYr_Int : PSI<opc, MRMSrcReg, (outs VR256:$dst), (ins VR256:$src),
1896                     !strconcat(OpcodeStr, "ps\t{$src, $dst|$dst, $src}"),
1897                     [(set VR256:$dst, (V4F32Int VR256:$src))]>;
1898   def PSYm_Int : PSI<opc, MRMSrcMem, (outs VR256:$dst), (ins f256mem:$src),
1899                     !strconcat(OpcodeStr, "ps\t{$src, $dst|$dst, $src}"),
1900                     [(set VR256:$dst, (V4F32Int (memopv8f32 addr:$src)))]>;
1901 }
1902
1903 /// sse2_fp_unop_s - SSE2 unops in scalar form.
1904 multiclass sse2_fp_unop_s<bits<8> opc, string OpcodeStr,
1905                           SDNode OpNode, Intrinsic F64Int> {
1906   def SDr : SDI<opc, MRMSrcReg, (outs FR64:$dst), (ins FR64:$src),
1907                 !strconcat(OpcodeStr, "sd\t{$src, $dst|$dst, $src}"),
1908                 [(set FR64:$dst, (OpNode FR64:$src))]>;
1909   // See the comments in sse1_fp_unop_s for why this is OptForSize.
1910   def SDm : I<opc, MRMSrcMem, (outs FR64:$dst), (ins f64mem:$src),
1911                 !strconcat(OpcodeStr, "sd\t{$src, $dst|$dst, $src}"),
1912                 [(set FR64:$dst, (OpNode (load addr:$src)))]>, XD,
1913             Requires<[HasSSE2, OptForSize]>;
1914   def SDr_Int : SDI<opc, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
1915                     !strconcat(OpcodeStr, "sd\t{$src, $dst|$dst, $src}"),
1916                     [(set VR128:$dst, (F64Int VR128:$src))]>;
1917   def SDm_Int : SDI<opc, MRMSrcMem, (outs VR128:$dst), (ins sdmem:$src),
1918                     !strconcat(OpcodeStr, "sd\t{$src, $dst|$dst, $src}"),
1919                     [(set VR128:$dst, (F64Int sse_load_f64:$src))]>;
1920 }
1921
1922 /// sse2_fp_unop_s_avx - AVX SSE2 unops in scalar form.
1923 multiclass sse2_fp_unop_s_avx<bits<8> opc, string OpcodeStr,
1924                               SDNode OpNode, Intrinsic F64Int> {
1925   def SDr : SDI<opc, MRMSrcReg, (outs FR64:$dst), (ins FR64:$src1, FR64:$src2),
1926                !strconcat(OpcodeStr,
1927                           "sd\t{$src2, $src1, $dst|$dst, $src1, $src2}"), []>;
1928   def SDm : SDI<opc, MRMSrcMem, (outs FR64:$dst),
1929                (ins FR64:$src1, f64mem:$src2),
1930                !strconcat(OpcodeStr,
1931                           "sd\t{$src2, $src1, $dst|$dst, $src1, $src2}"), []>;
1932   def SDr_Int : SDI<opc, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
1933            !strconcat(OpcodeStr, "sd\t{$src, $dst, $dst|$dst, $dst, $src}"),
1934            [(set VR128:$dst, (F64Int VR128:$src))]>;
1935   def SDm_Int : SDI<opc, MRMSrcMem, (outs VR128:$dst), (ins sdmem:$src),
1936            !strconcat(OpcodeStr, "sd\t{$src, $dst, $dst|$dst, $dst, $src}"),
1937            [(set VR128:$dst, (F64Int sse_load_f64:$src))]>;
1938 }
1939
1940 /// sse2_fp_unop_p - SSE2 unops in vector forms.
1941 multiclass sse2_fp_unop_p<bits<8> opc, string OpcodeStr,
1942                           SDNode OpNode> {
1943   def PDr : PDI<opc, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
1944               !strconcat(OpcodeStr, "pd\t{$src, $dst|$dst, $src}"),
1945               [(set VR128:$dst, (v2f64 (OpNode VR128:$src)))]>;
1946   def PDm : PDI<opc, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
1947                 !strconcat(OpcodeStr, "pd\t{$src, $dst|$dst, $src}"),
1948                 [(set VR128:$dst, (OpNode (memopv2f64 addr:$src)))]>;
1949 }
1950
1951 /// sse2_fp_unop_p_y - AVX SSE2 256-bit unops in vector forms.
1952 multiclass sse2_fp_unop_p_y<bits<8> opc, string OpcodeStr, SDNode OpNode> {
1953   def PDYr : PDI<opc, MRMSrcReg, (outs VR256:$dst), (ins VR256:$src),
1954               !strconcat(OpcodeStr, "pd\t{$src, $dst|$dst, $src}"),
1955               [(set VR256:$dst, (v4f64 (OpNode VR256:$src)))]>;
1956   def PDYm : PDI<opc, MRMSrcMem, (outs VR256:$dst), (ins f256mem:$src),
1957                 !strconcat(OpcodeStr, "pd\t{$src, $dst|$dst, $src}"),
1958                 [(set VR256:$dst, (OpNode (memopv4f64 addr:$src)))]>;
1959 }
1960
1961 /// sse2_fp_unop_p_int - SSE2 intrinsic unops in vector forms.
1962 multiclass sse2_fp_unop_p_int<bits<8> opc, string OpcodeStr,
1963                               Intrinsic V2F64Int> {
1964   def PDr_Int : PDI<opc, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
1965                     !strconcat(OpcodeStr, "pd\t{$src, $dst|$dst, $src}"),
1966                     [(set VR128:$dst, (V2F64Int VR128:$src))]>;
1967   def PDm_Int : PDI<opc, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
1968                     !strconcat(OpcodeStr, "pd\t{$src, $dst|$dst, $src}"),
1969                     [(set VR128:$dst, (V2F64Int (memopv2f64 addr:$src)))]>;
1970 }
1971
1972 /// sse2_fp_unop_p_y_int - AVX 256-bit intrinsic unops in vector forms.
1973 multiclass sse2_fp_unop_p_y_int<bits<8> opc, string OpcodeStr,
1974                                 Intrinsic V2F64Int> {
1975   def PDYr_Int : PDI<opc, MRMSrcReg, (outs VR256:$dst), (ins VR256:$src),
1976                     !strconcat(OpcodeStr, "pd\t{$src, $dst|$dst, $src}"),
1977                     [(set VR256:$dst, (V2F64Int VR256:$src))]>;
1978   def PDYm_Int : PDI<opc, MRMSrcMem, (outs VR256:$dst), (ins f256mem:$src),
1979                     !strconcat(OpcodeStr, "pd\t{$src, $dst|$dst, $src}"),
1980                     [(set VR256:$dst, (V2F64Int (memopv4f64 addr:$src)))]>;
1981 }
1982
1983 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
1984   // Square root.
1985   defm VSQRT  : sse1_fp_unop_s_avx<0x51, "vsqrt", fsqrt, int_x86_sse_sqrt_ss>,
1986                 sse2_fp_unop_s_avx<0x51, "vsqrt", fsqrt, int_x86_sse2_sqrt_sd>,
1987                 VEX_4V;
1988
1989   defm VSQRT  : sse1_fp_unop_p<0x51, "vsqrt", fsqrt>,
1990                 sse2_fp_unop_p<0x51, "vsqrt", fsqrt>,
1991                 sse1_fp_unop_p_y<0x51, "vsqrt", fsqrt>,
1992                 sse2_fp_unop_p_y<0x51, "vsqrt", fsqrt>,
1993                 sse1_fp_unop_p_int<0x51, "vsqrt", int_x86_sse_sqrt_ps>,
1994                 sse2_fp_unop_p_int<0x51, "vsqrt", int_x86_sse2_sqrt_pd>,
1995                 sse1_fp_unop_p_y_int<0x51, "vsqrt", int_x86_avx_sqrt_ps_256>,
1996                 sse2_fp_unop_p_y_int<0x51, "vsqrt", int_x86_avx_sqrt_pd_256>,
1997                 VEX;
1998
1999   // Reciprocal approximations. Note that these typically require refinement
2000   // in order to obtain suitable precision.
2001   defm VRSQRT : sse1_fp_unop_s_avx<0x52, "vrsqrt", X86frsqrt,
2002                                    int_x86_sse_rsqrt_ss>, VEX_4V;
2003   defm VRSQRT : sse1_fp_unop_p<0x52, "vrsqrt", X86frsqrt>,
2004                 sse1_fp_unop_p_y<0x52, "vrsqrt", X86frsqrt>,
2005                 sse1_fp_unop_p_y_int<0x52, "vrsqrt", int_x86_avx_rsqrt_ps_256>,
2006                 sse1_fp_unop_p_int<0x52, "vrsqrt", int_x86_sse_rsqrt_ps>, VEX;
2007
2008   defm VRCP   : sse1_fp_unop_s_avx<0x53, "vrcp", X86frcp, int_x86_sse_rcp_ss>,
2009                                    VEX_4V;
2010   defm VRCP   : sse1_fp_unop_p<0x53, "vrcp", X86frcp>,
2011                 sse1_fp_unop_p_y<0x53, "vrcp", X86frcp>,
2012                 sse1_fp_unop_p_y_int<0x53, "vrcp", int_x86_avx_rcp_ps_256>,
2013                 sse1_fp_unop_p_int<0x53, "vrcp", int_x86_sse_rcp_ps>, VEX;
2014 }
2015
2016 // Square root.
2017 defm SQRT  : sse1_fp_unop_s<0x51, "sqrt",  fsqrt, int_x86_sse_sqrt_ss>,
2018              sse1_fp_unop_p<0x51, "sqrt",  fsqrt>,
2019              sse1_fp_unop_p_int<0x51, "sqrt",  int_x86_sse_sqrt_ps>,
2020              sse2_fp_unop_s<0x51, "sqrt",  fsqrt, int_x86_sse2_sqrt_sd>,
2021              sse2_fp_unop_p<0x51, "sqrt",  fsqrt>,
2022              sse2_fp_unop_p_int<0x51, "sqrt", int_x86_sse2_sqrt_pd>;
2023
2024 // Reciprocal approximations. Note that these typically require refinement
2025 // in order to obtain suitable precision.
2026 defm RSQRT : sse1_fp_unop_s<0x52, "rsqrt", X86frsqrt, int_x86_sse_rsqrt_ss>,
2027              sse1_fp_unop_p<0x52, "rsqrt", X86frsqrt>,
2028              sse1_fp_unop_p_int<0x52, "rsqrt", int_x86_sse_rsqrt_ps>;
2029 defm RCP   : sse1_fp_unop_s<0x53, "rcp", X86frcp, int_x86_sse_rcp_ss>,
2030              sse1_fp_unop_p<0x53, "rcp", X86frcp>,
2031              sse1_fp_unop_p_int<0x53, "rcp", int_x86_sse_rcp_ps>;
2032
2033 // There is no f64 version of the reciprocal approximation instructions.
2034
2035 //===----------------------------------------------------------------------===//
2036 // SSE 1 & 2 - Non-temporal stores
2037 //===----------------------------------------------------------------------===//
2038
2039 let isAsmParserOnly = 1 in {
2040   def VMOVNTPSmr_Int : VPSI<0x2B, MRMDestMem, (outs),
2041                          (ins i128mem:$dst, VR128:$src),
2042                          "movntps\t{$src, $dst|$dst, $src}",
2043                          [(int_x86_sse_movnt_ps addr:$dst, VR128:$src)]>, VEX;
2044   def VMOVNTPDmr_Int : VPDI<0x2B, MRMDestMem, (outs),
2045                          (ins i128mem:$dst, VR128:$src),
2046                          "movntpd\t{$src, $dst|$dst, $src}",
2047                          [(int_x86_sse2_movnt_pd addr:$dst, VR128:$src)]>, VEX;
2048
2049   let ExeDomain = SSEPackedInt in
2050     def VMOVNTDQmr_Int : VPDI<0xE7, MRMDestMem, (outs),
2051                        (ins f128mem:$dst, VR128:$src),
2052                        "movntdq\t{$src, $dst|$dst, $src}",
2053                        [(int_x86_sse2_movnt_dq addr:$dst, VR128:$src)]>, VEX;
2054
2055   let AddedComplexity = 400 in { // Prefer non-temporal versions
2056     def VMOVNTPSmr : VPSI<0x2B, MRMDestMem, (outs),
2057                          (ins f128mem:$dst, VR128:$src),
2058                          "movntps\t{$src, $dst|$dst, $src}",
2059                          [(alignednontemporalstore (v4f32 VR128:$src),
2060                                                    addr:$dst)]>, VEX;
2061     def VMOVNTPDmr : VPDI<0x2B, MRMDestMem, (outs),
2062                          (ins f128mem:$dst, VR128:$src),
2063                          "movntpd\t{$src, $dst|$dst, $src}",
2064                          [(alignednontemporalstore (v2f64 VR128:$src),
2065                                                    addr:$dst)]>, VEX;
2066     def VMOVNTDQ_64mr : VPDI<0xE7, MRMDestMem, (outs),
2067                           (ins f128mem:$dst, VR128:$src),
2068                           "movntdq\t{$src, $dst|$dst, $src}",
2069                           [(alignednontemporalstore (v2f64 VR128:$src),
2070                                                     addr:$dst)]>, VEX;
2071     let ExeDomain = SSEPackedInt in
2072     def VMOVNTDQmr : VPDI<0xE7, MRMDestMem, (outs),
2073                         (ins f128mem:$dst, VR128:$src),
2074                         "movntdq\t{$src, $dst|$dst, $src}",
2075                         [(alignednontemporalstore (v4f32 VR128:$src),
2076                                                   addr:$dst)]>, VEX;
2077
2078     def VMOVNTPSYmr : VPSI<0x2B, MRMDestMem, (outs),
2079                          (ins f256mem:$dst, VR256:$src),
2080                          "movntps\t{$src, $dst|$dst, $src}",
2081                          [(alignednontemporalstore (v8f32 VR256:$src),
2082                                                    addr:$dst)]>, VEX;
2083     def VMOVNTPDYmr : VPDI<0x2B, MRMDestMem, (outs),
2084                          (ins f256mem:$dst, VR256:$src),
2085                          "movntpd\t{$src, $dst|$dst, $src}",
2086                          [(alignednontemporalstore (v4f64 VR256:$src),
2087                                                    addr:$dst)]>, VEX;
2088     def VMOVNTDQY_64mr : VPDI<0xE7, MRMDestMem, (outs),
2089                           (ins f256mem:$dst, VR256:$src),
2090                           "movntdq\t{$src, $dst|$dst, $src}",
2091                           [(alignednontemporalstore (v4f64 VR256:$src),
2092                                                     addr:$dst)]>, VEX;
2093     let ExeDomain = SSEPackedInt in
2094     def VMOVNTDQYmr : VPDI<0xE7, MRMDestMem, (outs),
2095                         (ins f256mem:$dst, VR256:$src),
2096                         "movntdq\t{$src, $dst|$dst, $src}",
2097                         [(alignednontemporalstore (v8f32 VR256:$src),
2098                                                   addr:$dst)]>, VEX;
2099   }
2100 }
2101
2102 def : Pat<(int_x86_avx_movnt_dq_256 addr:$dst, VR256:$src),
2103           (VMOVNTDQYmr addr:$dst, VR256:$src)>;
2104 def : Pat<(int_x86_avx_movnt_pd_256 addr:$dst, VR256:$src),
2105           (VMOVNTPDYmr addr:$dst, VR256:$src)>;
2106 def : Pat<(int_x86_avx_movnt_ps_256 addr:$dst, VR256:$src),
2107           (VMOVNTPSYmr addr:$dst, VR256:$src)>;
2108
2109 def MOVNTPSmr_Int : PSI<0x2B, MRMDestMem, (outs), (ins i128mem:$dst, VR128:$src),
2110                     "movntps\t{$src, $dst|$dst, $src}",
2111                     [(int_x86_sse_movnt_ps addr:$dst, VR128:$src)]>;
2112 def MOVNTPDmr_Int : PDI<0x2B, MRMDestMem, (outs), (ins i128mem:$dst, VR128:$src),
2113                         "movntpd\t{$src, $dst|$dst, $src}",
2114                         [(int_x86_sse2_movnt_pd addr:$dst, VR128:$src)]>;
2115
2116 let ExeDomain = SSEPackedInt in
2117 def MOVNTDQmr_Int : PDI<0xE7, MRMDestMem, (outs), (ins f128mem:$dst, VR128:$src),
2118                         "movntdq\t{$src, $dst|$dst, $src}",
2119                         [(int_x86_sse2_movnt_dq addr:$dst, VR128:$src)]>;
2120
2121 let AddedComplexity = 400 in { // Prefer non-temporal versions
2122 def MOVNTPSmr : PSI<0x2B, MRMDestMem, (outs), (ins f128mem:$dst, VR128:$src),
2123                     "movntps\t{$src, $dst|$dst, $src}",
2124                     [(alignednontemporalstore (v4f32 VR128:$src), addr:$dst)]>;
2125 def MOVNTPDmr : PDI<0x2B, MRMDestMem, (outs), (ins f128mem:$dst, VR128:$src),
2126                     "movntpd\t{$src, $dst|$dst, $src}",
2127                     [(alignednontemporalstore(v2f64 VR128:$src), addr:$dst)]>;
2128
2129 def MOVNTDQ_64mr : PDI<0xE7, MRMDestMem, (outs), (ins f128mem:$dst, VR128:$src),
2130                     "movntdq\t{$src, $dst|$dst, $src}",
2131                     [(alignednontemporalstore (v2f64 VR128:$src), addr:$dst)]>;
2132
2133 let ExeDomain = SSEPackedInt in
2134 def MOVNTDQmr : PDI<0xE7, MRMDestMem, (outs), (ins f128mem:$dst, VR128:$src),
2135                     "movntdq\t{$src, $dst|$dst, $src}",
2136                     [(alignednontemporalstore (v4f32 VR128:$src), addr:$dst)]>;
2137
2138 // There is no AVX form for instructions below this point
2139 def MOVNTImr : I<0xC3, MRMDestMem, (outs), (ins i32mem:$dst, GR32:$src),
2140                  "movnti\t{$src, $dst|$dst, $src}",
2141                  [(nontemporalstore (i32 GR32:$src), addr:$dst)]>,
2142                TB, Requires<[HasSSE2]>;
2143
2144 def MOVNTI_64mr : RI<0xC3, MRMDestMem, (outs), (ins i64mem:$dst, GR64:$src),
2145                      "movnti\t{$src, $dst|$dst, $src}",
2146                      [(nontemporalstore (i64 GR64:$src), addr:$dst)]>,
2147                   TB, Requires<[HasSSE2]>;
2148
2149 }
2150 def MOVNTImr_Int  :   I<0xC3, MRMDestMem, (outs), (ins i32mem:$dst, GR32:$src),
2151                     "movnti\t{$src, $dst|$dst, $src}",
2152                     [(int_x86_sse2_movnt_i addr:$dst, GR32:$src)]>,
2153                   TB, Requires<[HasSSE2]>;
2154
2155 //===----------------------------------------------------------------------===//
2156 // SSE 1 & 2 - Misc Instructions (No AVX form)
2157 //===----------------------------------------------------------------------===//
2158
2159 // Prefetch intrinsic.
2160 def PREFETCHT0   : PSI<0x18, MRM1m, (outs), (ins i8mem:$src),
2161     "prefetcht0\t$src", [(prefetch addr:$src, imm, (i32 3))]>;
2162 def PREFETCHT1   : PSI<0x18, MRM2m, (outs), (ins i8mem:$src),
2163     "prefetcht1\t$src", [(prefetch addr:$src, imm, (i32 2))]>;
2164 def PREFETCHT2   : PSI<0x18, MRM3m, (outs), (ins i8mem:$src),
2165     "prefetcht2\t$src", [(prefetch addr:$src, imm, (i32 1))]>;
2166 def PREFETCHNTA  : PSI<0x18, MRM0m, (outs), (ins i8mem:$src),
2167     "prefetchnta\t$src", [(prefetch addr:$src, imm, (i32 0))]>;
2168
2169 // Load, store, and memory fence
2170 def SFENCE : I<0xAE, MRM_F8, (outs), (ins), "sfence", [(int_x86_sse_sfence)]>,
2171              TB, Requires<[HasSSE1]>;
2172 def : Pat<(X86SFence), (SFENCE)>;
2173
2174 // Alias instructions that map zero vector to pxor / xorp* for sse.
2175 // We set canFoldAsLoad because this can be converted to a constant-pool
2176 // load of an all-zeros value if folding it would be beneficial.
2177 // FIXME: Change encoding to pseudo!
2178 let isReMaterializable = 1, isAsCheapAsAMove = 1, canFoldAsLoad = 1,
2179     isCodeGenOnly = 1 in {
2180 def V_SET0PS : PSI<0x57, MRMInitReg, (outs VR128:$dst), (ins), "",
2181                  [(set VR128:$dst, (v4f32 immAllZerosV))]>;
2182 def V_SET0PD : PDI<0x57, MRMInitReg, (outs VR128:$dst), (ins), "",
2183                  [(set VR128:$dst, (v2f64 immAllZerosV))]>;
2184 let ExeDomain = SSEPackedInt in
2185 def V_SET0PI : PDI<0xEF, MRMInitReg, (outs VR128:$dst), (ins), "",
2186                  [(set VR128:$dst, (v4i32 immAllZerosV))]>;
2187 }
2188
2189 let isReMaterializable = 1, isAsCheapAsAMove = 1, canFoldAsLoad = 1,
2190     isCodeGenOnly = 1, Predicates = [HasAVX] in {
2191 def V_SET0PSY : PSI<0x57, MRMInitReg, (outs VR256:$dst), (ins), "",
2192                  [(set VR256:$dst, (v8f32 immAllZerosV))]>, VEX_4V;
2193 def V_SET0PDY : PDI<0x57, MRMInitReg, (outs VR256:$dst), (ins), "",
2194                  [(set VR256:$dst, (v4f64 immAllZerosV))]>, VEX_4V;
2195 }
2196
2197 def : Pat<(v2i64 immAllZerosV), (V_SET0PI)>;
2198 def : Pat<(v8i16 immAllZerosV), (V_SET0PI)>;
2199 def : Pat<(v16i8 immAllZerosV), (V_SET0PI)>;
2200
2201 def : Pat<(f32 (vector_extract (v4f32 VR128:$src), (iPTR 0))),
2202           (f32 (EXTRACT_SUBREG (v4f32 VR128:$src), sub_ss))>;
2203
2204 //===----------------------------------------------------------------------===//
2205 // SSE 1 & 2 - Load/Store XCSR register
2206 //===----------------------------------------------------------------------===//
2207
2208 let isAsmParserOnly = 1 in {
2209   def VLDMXCSR : VPSI<0xAE, MRM2m, (outs), (ins i32mem:$src),
2210                     "ldmxcsr\t$src", [(int_x86_sse_ldmxcsr addr:$src)]>, VEX;
2211   def VSTMXCSR : VPSI<0xAE, MRM3m, (outs), (ins i32mem:$dst),
2212                     "stmxcsr\t$dst", [(int_x86_sse_stmxcsr addr:$dst)]>, VEX;
2213 }
2214
2215 def LDMXCSR : PSI<0xAE, MRM2m, (outs), (ins i32mem:$src),
2216                   "ldmxcsr\t$src", [(int_x86_sse_ldmxcsr addr:$src)]>;
2217 def STMXCSR : PSI<0xAE, MRM3m, (outs), (ins i32mem:$dst),
2218                   "stmxcsr\t$dst", [(int_x86_sse_stmxcsr addr:$dst)]>;
2219
2220 //===---------------------------------------------------------------------===//
2221 // SSE2 - Move Aligned/Unaligned Packed Integer Instructions
2222 //===---------------------------------------------------------------------===//
2223
2224 let ExeDomain = SSEPackedInt in { // SSE integer instructions
2225
2226 let isAsmParserOnly = 1 in {
2227   let neverHasSideEffects = 1 in {
2228   def VMOVDQArr  : VPDI<0x6F, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
2229                       "movdqa\t{$src, $dst|$dst, $src}", []>, VEX;
2230   def VMOVDQAYrr : VPDI<0x6F, MRMSrcReg, (outs VR256:$dst), (ins VR256:$src),
2231                       "movdqa\t{$src, $dst|$dst, $src}", []>, VEX;
2232   }
2233   def VMOVDQUrr  : VPDI<0x6F, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
2234                       "movdqu\t{$src, $dst|$dst, $src}", []>, XS, VEX;
2235   def VMOVDQUYrr : VPDI<0x6F, MRMSrcReg, (outs VR256:$dst), (ins VR256:$src),
2236                       "movdqu\t{$src, $dst|$dst, $src}", []>, XS, VEX;
2237
2238   let canFoldAsLoad = 1, mayLoad = 1 in {
2239   def VMOVDQArm  : VPDI<0x6F, MRMSrcMem, (outs VR128:$dst), (ins i128mem:$src),
2240                      "movdqa\t{$src, $dst|$dst, $src}", []>, VEX;
2241   def VMOVDQAYrm : VPDI<0x6F, MRMSrcMem, (outs VR256:$dst), (ins i256mem:$src),
2242                      "movdqa\t{$src, $dst|$dst, $src}", []>, VEX;
2243   let Predicates = [HasAVX] in {
2244     def VMOVDQUrm  : I<0x6F, MRMSrcMem, (outs VR128:$dst), (ins i128mem:$src),
2245                       "vmovdqu\t{$src, $dst|$dst, $src}",[]>, XS, VEX;
2246     def VMOVDQUYrm : I<0x6F, MRMSrcMem, (outs VR256:$dst), (ins i256mem:$src),
2247                       "vmovdqu\t{$src, $dst|$dst, $src}",[]>, XS, VEX;
2248   }
2249   }
2250
2251   let mayStore = 1 in {
2252   def VMOVDQAmr  : VPDI<0x7F, MRMDestMem, (outs),
2253                        (ins i128mem:$dst, VR128:$src),
2254                        "movdqa\t{$src, $dst|$dst, $src}", []>, VEX;
2255   def VMOVDQAYmr : VPDI<0x7F, MRMDestMem, (outs),
2256                        (ins i256mem:$dst, VR256:$src),
2257                        "movdqa\t{$src, $dst|$dst, $src}", []>, VEX;
2258   let Predicates = [HasAVX] in {
2259   def VMOVDQUmr  : I<0x7F, MRMDestMem, (outs), (ins i128mem:$dst, VR128:$src),
2260                     "vmovdqu\t{$src, $dst|$dst, $src}",[]>, XS, VEX;
2261   def VMOVDQUYmr : I<0x7F, MRMDestMem, (outs), (ins i256mem:$dst, VR256:$src),
2262                     "vmovdqu\t{$src, $dst|$dst, $src}",[]>, XS, VEX;
2263   }
2264   }
2265 }
2266
2267 let neverHasSideEffects = 1 in
2268 def MOVDQArr : PDI<0x6F, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
2269                    "movdqa\t{$src, $dst|$dst, $src}", []>;
2270
2271 let canFoldAsLoad = 1, mayLoad = 1 in {
2272 def MOVDQArm : PDI<0x6F, MRMSrcMem, (outs VR128:$dst), (ins i128mem:$src),
2273                    "movdqa\t{$src, $dst|$dst, $src}",
2274                    [/*(set VR128:$dst, (alignedloadv2i64 addr:$src))*/]>;
2275 def MOVDQUrm :   I<0x6F, MRMSrcMem, (outs VR128:$dst), (ins i128mem:$src),
2276                    "movdqu\t{$src, $dst|$dst, $src}",
2277                    [/*(set VR128:$dst, (loadv2i64 addr:$src))*/]>,
2278                  XS, Requires<[HasSSE2]>;
2279 }
2280
2281 let mayStore = 1 in {
2282 def MOVDQAmr : PDI<0x7F, MRMDestMem, (outs), (ins i128mem:$dst, VR128:$src),
2283                    "movdqa\t{$src, $dst|$dst, $src}",
2284                    [/*(alignedstore (v2i64 VR128:$src), addr:$dst)*/]>;
2285 def MOVDQUmr :   I<0x7F, MRMDestMem, (outs), (ins i128mem:$dst, VR128:$src),
2286                    "movdqu\t{$src, $dst|$dst, $src}",
2287                    [/*(store (v2i64 VR128:$src), addr:$dst)*/]>,
2288                  XS, Requires<[HasSSE2]>;
2289 }
2290
2291 // Intrinsic forms of MOVDQU load and store
2292 let isAsmParserOnly = 1 in {
2293 let canFoldAsLoad = 1 in
2294 def VMOVDQUrm_Int : I<0x6F, MRMSrcMem, (outs VR128:$dst), (ins i128mem:$src),
2295                        "vmovdqu\t{$src, $dst|$dst, $src}",
2296                        [(set VR128:$dst, (int_x86_sse2_loadu_dq addr:$src))]>,
2297                      XS, VEX, Requires<[HasAVX]>;
2298 def VMOVDQUmr_Int : I<0x7F, MRMDestMem, (outs), (ins i128mem:$dst, VR128:$src),
2299                        "vmovdqu\t{$src, $dst|$dst, $src}",
2300                        [(int_x86_sse2_storeu_dq addr:$dst, VR128:$src)]>,
2301                      XS, VEX, Requires<[HasAVX]>;
2302 }
2303
2304 let canFoldAsLoad = 1 in
2305 def MOVDQUrm_Int :   I<0x6F, MRMSrcMem, (outs VR128:$dst), (ins i128mem:$src),
2306                        "movdqu\t{$src, $dst|$dst, $src}",
2307                        [(set VR128:$dst, (int_x86_sse2_loadu_dq addr:$src))]>,
2308                  XS, Requires<[HasSSE2]>;
2309 def MOVDQUmr_Int :   I<0x7F, MRMDestMem, (outs), (ins i128mem:$dst, VR128:$src),
2310                        "movdqu\t{$src, $dst|$dst, $src}",
2311                        [(int_x86_sse2_storeu_dq addr:$dst, VR128:$src)]>,
2312                      XS, Requires<[HasSSE2]>;
2313
2314 } // ExeDomain = SSEPackedInt
2315
2316 def : Pat<(int_x86_avx_loadu_dq_256 addr:$src), (VMOVDQUYrm addr:$src)>;
2317 def : Pat<(int_x86_avx_storeu_dq_256 addr:$dst, VR256:$src),
2318           (VMOVDQUYmr addr:$dst, VR256:$src)>;
2319
2320 //===---------------------------------------------------------------------===//
2321 // SSE2 - Packed Integer Arithmetic Instructions
2322 //===---------------------------------------------------------------------===//
2323
2324 let ExeDomain = SSEPackedInt in { // SSE integer instructions
2325
2326 multiclass PDI_binop_rm_int<bits<8> opc, string OpcodeStr, Intrinsic IntId,
2327                             bit IsCommutable = 0, bit Is2Addr = 1> {
2328   let isCommutable = IsCommutable in
2329   def rr : PDI<opc, MRMSrcReg, (outs VR128:$dst),
2330        (ins VR128:$src1, VR128:$src2),
2331        !if(Is2Addr,
2332            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
2333            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
2334        [(set VR128:$dst, (IntId VR128:$src1, VR128:$src2))]>;
2335   def rm : PDI<opc, MRMSrcMem, (outs VR128:$dst),
2336        (ins VR128:$src1, i128mem:$src2),
2337        !if(Is2Addr,
2338            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
2339            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
2340        [(set VR128:$dst, (IntId VR128:$src1,
2341                                 (bitconvert (memopv2i64 addr:$src2))))]>;
2342 }
2343
2344 multiclass PDI_binop_rmi_int<bits<8> opc, bits<8> opc2, Format ImmForm,
2345                              string OpcodeStr, Intrinsic IntId,
2346                              Intrinsic IntId2, bit Is2Addr = 1> {
2347   def rr : PDI<opc, MRMSrcReg, (outs VR128:$dst),
2348        (ins VR128:$src1, VR128:$src2),
2349        !if(Is2Addr,
2350            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
2351            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
2352        [(set VR128:$dst, (IntId VR128:$src1, VR128:$src2))]>;
2353   def rm : PDI<opc, MRMSrcMem, (outs VR128:$dst),
2354        (ins VR128:$src1, i128mem:$src2),
2355        !if(Is2Addr,
2356            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
2357            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
2358        [(set VR128:$dst, (IntId VR128:$src1,
2359                                       (bitconvert (memopv2i64 addr:$src2))))]>;
2360   def ri : PDIi8<opc2, ImmForm, (outs VR128:$dst),
2361        (ins VR128:$src1, i32i8imm:$src2),
2362        !if(Is2Addr,
2363            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
2364            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
2365        [(set VR128:$dst, (IntId2 VR128:$src1, (i32 imm:$src2)))]>;
2366 }
2367
2368 /// PDI_binop_rm - Simple SSE2 binary operator.
2369 multiclass PDI_binop_rm<bits<8> opc, string OpcodeStr, SDNode OpNode,
2370                         ValueType OpVT, bit IsCommutable = 0, bit Is2Addr = 1> {
2371   let isCommutable = IsCommutable in
2372   def rr : PDI<opc, MRMSrcReg, (outs VR128:$dst),
2373        (ins VR128:$src1, VR128:$src2),
2374        !if(Is2Addr,
2375            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
2376            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
2377        [(set VR128:$dst, (OpVT (OpNode VR128:$src1, VR128:$src2)))]>;
2378   def rm : PDI<opc, MRMSrcMem, (outs VR128:$dst),
2379        (ins VR128:$src1, i128mem:$src2),
2380        !if(Is2Addr,
2381            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
2382            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
2383        [(set VR128:$dst, (OpVT (OpNode VR128:$src1,
2384                                      (bitconvert (memopv2i64 addr:$src2)))))]>;
2385 }
2386
2387 /// PDI_binop_rm_v2i64 - Simple SSE2 binary operator whose type is v2i64.
2388 ///
2389 /// FIXME: we could eliminate this and use PDI_binop_rm instead if tblgen knew
2390 /// to collapse (bitconvert VT to VT) into its operand.
2391 ///
2392 multiclass PDI_binop_rm_v2i64<bits<8> opc, string OpcodeStr, SDNode OpNode,
2393                               bit IsCommutable = 0, bit Is2Addr = 1> {
2394   let isCommutable = IsCommutable in
2395   def rr : PDI<opc, MRMSrcReg, (outs VR128:$dst),
2396        (ins VR128:$src1, VR128:$src2),
2397        !if(Is2Addr,
2398            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
2399            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
2400        [(set VR128:$dst, (v2i64 (OpNode VR128:$src1, VR128:$src2)))]>;
2401   def rm : PDI<opc, MRMSrcMem, (outs VR128:$dst),
2402        (ins VR128:$src1, i128mem:$src2),
2403        !if(Is2Addr,
2404            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
2405            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
2406        [(set VR128:$dst, (OpNode VR128:$src1, (memopv2i64 addr:$src2)))]>;
2407 }
2408
2409 } // ExeDomain = SSEPackedInt
2410
2411 // 128-bit Integer Arithmetic
2412
2413 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
2414 defm VPADDB  : PDI_binop_rm<0xFC, "vpaddb", add, v16i8, 1, 0 /*3addr*/>, VEX_4V;
2415 defm VPADDW  : PDI_binop_rm<0xFD, "vpaddw", add, v8i16, 1, 0>, VEX_4V;
2416 defm VPADDD  : PDI_binop_rm<0xFE, "vpaddd", add, v4i32, 1, 0>, VEX_4V;
2417 defm VPADDQ  : PDI_binop_rm_v2i64<0xD4, "vpaddq", add, 1, 0>, VEX_4V;
2418 defm VPMULLW : PDI_binop_rm<0xD5, "vpmullw", mul, v8i16, 1, 0>, VEX_4V;
2419 defm VPSUBB : PDI_binop_rm<0xF8, "vpsubb", sub, v16i8, 0, 0>, VEX_4V;
2420 defm VPSUBW : PDI_binop_rm<0xF9, "vpsubw", sub, v8i16, 0, 0>, VEX_4V;
2421 defm VPSUBD : PDI_binop_rm<0xFA, "vpsubd", sub, v4i32, 0, 0>, VEX_4V;
2422 defm VPSUBQ : PDI_binop_rm_v2i64<0xFB, "vpsubq", sub, 0, 0>, VEX_4V;
2423
2424 // Intrinsic forms
2425 defm VPSUBSB  : PDI_binop_rm_int<0xE8, "vpsubsb" , int_x86_sse2_psubs_b, 0, 0>,
2426                                  VEX_4V;
2427 defm VPSUBSW  : PDI_binop_rm_int<0xE9, "vpsubsw" , int_x86_sse2_psubs_w, 0, 0>,
2428                                  VEX_4V;
2429 defm VPSUBUSB : PDI_binop_rm_int<0xD8, "vpsubusb", int_x86_sse2_psubus_b, 0, 0>,
2430                                  VEX_4V;
2431 defm VPSUBUSW : PDI_binop_rm_int<0xD9, "vpsubusw", int_x86_sse2_psubus_w, 0, 0>,
2432                                  VEX_4V;
2433 defm VPADDSB  : PDI_binop_rm_int<0xEC, "vpaddsb" , int_x86_sse2_padds_b, 1, 0>,
2434                                  VEX_4V;
2435 defm VPADDSW  : PDI_binop_rm_int<0xED, "vpaddsw" , int_x86_sse2_padds_w, 1, 0>,
2436                                  VEX_4V;
2437 defm VPADDUSB : PDI_binop_rm_int<0xDC, "vpaddusb", int_x86_sse2_paddus_b, 1, 0>,
2438                                  VEX_4V;
2439 defm VPADDUSW : PDI_binop_rm_int<0xDD, "vpaddusw", int_x86_sse2_paddus_w, 1, 0>,
2440                                  VEX_4V;
2441 defm VPMULHUW : PDI_binop_rm_int<0xE4, "vpmulhuw", int_x86_sse2_pmulhu_w, 1, 0>,
2442                                  VEX_4V;
2443 defm VPMULHW  : PDI_binop_rm_int<0xE5, "vpmulhw" , int_x86_sse2_pmulh_w, 1, 0>,
2444                                  VEX_4V;
2445 defm VPMULUDQ : PDI_binop_rm_int<0xF4, "vpmuludq", int_x86_sse2_pmulu_dq, 1, 0>,
2446                                  VEX_4V;
2447 defm VPMADDWD : PDI_binop_rm_int<0xF5, "vpmaddwd", int_x86_sse2_pmadd_wd, 1, 0>,
2448                                  VEX_4V;
2449 defm VPAVGB   : PDI_binop_rm_int<0xE0, "vpavgb", int_x86_sse2_pavg_b, 1, 0>,
2450                                  VEX_4V;
2451 defm VPAVGW   : PDI_binop_rm_int<0xE3, "vpavgw", int_x86_sse2_pavg_w, 1, 0>,
2452                                  VEX_4V;
2453 defm VPMINUB  : PDI_binop_rm_int<0xDA, "vpminub", int_x86_sse2_pminu_b, 1, 0>,
2454                                  VEX_4V;
2455 defm VPMINSW  : PDI_binop_rm_int<0xEA, "vpminsw", int_x86_sse2_pmins_w, 1, 0>,
2456                                  VEX_4V;
2457 defm VPMAXUB  : PDI_binop_rm_int<0xDE, "vpmaxub", int_x86_sse2_pmaxu_b, 1, 0>,
2458                                  VEX_4V;
2459 defm VPMAXSW  : PDI_binop_rm_int<0xEE, "vpmaxsw", int_x86_sse2_pmaxs_w, 1, 0>,
2460                                  VEX_4V;
2461 defm VPSADBW  : PDI_binop_rm_int<0xF6, "vpsadbw", int_x86_sse2_psad_bw, 1, 0>,
2462                                  VEX_4V;
2463 }
2464
2465 let Constraints = "$src1 = $dst" in {
2466 defm PADDB  : PDI_binop_rm<0xFC, "paddb", add, v16i8, 1>;
2467 defm PADDW  : PDI_binop_rm<0xFD, "paddw", add, v8i16, 1>;
2468 defm PADDD  : PDI_binop_rm<0xFE, "paddd", add, v4i32, 1>;
2469 defm PADDQ  : PDI_binop_rm_v2i64<0xD4, "paddq", add, 1>;
2470 defm PMULLW : PDI_binop_rm<0xD5, "pmullw", mul, v8i16, 1>;
2471 defm PSUBB : PDI_binop_rm<0xF8, "psubb", sub, v16i8>;
2472 defm PSUBW : PDI_binop_rm<0xF9, "psubw", sub, v8i16>;
2473 defm PSUBD : PDI_binop_rm<0xFA, "psubd", sub, v4i32>;
2474 defm PSUBQ : PDI_binop_rm_v2i64<0xFB, "psubq", sub>;
2475
2476 // Intrinsic forms
2477 defm PSUBSB  : PDI_binop_rm_int<0xE8, "psubsb" , int_x86_sse2_psubs_b>;
2478 defm PSUBSW  : PDI_binop_rm_int<0xE9, "psubsw" , int_x86_sse2_psubs_w>;
2479 defm PSUBUSB : PDI_binop_rm_int<0xD8, "psubusb", int_x86_sse2_psubus_b>;
2480 defm PSUBUSW : PDI_binop_rm_int<0xD9, "psubusw", int_x86_sse2_psubus_w>;
2481 defm PADDSB  : PDI_binop_rm_int<0xEC, "paddsb" , int_x86_sse2_padds_b, 1>;
2482 defm PADDSW  : PDI_binop_rm_int<0xED, "paddsw" , int_x86_sse2_padds_w, 1>;
2483 defm PADDUSB : PDI_binop_rm_int<0xDC, "paddusb", int_x86_sse2_paddus_b, 1>;
2484 defm PADDUSW : PDI_binop_rm_int<0xDD, "paddusw", int_x86_sse2_paddus_w, 1>;
2485 defm PMULHUW : PDI_binop_rm_int<0xE4, "pmulhuw", int_x86_sse2_pmulhu_w, 1>;
2486 defm PMULHW  : PDI_binop_rm_int<0xE5, "pmulhw" , int_x86_sse2_pmulh_w, 1>;
2487 defm PMULUDQ : PDI_binop_rm_int<0xF4, "pmuludq", int_x86_sse2_pmulu_dq, 1>;
2488 defm PMADDWD : PDI_binop_rm_int<0xF5, "pmaddwd", int_x86_sse2_pmadd_wd, 1>;
2489 defm PAVGB   : PDI_binop_rm_int<0xE0, "pavgb", int_x86_sse2_pavg_b, 1>;
2490 defm PAVGW   : PDI_binop_rm_int<0xE3, "pavgw", int_x86_sse2_pavg_w, 1>;
2491 defm PMINUB  : PDI_binop_rm_int<0xDA, "pminub", int_x86_sse2_pminu_b, 1>;
2492 defm PMINSW  : PDI_binop_rm_int<0xEA, "pminsw", int_x86_sse2_pmins_w, 1>;
2493 defm PMAXUB  : PDI_binop_rm_int<0xDE, "pmaxub", int_x86_sse2_pmaxu_b, 1>;
2494 defm PMAXSW  : PDI_binop_rm_int<0xEE, "pmaxsw", int_x86_sse2_pmaxs_w, 1>;
2495 defm PSADBW  : PDI_binop_rm_int<0xF6, "psadbw", int_x86_sse2_psad_bw, 1>;
2496
2497 } // Constraints = "$src1 = $dst"
2498
2499 //===---------------------------------------------------------------------===//
2500 // SSE2 - Packed Integer Logical Instructions
2501 //===---------------------------------------------------------------------===//
2502
2503 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
2504 defm VPSLLW : PDI_binop_rmi_int<0xF1, 0x71, MRM6r, "vpsllw",
2505                                 int_x86_sse2_psll_w, int_x86_sse2_pslli_w, 0>,
2506                                 VEX_4V;
2507 defm VPSLLD : PDI_binop_rmi_int<0xF2, 0x72, MRM6r, "vpslld",
2508                                 int_x86_sse2_psll_d, int_x86_sse2_pslli_d, 0>,
2509                                 VEX_4V;
2510 defm VPSLLQ : PDI_binop_rmi_int<0xF3, 0x73, MRM6r, "vpsllq",
2511                                 int_x86_sse2_psll_q, int_x86_sse2_pslli_q, 0>,
2512                                 VEX_4V;
2513
2514 defm VPSRLW : PDI_binop_rmi_int<0xD1, 0x71, MRM2r, "vpsrlw",
2515                                 int_x86_sse2_psrl_w, int_x86_sse2_psrli_w, 0>,
2516                                 VEX_4V;
2517 defm VPSRLD : PDI_binop_rmi_int<0xD2, 0x72, MRM2r, "vpsrld",
2518                                 int_x86_sse2_psrl_d, int_x86_sse2_psrli_d, 0>,
2519                                 VEX_4V;
2520 defm VPSRLQ : PDI_binop_rmi_int<0xD3, 0x73, MRM2r, "vpsrlq",
2521                                 int_x86_sse2_psrl_q, int_x86_sse2_psrli_q, 0>,
2522                                 VEX_4V;
2523
2524 defm VPSRAW : PDI_binop_rmi_int<0xE1, 0x71, MRM4r, "vpsraw",
2525                                 int_x86_sse2_psra_w, int_x86_sse2_psrai_w, 0>,
2526                                 VEX_4V;
2527 defm VPSRAD : PDI_binop_rmi_int<0xE2, 0x72, MRM4r, "vpsrad",
2528                                 int_x86_sse2_psra_d, int_x86_sse2_psrai_d, 0>,
2529                                 VEX_4V;
2530
2531 defm VPAND : PDI_binop_rm_v2i64<0xDB, "vpand", and, 1, 0>, VEX_4V;
2532 defm VPOR  : PDI_binop_rm_v2i64<0xEB, "vpor" , or, 1, 0>, VEX_4V;
2533 defm VPXOR : PDI_binop_rm_v2i64<0xEF, "vpxor", xor, 1, 0>, VEX_4V;
2534
2535 let ExeDomain = SSEPackedInt in {
2536   let neverHasSideEffects = 1 in {
2537     // 128-bit logical shifts.
2538     def VPSLLDQri : PDIi8<0x73, MRM7r,
2539                       (outs VR128:$dst), (ins VR128:$src1, i32i8imm:$src2),
2540                       "vpslldq\t{$src2, $src1, $dst|$dst, $src1, $src2}", []>,
2541                       VEX_4V;
2542     def VPSRLDQri : PDIi8<0x73, MRM3r,
2543                       (outs VR128:$dst), (ins VR128:$src1, i32i8imm:$src2),
2544                       "vpsrldq\t{$src2, $src1, $dst|$dst, $src1, $src2}", []>,
2545                       VEX_4V;
2546     // PSRADQri doesn't exist in SSE[1-3].
2547   }
2548   def VPANDNrr : PDI<0xDF, MRMSrcReg,
2549                     (outs VR128:$dst), (ins VR128:$src1, VR128:$src2),
2550                     "vpandn\t{$src2, $src1, $dst|$dst, $src1, $src2}",
2551                     [(set VR128:$dst, (v2i64 (and (vnot VR128:$src1),
2552                                               VR128:$src2)))]>, VEX_4V;
2553
2554   def VPANDNrm : PDI<0xDF, MRMSrcMem,
2555                     (outs VR128:$dst), (ins VR128:$src1, i128mem:$src2),
2556                     "vpandn\t{$src2, $src1, $dst|$dst, $src1, $src2}",
2557                     [(set VR128:$dst, (v2i64 (and (vnot VR128:$src1),
2558                                               (memopv2i64 addr:$src2))))]>,
2559                                               VEX_4V;
2560 }
2561 }
2562
2563 let Constraints = "$src1 = $dst" in {
2564 defm PSLLW : PDI_binop_rmi_int<0xF1, 0x71, MRM6r, "psllw",
2565                                int_x86_sse2_psll_w, int_x86_sse2_pslli_w>;
2566 defm PSLLD : PDI_binop_rmi_int<0xF2, 0x72, MRM6r, "pslld",
2567                                int_x86_sse2_psll_d, int_x86_sse2_pslli_d>;
2568 defm PSLLQ : PDI_binop_rmi_int<0xF3, 0x73, MRM6r, "psllq",
2569                                int_x86_sse2_psll_q, int_x86_sse2_pslli_q>;
2570
2571 defm PSRLW : PDI_binop_rmi_int<0xD1, 0x71, MRM2r, "psrlw",
2572                                int_x86_sse2_psrl_w, int_x86_sse2_psrli_w>;
2573 defm PSRLD : PDI_binop_rmi_int<0xD2, 0x72, MRM2r, "psrld",
2574                                int_x86_sse2_psrl_d, int_x86_sse2_psrli_d>;
2575 defm PSRLQ : PDI_binop_rmi_int<0xD3, 0x73, MRM2r, "psrlq",
2576                                int_x86_sse2_psrl_q, int_x86_sse2_psrli_q>;
2577
2578 defm PSRAW : PDI_binop_rmi_int<0xE1, 0x71, MRM4r, "psraw",
2579                                int_x86_sse2_psra_w, int_x86_sse2_psrai_w>;
2580 defm PSRAD : PDI_binop_rmi_int<0xE2, 0x72, MRM4r, "psrad",
2581                                int_x86_sse2_psra_d, int_x86_sse2_psrai_d>;
2582
2583 defm PAND : PDI_binop_rm_v2i64<0xDB, "pand", and, 1>;
2584 defm POR  : PDI_binop_rm_v2i64<0xEB, "por" , or, 1>;
2585 defm PXOR : PDI_binop_rm_v2i64<0xEF, "pxor", xor, 1>;
2586
2587 let ExeDomain = SSEPackedInt in {
2588   let neverHasSideEffects = 1 in {
2589     // 128-bit logical shifts.
2590     def PSLLDQri : PDIi8<0x73, MRM7r,
2591                          (outs VR128:$dst), (ins VR128:$src1, i32i8imm:$src2),
2592                          "pslldq\t{$src2, $dst|$dst, $src2}", []>;
2593     def PSRLDQri : PDIi8<0x73, MRM3r,
2594                          (outs VR128:$dst), (ins VR128:$src1, i32i8imm:$src2),
2595                          "psrldq\t{$src2, $dst|$dst, $src2}", []>;
2596     // PSRADQri doesn't exist in SSE[1-3].
2597   }
2598   def PANDNrr : PDI<0xDF, MRMSrcReg,
2599                     (outs VR128:$dst), (ins VR128:$src1, VR128:$src2),
2600                     "pandn\t{$src2, $dst|$dst, $src2}",
2601                     [(set VR128:$dst, (v2i64 (and (vnot VR128:$src1),
2602                                               VR128:$src2)))]>;
2603
2604   def PANDNrm : PDI<0xDF, MRMSrcMem,
2605                     (outs VR128:$dst), (ins VR128:$src1, i128mem:$src2),
2606                     "pandn\t{$src2, $dst|$dst, $src2}",
2607                     [(set VR128:$dst, (v2i64 (and (vnot VR128:$src1),
2608                                               (memopv2i64 addr:$src2))))]>;
2609 }
2610 } // Constraints = "$src1 = $dst"
2611
2612 let Predicates = [HasAVX] in {
2613   def : Pat<(int_x86_sse2_psll_dq VR128:$src1, imm:$src2),
2614             (v2i64 (VPSLLDQri VR128:$src1, (BYTE_imm imm:$src2)))>;
2615   def : Pat<(int_x86_sse2_psrl_dq VR128:$src1, imm:$src2),
2616             (v2i64 (VPSRLDQri VR128:$src1, (BYTE_imm imm:$src2)))>;
2617   def : Pat<(int_x86_sse2_psll_dq_bs VR128:$src1, imm:$src2),
2618             (v2i64 (VPSLLDQri VR128:$src1, imm:$src2))>;
2619   def : Pat<(int_x86_sse2_psrl_dq_bs VR128:$src1, imm:$src2),
2620             (v2i64 (VPSRLDQri VR128:$src1, imm:$src2))>;
2621   def : Pat<(v2f64 (X86fsrl VR128:$src1, i32immSExt8:$src2)),
2622             (v2f64 (VPSRLDQri VR128:$src1, (BYTE_imm imm:$src2)))>;
2623
2624   // Shift up / down and insert zero's.
2625   def : Pat<(v2i64 (X86vshl  VR128:$src, (i8 imm:$amt))),
2626             (v2i64 (VPSLLDQri VR128:$src, (BYTE_imm imm:$amt)))>;
2627   def : Pat<(v2i64 (X86vshr  VR128:$src, (i8 imm:$amt))),
2628             (v2i64 (VPSRLDQri VR128:$src, (BYTE_imm imm:$amt)))>;
2629 }
2630
2631 let Predicates = [HasSSE2] in {
2632   def : Pat<(int_x86_sse2_psll_dq VR128:$src1, imm:$src2),
2633             (v2i64 (PSLLDQri VR128:$src1, (BYTE_imm imm:$src2)))>;
2634   def : Pat<(int_x86_sse2_psrl_dq VR128:$src1, imm:$src2),
2635             (v2i64 (PSRLDQri VR128:$src1, (BYTE_imm imm:$src2)))>;
2636   def : Pat<(int_x86_sse2_psll_dq_bs VR128:$src1, imm:$src2),
2637             (v2i64 (PSLLDQri VR128:$src1, imm:$src2))>;
2638   def : Pat<(int_x86_sse2_psrl_dq_bs VR128:$src1, imm:$src2),
2639             (v2i64 (PSRLDQri VR128:$src1, imm:$src2))>;
2640   def : Pat<(v2f64 (X86fsrl VR128:$src1, i32immSExt8:$src2)),
2641             (v2f64 (PSRLDQri VR128:$src1, (BYTE_imm imm:$src2)))>;
2642
2643   // Shift up / down and insert zero's.
2644   def : Pat<(v2i64 (X86vshl  VR128:$src, (i8 imm:$amt))),
2645             (v2i64 (PSLLDQri VR128:$src, (BYTE_imm imm:$amt)))>;
2646   def : Pat<(v2i64 (X86vshr  VR128:$src, (i8 imm:$amt))),
2647             (v2i64 (PSRLDQri VR128:$src, (BYTE_imm imm:$amt)))>;
2648 }
2649
2650 //===---------------------------------------------------------------------===//
2651 // SSE2 - Packed Integer Comparison Instructions
2652 //===---------------------------------------------------------------------===//
2653
2654 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
2655   defm VPCMPEQB  : PDI_binop_rm_int<0x74, "vpcmpeqb", int_x86_sse2_pcmpeq_b, 1,
2656                                     0>, VEX_4V;
2657   defm VPCMPEQW  : PDI_binop_rm_int<0x75, "vpcmpeqw", int_x86_sse2_pcmpeq_w, 1,
2658                                     0>, VEX_4V;
2659   defm VPCMPEQD  : PDI_binop_rm_int<0x76, "vpcmpeqd", int_x86_sse2_pcmpeq_d, 1,
2660                                     0>, VEX_4V;
2661   defm VPCMPGTB  : PDI_binop_rm_int<0x64, "vpcmpgtb", int_x86_sse2_pcmpgt_b, 0,
2662                                     0>, VEX_4V;
2663   defm VPCMPGTW  : PDI_binop_rm_int<0x65, "vpcmpgtw", int_x86_sse2_pcmpgt_w, 0,
2664                                     0>, VEX_4V;
2665   defm VPCMPGTD  : PDI_binop_rm_int<0x66, "vpcmpgtd", int_x86_sse2_pcmpgt_d, 0,
2666                                     0>, VEX_4V;
2667 }
2668
2669 let Constraints = "$src1 = $dst" in {
2670   defm PCMPEQB  : PDI_binop_rm_int<0x74, "pcmpeqb", int_x86_sse2_pcmpeq_b, 1>;
2671   defm PCMPEQW  : PDI_binop_rm_int<0x75, "pcmpeqw", int_x86_sse2_pcmpeq_w, 1>;
2672   defm PCMPEQD  : PDI_binop_rm_int<0x76, "pcmpeqd", int_x86_sse2_pcmpeq_d, 1>;
2673   defm PCMPGTB  : PDI_binop_rm_int<0x64, "pcmpgtb", int_x86_sse2_pcmpgt_b>;
2674   defm PCMPGTW  : PDI_binop_rm_int<0x65, "pcmpgtw", int_x86_sse2_pcmpgt_w>;
2675   defm PCMPGTD  : PDI_binop_rm_int<0x66, "pcmpgtd", int_x86_sse2_pcmpgt_d>;
2676 } // Constraints = "$src1 = $dst"
2677
2678 def : Pat<(v16i8 (X86pcmpeqb VR128:$src1, VR128:$src2)),
2679           (PCMPEQBrr VR128:$src1, VR128:$src2)>;
2680 def : Pat<(v16i8 (X86pcmpeqb VR128:$src1, (memop addr:$src2))),
2681           (PCMPEQBrm VR128:$src1, addr:$src2)>;
2682 def : Pat<(v8i16 (X86pcmpeqw VR128:$src1, VR128:$src2)),
2683           (PCMPEQWrr VR128:$src1, VR128:$src2)>;
2684 def : Pat<(v8i16 (X86pcmpeqw VR128:$src1, (memop addr:$src2))),
2685           (PCMPEQWrm VR128:$src1, addr:$src2)>;
2686 def : Pat<(v4i32 (X86pcmpeqd VR128:$src1, VR128:$src2)),
2687           (PCMPEQDrr VR128:$src1, VR128:$src2)>;
2688 def : Pat<(v4i32 (X86pcmpeqd VR128:$src1, (memop addr:$src2))),
2689           (PCMPEQDrm VR128:$src1, addr:$src2)>;
2690
2691 def : Pat<(v16i8 (X86pcmpgtb VR128:$src1, VR128:$src2)),
2692           (PCMPGTBrr VR128:$src1, VR128:$src2)>;
2693 def : Pat<(v16i8 (X86pcmpgtb VR128:$src1, (memop addr:$src2))),
2694           (PCMPGTBrm VR128:$src1, addr:$src2)>;
2695 def : Pat<(v8i16 (X86pcmpgtw VR128:$src1, VR128:$src2)),
2696           (PCMPGTWrr VR128:$src1, VR128:$src2)>;
2697 def : Pat<(v8i16 (X86pcmpgtw VR128:$src1, (memop addr:$src2))),
2698           (PCMPGTWrm VR128:$src1, addr:$src2)>;
2699 def : Pat<(v4i32 (X86pcmpgtd VR128:$src1, VR128:$src2)),
2700           (PCMPGTDrr VR128:$src1, VR128:$src2)>;
2701 def : Pat<(v4i32 (X86pcmpgtd VR128:$src1, (memop addr:$src2))),
2702           (PCMPGTDrm VR128:$src1, addr:$src2)>;
2703
2704 //===---------------------------------------------------------------------===//
2705 // SSE2 - Packed Integer Pack Instructions
2706 //===---------------------------------------------------------------------===//
2707
2708 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
2709 defm VPACKSSWB : PDI_binop_rm_int<0x63, "vpacksswb", int_x86_sse2_packsswb_128,
2710                                   0, 0>, VEX_4V;
2711 defm VPACKSSDW : PDI_binop_rm_int<0x6B, "vpackssdw", int_x86_sse2_packssdw_128,
2712                                   0, 0>, VEX_4V;
2713 defm VPACKUSWB : PDI_binop_rm_int<0x67, "vpackuswb", int_x86_sse2_packuswb_128,
2714                                   0, 0>, VEX_4V;
2715 }
2716
2717 let Constraints = "$src1 = $dst" in {
2718 defm PACKSSWB : PDI_binop_rm_int<0x63, "packsswb", int_x86_sse2_packsswb_128>;
2719 defm PACKSSDW : PDI_binop_rm_int<0x6B, "packssdw", int_x86_sse2_packssdw_128>;
2720 defm PACKUSWB : PDI_binop_rm_int<0x67, "packuswb", int_x86_sse2_packuswb_128>;
2721 } // Constraints = "$src1 = $dst"
2722
2723 //===---------------------------------------------------------------------===//
2724 // SSE2 - Packed Integer Shuffle Instructions
2725 //===---------------------------------------------------------------------===//
2726
2727 let ExeDomain = SSEPackedInt in {
2728 multiclass sse2_pshuffle<string OpcodeStr, ValueType vt, PatFrag pshuf_frag,
2729                          PatFrag bc_frag> {
2730 def ri : Ii8<0x70, MRMSrcReg,
2731               (outs VR128:$dst), (ins VR128:$src1, i8imm:$src2),
2732               !strconcat(OpcodeStr,
2733                          "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
2734               [(set VR128:$dst, (vt (pshuf_frag:$src2 VR128:$src1,
2735                                                       (undef))))]>;
2736 def mi : Ii8<0x70, MRMSrcMem,
2737               (outs VR128:$dst), (ins i128mem:$src1, i8imm:$src2),
2738               !strconcat(OpcodeStr,
2739                          "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
2740               [(set VR128:$dst, (vt (pshuf_frag:$src2
2741                                       (bc_frag (memopv2i64 addr:$src1)),
2742                                       (undef))))]>;
2743 }
2744 } // ExeDomain = SSEPackedInt
2745
2746 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
2747   let AddedComplexity = 5 in
2748   defm VPSHUFD : sse2_pshuffle<"vpshufd", v4i32, pshufd, bc_v4i32>, OpSize,
2749                                VEX;
2750
2751   // SSE2 with ImmT == Imm8 and XS prefix.
2752   defm VPSHUFHW : sse2_pshuffle<"vpshufhw", v8i16, pshufhw, bc_v8i16>, XS,
2753                                VEX;
2754
2755   // SSE2 with ImmT == Imm8 and XD prefix.
2756   defm VPSHUFLW : sse2_pshuffle<"vpshuflw", v8i16, pshuflw, bc_v8i16>, XD,
2757                                VEX;
2758 }
2759
2760 let Predicates = [HasSSE2] in {
2761   let AddedComplexity = 5 in
2762   defm PSHUFD : sse2_pshuffle<"pshufd", v4i32, pshufd, bc_v4i32>, TB, OpSize;
2763
2764   // SSE2 with ImmT == Imm8 and XS prefix.
2765   defm PSHUFHW : sse2_pshuffle<"pshufhw", v8i16, pshufhw, bc_v8i16>, XS;
2766
2767   // SSE2 with ImmT == Imm8 and XD prefix.
2768   defm PSHUFLW : sse2_pshuffle<"pshuflw", v8i16, pshuflw, bc_v8i16>, XD;
2769 }
2770
2771 //===---------------------------------------------------------------------===//
2772 // SSE2 - Packed Integer Unpack Instructions
2773 //===---------------------------------------------------------------------===//
2774
2775 let ExeDomain = SSEPackedInt in {
2776 multiclass sse2_unpack<bits<8> opc, string OpcodeStr, ValueType vt,
2777                        PatFrag unp_frag, PatFrag bc_frag, bit Is2Addr = 1> {
2778   def rr : PDI<opc, MRMSrcReg,
2779       (outs VR128:$dst), (ins VR128:$src1, VR128:$src2),
2780       !if(Is2Addr,
2781           !strconcat(OpcodeStr,"\t{$src2, $dst|$dst, $src2}"),
2782           !strconcat(OpcodeStr,"\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
2783       [(set VR128:$dst, (vt (unp_frag VR128:$src1, VR128:$src2)))]>;
2784   def rm : PDI<opc, MRMSrcMem,
2785       (outs VR128:$dst), (ins VR128:$src1, i128mem:$src2),
2786       !if(Is2Addr,
2787           !strconcat(OpcodeStr,"\t{$src2, $dst|$dst, $src2}"),
2788           !strconcat(OpcodeStr,"\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
2789       [(set VR128:$dst, (unp_frag VR128:$src1,
2790                                   (bc_frag (memopv2i64
2791                                                addr:$src2))))]>;
2792 }
2793
2794 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
2795   defm VPUNPCKLBW  : sse2_unpack<0x60, "vpunpcklbw", v16i8, unpckl, bc_v16i8,
2796                                  0>, VEX_4V;
2797   defm VPUNPCKLWD  : sse2_unpack<0x61, "vpunpcklwd", v8i16, unpckl, bc_v8i16,
2798                                  0>, VEX_4V;
2799   defm VPUNPCKLDQ  : sse2_unpack<0x62, "vpunpckldq", v4i32, unpckl, bc_v4i32,
2800                                  0>, VEX_4V;
2801
2802   /// FIXME: we could eliminate this and use sse2_unpack instead if tblgen
2803   /// knew to collapse (bitconvert VT to VT) into its operand.
2804   def VPUNPCKLQDQrr : PDI<0x6C, MRMSrcReg,
2805                          (outs VR128:$dst), (ins VR128:$src1, VR128:$src2),
2806                          "vpunpcklqdq\t{$src2, $src1, $dst|$dst, $src1, $src2}",
2807                         [(set VR128:$dst,
2808                           (v2i64 (unpckl VR128:$src1, VR128:$src2)))]>, VEX_4V;
2809   def VPUNPCKLQDQrm : PDI<0x6C, MRMSrcMem,
2810                          (outs VR128:$dst), (ins VR128:$src1, i128mem:$src2),
2811                          "vpunpcklqdq\t{$src2, $src1, $dst|$dst, $src1, $src2}",
2812                         [(set VR128:$dst,
2813                           (v2i64 (unpckl VR128:$src1,
2814                                          (memopv2i64 addr:$src2))))]>, VEX_4V;
2815
2816   defm VPUNPCKHBW  : sse2_unpack<0x68, "vpunpckhbw", v16i8, unpckh, bc_v16i8,
2817                                  0>, VEX_4V;
2818   defm VPUNPCKHWD  : sse2_unpack<0x69, "vpunpckhwd", v8i16, unpckh, bc_v8i16,
2819                                  0>, VEX_4V;
2820   defm VPUNPCKHDQ  : sse2_unpack<0x6A, "vpunpckhdq", v4i32, unpckh, bc_v4i32,
2821                                  0>, VEX_4V;
2822
2823   /// FIXME: we could eliminate this and use sse2_unpack instead if tblgen
2824   /// knew to collapse (bitconvert VT to VT) into its operand.
2825   def VPUNPCKHQDQrr : PDI<0x6D, MRMSrcReg,
2826                          (outs VR128:$dst), (ins VR128:$src1, VR128:$src2),
2827                          "vpunpckhqdq\t{$src2, $src1, $dst|$dst, $src1, $src2}",
2828                         [(set VR128:$dst,
2829                           (v2i64 (unpckh VR128:$src1, VR128:$src2)))]>, VEX_4V;
2830   def VPUNPCKHQDQrm : PDI<0x6D, MRMSrcMem,
2831                         (outs VR128:$dst), (ins VR128:$src1, i128mem:$src2),
2832                         "vpunpckhqdq\t{$src2, $src1, $dst|$dst, $src1, $src2}",
2833                         [(set VR128:$dst,
2834                           (v2i64 (unpckh VR128:$src1,
2835                                          (memopv2i64 addr:$src2))))]>, VEX_4V;
2836 }
2837
2838 let Constraints = "$src1 = $dst" in {
2839   defm PUNPCKLBW  : sse2_unpack<0x60, "punpcklbw", v16i8, unpckl, bc_v16i8>;
2840   defm PUNPCKLWD  : sse2_unpack<0x61, "punpcklwd", v8i16, unpckl, bc_v8i16>;
2841   defm PUNPCKLDQ  : sse2_unpack<0x62, "punpckldq", v4i32, unpckl, bc_v4i32>;
2842
2843   /// FIXME: we could eliminate this and use sse2_unpack instead if tblgen
2844   /// knew to collapse (bitconvert VT to VT) into its operand.
2845   def PUNPCKLQDQrr : PDI<0x6C, MRMSrcReg,
2846                          (outs VR128:$dst), (ins VR128:$src1, VR128:$src2),
2847                          "punpcklqdq\t{$src2, $dst|$dst, $src2}",
2848                         [(set VR128:$dst,
2849                           (v2i64 (unpckl VR128:$src1, VR128:$src2)))]>;
2850   def PUNPCKLQDQrm : PDI<0x6C, MRMSrcMem,
2851                          (outs VR128:$dst), (ins VR128:$src1, i128mem:$src2),
2852                          "punpcklqdq\t{$src2, $dst|$dst, $src2}",
2853                         [(set VR128:$dst,
2854                           (v2i64 (unpckl VR128:$src1,
2855                                          (memopv2i64 addr:$src2))))]>;
2856
2857   defm PUNPCKHBW  : sse2_unpack<0x68, "punpckhbw", v16i8, unpckh, bc_v16i8>;
2858   defm PUNPCKHWD  : sse2_unpack<0x69, "punpckhwd", v8i16, unpckh, bc_v8i16>;
2859   defm PUNPCKHDQ  : sse2_unpack<0x6A, "punpckhdq", v4i32, unpckh, bc_v4i32>;
2860
2861   /// FIXME: we could eliminate this and use sse2_unpack instead if tblgen
2862   /// knew to collapse (bitconvert VT to VT) into its operand.
2863   def PUNPCKHQDQrr : PDI<0x6D, MRMSrcReg,
2864                          (outs VR128:$dst), (ins VR128:$src1, VR128:$src2),
2865                          "punpckhqdq\t{$src2, $dst|$dst, $src2}",
2866                         [(set VR128:$dst,
2867                           (v2i64 (unpckh VR128:$src1, VR128:$src2)))]>;
2868   def PUNPCKHQDQrm : PDI<0x6D, MRMSrcMem,
2869                         (outs VR128:$dst), (ins VR128:$src1, i128mem:$src2),
2870                         "punpckhqdq\t{$src2, $dst|$dst, $src2}",
2871                         [(set VR128:$dst,
2872                           (v2i64 (unpckh VR128:$src1,
2873                                          (memopv2i64 addr:$src2))))]>;
2874 }
2875
2876 } // ExeDomain = SSEPackedInt
2877
2878 //===---------------------------------------------------------------------===//
2879 // SSE2 - Packed Integer Extract and Insert
2880 //===---------------------------------------------------------------------===//
2881
2882 let ExeDomain = SSEPackedInt in {
2883 multiclass sse2_pinsrw<bit Is2Addr = 1> {
2884   def rri : Ii8<0xC4, MRMSrcReg,
2885        (outs VR128:$dst), (ins VR128:$src1,
2886         GR32:$src2, i32i8imm:$src3),
2887        !if(Is2Addr,
2888            "pinsrw\t{$src3, $src2, $dst|$dst, $src2, $src3}",
2889            "vpinsrw\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}"),
2890        [(set VR128:$dst,
2891          (X86pinsrw VR128:$src1, GR32:$src2, imm:$src3))]>;
2892   def rmi : Ii8<0xC4, MRMSrcMem,
2893                        (outs VR128:$dst), (ins VR128:$src1,
2894                         i16mem:$src2, i32i8imm:$src3),
2895        !if(Is2Addr,
2896            "pinsrw\t{$src3, $src2, $dst|$dst, $src2, $src3}",
2897            "vpinsrw\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}"),
2898        [(set VR128:$dst,
2899          (X86pinsrw VR128:$src1, (extloadi16 addr:$src2),
2900                     imm:$src3))]>;
2901 }
2902
2903 // Extract
2904 let isAsmParserOnly = 1, Predicates = [HasAVX] in
2905 def VPEXTRWri : Ii8<0xC5, MRMSrcReg,
2906                     (outs GR32:$dst), (ins VR128:$src1, i32i8imm:$src2),
2907                     "vpextrw\t{$src2, $src1, $dst|$dst, $src1, $src2}",
2908                     [(set GR32:$dst, (X86pextrw (v8i16 VR128:$src1),
2909                                                 imm:$src2))]>, OpSize, VEX;
2910 def PEXTRWri : PDIi8<0xC5, MRMSrcReg,
2911                     (outs GR32:$dst), (ins VR128:$src1, i32i8imm:$src2),
2912                     "pextrw\t{$src2, $src1, $dst|$dst, $src1, $src2}",
2913                     [(set GR32:$dst, (X86pextrw (v8i16 VR128:$src1),
2914                                                 imm:$src2))]>;
2915
2916 // Insert
2917 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
2918   defm VPINSRW : sse2_pinsrw<0>, OpSize, VEX_4V;
2919   def  VPINSRWrr64i : Ii8<0xC4, MRMSrcReg, (outs VR128:$dst),
2920        (ins VR128:$src1, GR64:$src2, i32i8imm:$src3),
2921        "vpinsrw\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}",
2922        []>, OpSize, VEX_4V;
2923 }
2924
2925 let Constraints = "$src1 = $dst" in
2926   defm PINSRW : sse2_pinsrw, TB, OpSize, Requires<[HasSSE2]>;
2927
2928 } // ExeDomain = SSEPackedInt
2929
2930 //===---------------------------------------------------------------------===//
2931 // SSE2 - Packed Mask Creation
2932 //===---------------------------------------------------------------------===//
2933
2934 let ExeDomain = SSEPackedInt in {
2935
2936 let isAsmParserOnly = 1 in {
2937 def VPMOVMSKBrr  : VPDI<0xD7, MRMSrcReg, (outs GR32:$dst), (ins VR128:$src),
2938            "pmovmskb\t{$src, $dst|$dst, $src}",
2939            [(set GR32:$dst, (int_x86_sse2_pmovmskb_128 VR128:$src))]>, VEX;
2940 def VPMOVMSKBr64r : VPDI<0xD7, MRMSrcReg, (outs GR64:$dst), (ins VR128:$src),
2941            "pmovmskb\t{$src, $dst|$dst, $src}", []>, VEX;
2942 }
2943 def PMOVMSKBrr : PDI<0xD7, MRMSrcReg, (outs GR32:$dst), (ins VR128:$src),
2944            "pmovmskb\t{$src, $dst|$dst, $src}",
2945            [(set GR32:$dst, (int_x86_sse2_pmovmskb_128 VR128:$src))]>;
2946
2947 } // ExeDomain = SSEPackedInt
2948
2949 //===---------------------------------------------------------------------===//
2950 // SSE2 - Conditional Store
2951 //===---------------------------------------------------------------------===//
2952
2953 let ExeDomain = SSEPackedInt in {
2954
2955 let isAsmParserOnly = 1 in {
2956 let Uses = [EDI] in
2957 def VMASKMOVDQU : VPDI<0xF7, MRMSrcReg, (outs),
2958            (ins VR128:$src, VR128:$mask),
2959            "maskmovdqu\t{$mask, $src|$src, $mask}",
2960            [(int_x86_sse2_maskmov_dqu VR128:$src, VR128:$mask, EDI)]>, VEX;
2961 let Uses = [RDI] in
2962 def VMASKMOVDQU64 : VPDI<0xF7, MRMSrcReg, (outs),
2963            (ins VR128:$src, VR128:$mask),
2964            "maskmovdqu\t{$mask, $src|$src, $mask}",
2965            [(int_x86_sse2_maskmov_dqu VR128:$src, VR128:$mask, RDI)]>, VEX;
2966 }
2967
2968 let Uses = [EDI] in
2969 def MASKMOVDQU : PDI<0xF7, MRMSrcReg, (outs), (ins VR128:$src, VR128:$mask),
2970            "maskmovdqu\t{$mask, $src|$src, $mask}",
2971            [(int_x86_sse2_maskmov_dqu VR128:$src, VR128:$mask, EDI)]>;
2972 let Uses = [RDI] in
2973 def MASKMOVDQU64 : PDI<0xF7, MRMSrcReg, (outs), (ins VR128:$src, VR128:$mask),
2974            "maskmovdqu\t{$mask, $src|$src, $mask}",
2975            [(int_x86_sse2_maskmov_dqu VR128:$src, VR128:$mask, RDI)]>;
2976
2977 } // ExeDomain = SSEPackedInt
2978
2979 //===---------------------------------------------------------------------===//
2980 // SSE2 - Move Doubleword
2981 //===---------------------------------------------------------------------===//
2982
2983 // Move Int Doubleword to Packed Double Int
2984 let isAsmParserOnly = 1 in {
2985 def VMOVDI2PDIrr : VPDI<0x6E, MRMSrcReg, (outs VR128:$dst), (ins GR32:$src),
2986                       "movd\t{$src, $dst|$dst, $src}",
2987                       [(set VR128:$dst,
2988                         (v4i32 (scalar_to_vector GR32:$src)))]>, VEX;
2989 def VMOVDI2PDIrm : VPDI<0x6E, MRMSrcMem, (outs VR128:$dst), (ins i32mem:$src),
2990                       "movd\t{$src, $dst|$dst, $src}",
2991                       [(set VR128:$dst,
2992                         (v4i32 (scalar_to_vector (loadi32 addr:$src))))]>,
2993                       VEX;
2994 }
2995 def MOVDI2PDIrr : PDI<0x6E, MRMSrcReg, (outs VR128:$dst), (ins GR32:$src),
2996                       "movd\t{$src, $dst|$dst, $src}",
2997                       [(set VR128:$dst,
2998                         (v4i32 (scalar_to_vector GR32:$src)))]>;
2999 def MOVDI2PDIrm : PDI<0x6E, MRMSrcMem, (outs VR128:$dst), (ins i32mem:$src),
3000                       "movd\t{$src, $dst|$dst, $src}",
3001                       [(set VR128:$dst,
3002                         (v4i32 (scalar_to_vector (loadi32 addr:$src))))]>;
3003
3004
3005 // Move Int Doubleword to Single Scalar
3006 let isAsmParserOnly = 1 in {
3007 def VMOVDI2SSrr  : VPDI<0x6E, MRMSrcReg, (outs FR32:$dst), (ins GR32:$src),
3008                       "movd\t{$src, $dst|$dst, $src}",
3009                       [(set FR32:$dst, (bitconvert GR32:$src))]>, VEX;
3010
3011 def VMOVDI2SSrm  : VPDI<0x6E, MRMSrcMem, (outs FR32:$dst), (ins i32mem:$src),
3012                       "movd\t{$src, $dst|$dst, $src}",
3013                       [(set FR32:$dst, (bitconvert (loadi32 addr:$src)))]>,
3014                       VEX;
3015 }
3016 def MOVDI2SSrr  : PDI<0x6E, MRMSrcReg, (outs FR32:$dst), (ins GR32:$src),
3017                       "movd\t{$src, $dst|$dst, $src}",
3018                       [(set FR32:$dst, (bitconvert GR32:$src))]>;
3019
3020 def MOVDI2SSrm  : PDI<0x6E, MRMSrcMem, (outs FR32:$dst), (ins i32mem:$src),
3021                       "movd\t{$src, $dst|$dst, $src}",
3022                       [(set FR32:$dst, (bitconvert (loadi32 addr:$src)))]>;
3023
3024 // Move Packed Doubleword Int to Packed Double Int
3025 let isAsmParserOnly = 1 in {
3026 def VMOVPDI2DIrr  : VPDI<0x7E, MRMDestReg, (outs GR32:$dst), (ins VR128:$src),
3027                        "movd\t{$src, $dst|$dst, $src}",
3028                        [(set GR32:$dst, (vector_extract (v4i32 VR128:$src),
3029                                         (iPTR 0)))]>, VEX;
3030 def VMOVPDI2DImr  : VPDI<0x7E, MRMDestMem, (outs),
3031                        (ins i32mem:$dst, VR128:$src),
3032                        "movd\t{$src, $dst|$dst, $src}",
3033                        [(store (i32 (vector_extract (v4i32 VR128:$src),
3034                                      (iPTR 0))), addr:$dst)]>, VEX;
3035 }
3036 def MOVPDI2DIrr  : PDI<0x7E, MRMDestReg, (outs GR32:$dst), (ins VR128:$src),
3037                        "movd\t{$src, $dst|$dst, $src}",
3038                        [(set GR32:$dst, (vector_extract (v4i32 VR128:$src),
3039                                         (iPTR 0)))]>;
3040 def MOVPDI2DImr  : PDI<0x7E, MRMDestMem, (outs), (ins i32mem:$dst, VR128:$src),
3041                        "movd\t{$src, $dst|$dst, $src}",
3042                        [(store (i32 (vector_extract (v4i32 VR128:$src),
3043                                      (iPTR 0))), addr:$dst)]>;
3044
3045 // Move Scalar Single to Double Int
3046 let isAsmParserOnly = 1 in {
3047 def VMOVSS2DIrr  : VPDI<0x7E, MRMDestReg, (outs GR32:$dst), (ins FR32:$src),
3048                       "movd\t{$src, $dst|$dst, $src}",
3049                       [(set GR32:$dst, (bitconvert FR32:$src))]>, VEX;
3050 def VMOVSS2DImr  : VPDI<0x7E, MRMDestMem, (outs), (ins i32mem:$dst, FR32:$src),
3051                       "movd\t{$src, $dst|$dst, $src}",
3052                       [(store (i32 (bitconvert FR32:$src)), addr:$dst)]>, VEX;
3053 }
3054 def MOVSS2DIrr  : PDI<0x7E, MRMDestReg, (outs GR32:$dst), (ins FR32:$src),
3055                       "movd\t{$src, $dst|$dst, $src}",
3056                       [(set GR32:$dst, (bitconvert FR32:$src))]>;
3057 def MOVSS2DImr  : PDI<0x7E, MRMDestMem, (outs), (ins i32mem:$dst, FR32:$src),
3058                       "movd\t{$src, $dst|$dst, $src}",
3059                       [(store (i32 (bitconvert FR32:$src)), addr:$dst)]>;
3060
3061 // movd / movq to XMM register zero-extends
3062 let AddedComplexity = 15, isAsmParserOnly = 1 in {
3063 def VMOVZDI2PDIrr : VPDI<0x6E, MRMSrcReg, (outs VR128:$dst), (ins GR32:$src),
3064                        "movd\t{$src, $dst|$dst, $src}",
3065                        [(set VR128:$dst, (v4i32 (X86vzmovl
3066                                       (v4i32 (scalar_to_vector GR32:$src)))))]>,
3067                                       VEX;
3068 def VMOVZQI2PQIrr : VPDI<0x6E, MRMSrcReg, (outs VR128:$dst), (ins GR64:$src),
3069                        "mov{d|q}\t{$src, $dst|$dst, $src}", // X86-64 only
3070                        [(set VR128:$dst, (v2i64 (X86vzmovl
3071                                       (v2i64 (scalar_to_vector GR64:$src)))))]>,
3072                                       VEX, VEX_W;
3073 }
3074 let AddedComplexity = 15 in {
3075 def MOVZDI2PDIrr : PDI<0x6E, MRMSrcReg, (outs VR128:$dst), (ins GR32:$src),
3076                        "movd\t{$src, $dst|$dst, $src}",
3077                        [(set VR128:$dst, (v4i32 (X86vzmovl
3078                                       (v4i32 (scalar_to_vector GR32:$src)))))]>;
3079 def MOVZQI2PQIrr : RPDI<0x6E, MRMSrcReg, (outs VR128:$dst), (ins GR64:$src),
3080                        "mov{d|q}\t{$src, $dst|$dst, $src}", // X86-64 only
3081                        [(set VR128:$dst, (v2i64 (X86vzmovl
3082                                       (v2i64 (scalar_to_vector GR64:$src)))))]>;
3083 }
3084
3085 let AddedComplexity = 20 in {
3086 let isAsmParserOnly = 1 in
3087 def VMOVZDI2PDIrm : VPDI<0x6E, MRMSrcMem, (outs VR128:$dst), (ins i32mem:$src),
3088                        "movd\t{$src, $dst|$dst, $src}",
3089                        [(set VR128:$dst,
3090                          (v4i32 (X86vzmovl (v4i32 (scalar_to_vector
3091                                                    (loadi32 addr:$src))))))]>,
3092                                                    VEX;
3093 def MOVZDI2PDIrm : PDI<0x6E, MRMSrcMem, (outs VR128:$dst), (ins i32mem:$src),
3094                        "movd\t{$src, $dst|$dst, $src}",
3095                        [(set VR128:$dst,
3096                          (v4i32 (X86vzmovl (v4i32 (scalar_to_vector
3097                                                    (loadi32 addr:$src))))))]>;
3098
3099 def : Pat<(v4i32 (X86vzmovl (loadv4i32 addr:$src))),
3100             (MOVZDI2PDIrm addr:$src)>;
3101 def : Pat<(v4i32 (X86vzmovl (bc_v4i32 (loadv4f32 addr:$src)))),
3102             (MOVZDI2PDIrm addr:$src)>;
3103 def : Pat<(v4i32 (X86vzmovl (bc_v4i32 (loadv2i64 addr:$src)))),
3104             (MOVZDI2PDIrm addr:$src)>;
3105 }
3106
3107 //===---------------------------------------------------------------------===//
3108 // SSE2 - Move Quadword
3109 //===---------------------------------------------------------------------===//
3110
3111 // Move Quadword Int to Packed Quadword Int
3112 let isAsmParserOnly = 1 in
3113 def VMOVQI2PQIrm : I<0x7E, MRMSrcMem, (outs VR128:$dst), (ins i64mem:$src),
3114                     "vmovq\t{$src, $dst|$dst, $src}",
3115                     [(set VR128:$dst,
3116                       (v2i64 (scalar_to_vector (loadi64 addr:$src))))]>, XS,
3117                     VEX, Requires<[HasAVX]>;
3118 def MOVQI2PQIrm : I<0x7E, MRMSrcMem, (outs VR128:$dst), (ins i64mem:$src),
3119                     "movq\t{$src, $dst|$dst, $src}",
3120                     [(set VR128:$dst,
3121                       (v2i64 (scalar_to_vector (loadi64 addr:$src))))]>, XS,
3122                     Requires<[HasSSE2]>; // SSE2 instruction with XS Prefix
3123
3124 // Move Packed Quadword Int to Quadword Int
3125 let isAsmParserOnly = 1 in
3126 def VMOVPQI2QImr : VPDI<0xD6, MRMDestMem, (outs), (ins i64mem:$dst, VR128:$src),
3127                       "movq\t{$src, $dst|$dst, $src}",
3128                       [(store (i64 (vector_extract (v2i64 VR128:$src),
3129                                     (iPTR 0))), addr:$dst)]>, VEX;
3130 def MOVPQI2QImr : PDI<0xD6, MRMDestMem, (outs), (ins i64mem:$dst, VR128:$src),
3131                       "movq\t{$src, $dst|$dst, $src}",
3132                       [(store (i64 (vector_extract (v2i64 VR128:$src),
3133                                     (iPTR 0))), addr:$dst)]>;
3134
3135 def : Pat<(f64 (vector_extract (v2f64 VR128:$src), (iPTR 0))),
3136           (f64 (EXTRACT_SUBREG (v2f64 VR128:$src), sub_sd))>;
3137
3138 // Store / copy lower 64-bits of a XMM register.
3139 let isAsmParserOnly = 1 in
3140 def VMOVLQ128mr : VPDI<0xD6, MRMDestMem, (outs), (ins i64mem:$dst, VR128:$src),
3141                      "movq\t{$src, $dst|$dst, $src}",
3142                      [(int_x86_sse2_storel_dq addr:$dst, VR128:$src)]>, VEX;
3143 def MOVLQ128mr : PDI<0xD6, MRMDestMem, (outs), (ins i64mem:$dst, VR128:$src),
3144                      "movq\t{$src, $dst|$dst, $src}",
3145                      [(int_x86_sse2_storel_dq addr:$dst, VR128:$src)]>;
3146
3147 let AddedComplexity = 20, isAsmParserOnly = 1 in
3148 def VMOVZQI2PQIrm : I<0x7E, MRMSrcMem, (outs VR128:$dst), (ins i64mem:$src),
3149                      "vmovq\t{$src, $dst|$dst, $src}",
3150                      [(set VR128:$dst,
3151                        (v2i64 (X86vzmovl (v2i64 (scalar_to_vector
3152                                                  (loadi64 addr:$src))))))]>,
3153                      XS, VEX, Requires<[HasAVX]>;
3154
3155 let AddedComplexity = 20 in {
3156 def MOVZQI2PQIrm : I<0x7E, MRMSrcMem, (outs VR128:$dst), (ins i64mem:$src),
3157                      "movq\t{$src, $dst|$dst, $src}",
3158                      [(set VR128:$dst,
3159                        (v2i64 (X86vzmovl (v2i64 (scalar_to_vector
3160                                                  (loadi64 addr:$src))))))]>,
3161                      XS, Requires<[HasSSE2]>;
3162
3163 def : Pat<(v2i64 (X86vzmovl (loadv2i64 addr:$src))),
3164             (MOVZQI2PQIrm addr:$src)>;
3165 def : Pat<(v2i64 (X86vzmovl (bc_v2i64 (loadv4f32 addr:$src)))),
3166             (MOVZQI2PQIrm addr:$src)>;
3167 def : Pat<(v2i64 (X86vzload addr:$src)), (MOVZQI2PQIrm addr:$src)>;
3168 }
3169
3170 // Moving from XMM to XMM and clear upper 64 bits. Note, there is a bug in
3171 // IA32 document. movq xmm1, xmm2 does clear the high bits.
3172 let isAsmParserOnly = 1, AddedComplexity = 15 in
3173 def VMOVZPQILo2PQIrr : I<0x7E, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
3174                         "vmovq\t{$src, $dst|$dst, $src}",
3175                     [(set VR128:$dst, (v2i64 (X86vzmovl (v2i64 VR128:$src))))]>,
3176                       XS, VEX, Requires<[HasAVX]>;
3177 let AddedComplexity = 15 in
3178 def MOVZPQILo2PQIrr : I<0x7E, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
3179                         "movq\t{$src, $dst|$dst, $src}",
3180                     [(set VR128:$dst, (v2i64 (X86vzmovl (v2i64 VR128:$src))))]>,
3181                       XS, Requires<[HasSSE2]>;
3182
3183 let AddedComplexity = 20, isAsmParserOnly = 1 in
3184 def VMOVZPQILo2PQIrm : I<0x7E, MRMSrcMem, (outs VR128:$dst), (ins i128mem:$src),
3185                         "vmovq\t{$src, $dst|$dst, $src}",
3186                     [(set VR128:$dst, (v2i64 (X86vzmovl
3187                                              (loadv2i64 addr:$src))))]>,
3188                       XS, VEX, Requires<[HasAVX]>;
3189 let AddedComplexity = 20 in {
3190 def MOVZPQILo2PQIrm : I<0x7E, MRMSrcMem, (outs VR128:$dst), (ins i128mem:$src),
3191                         "movq\t{$src, $dst|$dst, $src}",
3192                     [(set VR128:$dst, (v2i64 (X86vzmovl
3193                                              (loadv2i64 addr:$src))))]>,
3194                       XS, Requires<[HasSSE2]>;
3195
3196 def : Pat<(v2i64 (X86vzmovl (bc_v2i64 (loadv4i32 addr:$src)))),
3197             (MOVZPQILo2PQIrm addr:$src)>;
3198 }
3199
3200 // Instructions to match in the assembler
3201 let isAsmParserOnly = 1 in {
3202 def VMOVQs64rr : VPDI<0x6E, MRMSrcReg, (outs VR128:$dst), (ins GR64:$src),
3203                       "movq\t{$src, $dst|$dst, $src}", []>, VEX, VEX_W;
3204 def VMOVQd64rr : VPDI<0x7E, MRMDestReg, (outs GR64:$dst), (ins VR128:$src),
3205                       "movq\t{$src, $dst|$dst, $src}", []>, VEX, VEX_W;
3206 // Recognize "movd" with GR64 destination, but encode as a "movq"
3207 def VMOVQd64rr_alt : VPDI<0x7E, MRMDestReg, (outs GR64:$dst), (ins VR128:$src),
3208                           "movd\t{$src, $dst|$dst, $src}", []>, VEX, VEX_W;
3209 }
3210
3211 // Instructions for the disassembler
3212 // xr = XMM register
3213 // xm = mem64
3214
3215 let isAsmParserOnly = 1, Predicates = [HasAVX] in
3216 def VMOVQxrxr: I<0x7E, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
3217                  "vmovq\t{$src, $dst|$dst, $src}", []>, VEX, XS;
3218 def MOVQxrxr : I<0x7E, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
3219                  "movq\t{$src, $dst|$dst, $src}", []>, XS;
3220
3221 //===---------------------------------------------------------------------===//
3222 // SSE2 - Misc Instructions
3223 //===---------------------------------------------------------------------===//
3224
3225 // Flush cache
3226 def CLFLUSH : I<0xAE, MRM7m, (outs), (ins i8mem:$src),
3227                "clflush\t$src", [(int_x86_sse2_clflush addr:$src)]>,
3228               TB, Requires<[HasSSE2]>;
3229
3230 // Load, store, and memory fence
3231 def LFENCE : I<0xAE, MRM_E8, (outs), (ins),
3232                "lfence", [(int_x86_sse2_lfence)]>, TB, Requires<[HasSSE2]>;
3233 def MFENCE : I<0xAE, MRM_F0, (outs), (ins),
3234                "mfence", [(int_x86_sse2_mfence)]>, TB, Requires<[HasSSE2]>;
3235 def : Pat<(X86LFence), (LFENCE)>;
3236 def : Pat<(X86MFence), (MFENCE)>;
3237
3238
3239 // Pause. This "instruction" is encoded as "rep; nop", so even though it
3240 // was introduced with SSE2, it's backward compatible.
3241 def PAUSE : I<0x90, RawFrm, (outs), (ins), "pause", []>, REP;
3242
3243 // Alias instructions that map zero vector to pxor / xorp* for sse.
3244 // We set canFoldAsLoad because this can be converted to a constant-pool
3245 // load of an all-ones value if folding it would be beneficial.
3246 let isReMaterializable = 1, isAsCheapAsAMove = 1, canFoldAsLoad = 1,
3247     isCodeGenOnly = 1, ExeDomain = SSEPackedInt in
3248   // FIXME: Change encoding to pseudo.
3249   def V_SETALLONES : PDI<0x76, MRMInitReg, (outs VR128:$dst), (ins), "",
3250                          [(set VR128:$dst, (v4i32 immAllOnesV))]>;
3251
3252 //===---------------------------------------------------------------------===//
3253 // SSE3 - Conversion Instructions
3254 //===---------------------------------------------------------------------===//
3255
3256 // Convert Packed Double FP to Packed DW Integers
3257 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
3258 // The assembler can recognize rr 256-bit instructions by seeing a ymm
3259 // register, but the same isn't true when using memory operands instead.
3260 // Provide other assembly rr and rm forms to address this explicitly.
3261 def VCVTPD2DQrr  : S3DI<0xE6, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
3262                        "vcvtpd2dq\t{$src, $dst|$dst, $src}", []>, VEX;
3263 def VCVTPD2DQXrYr  : S3DI<0xE6, MRMSrcReg, (outs VR128:$dst), (ins VR256:$src),
3264                        "vcvtpd2dq\t{$src, $dst|$dst, $src}", []>, VEX;
3265
3266 // XMM only
3267 def VCVTPD2DQXrr : S3DI<0xE6, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
3268                       "vcvtpd2dqx\t{$src, $dst|$dst, $src}", []>, VEX;
3269 def VCVTPD2DQXrm : S3DI<0xE6, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
3270                       "vcvtpd2dqx\t{$src, $dst|$dst, $src}", []>, VEX;
3271
3272 // YMM only
3273 def VCVTPD2DQYrr : S3DI<0xE6, MRMSrcReg, (outs VR128:$dst), (ins VR256:$src),
3274                       "vcvtpd2dqy\t{$src, $dst|$dst, $src}", []>, VEX;
3275 def VCVTPD2DQYrm : S3DI<0xE6, MRMSrcMem, (outs VR128:$dst), (ins f256mem:$src),
3276                       "vcvtpd2dqy\t{$src, $dst|$dst, $src}", []>, VEX, VEX_L;
3277 }
3278
3279 def CVTPD2DQrm  : S3DI<0xE6, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
3280                        "cvtpd2dq\t{$src, $dst|$dst, $src}", []>;
3281 def CVTPD2DQrr  : S3DI<0xE6, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
3282                        "cvtpd2dq\t{$src, $dst|$dst, $src}", []>;
3283
3284 // Convert Packed DW Integers to Packed Double FP
3285 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
3286 def VCVTDQ2PDrm  : S3SI<0xE6, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
3287                      "vcvtdq2pd\t{$src, $dst|$dst, $src}", []>, VEX;
3288 def VCVTDQ2PDrr  : S3SI<0xE6, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
3289                      "vcvtdq2pd\t{$src, $dst|$dst, $src}", []>, VEX;
3290 def VCVTDQ2PDYrm  : S3SI<0xE6, MRMSrcMem, (outs VR256:$dst), (ins f128mem:$src),
3291                      "vcvtdq2pd\t{$src, $dst|$dst, $src}", []>, VEX;
3292 def VCVTDQ2PDYrr  : S3SI<0xE6, MRMSrcReg, (outs VR256:$dst), (ins VR128:$src),
3293                      "vcvtdq2pd\t{$src, $dst|$dst, $src}", []>, VEX;
3294 }
3295
3296 def CVTDQ2PDrm  : S3SI<0xE6, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
3297                        "cvtdq2pd\t{$src, $dst|$dst, $src}", []>;
3298 def CVTDQ2PDrr  : S3SI<0xE6, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
3299                        "cvtdq2pd\t{$src, $dst|$dst, $src}", []>;
3300
3301 // AVX 256-bit register conversion intrinsics
3302 def : Pat<(int_x86_avx_cvtdq2_pd_256 VR128:$src),
3303            (VCVTDQ2PDYrr VR128:$src)>;
3304 def : Pat<(int_x86_avx_cvtdq2_pd_256 (memopv4i32 addr:$src)),
3305            (VCVTDQ2PDYrm addr:$src)>;
3306
3307 def : Pat<(int_x86_avx_cvt_pd2dq_256 VR256:$src),
3308           (VCVTPD2DQYrr VR256:$src)>;
3309 def : Pat<(int_x86_avx_cvt_pd2dq_256 (memopv4f64 addr:$src)),
3310           (VCVTPD2DQYrm addr:$src)>;
3311
3312 //===---------------------------------------------------------------------===//
3313 // SSE3 - Move Instructions
3314 //===---------------------------------------------------------------------===//
3315
3316 // Replicate Single FP
3317 multiclass sse3_replicate_sfp<bits<8> op, PatFrag rep_frag, string OpcodeStr> {
3318 def rr : S3SI<op, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
3319                     !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"),
3320                       [(set VR128:$dst, (v4f32 (rep_frag
3321                                                 VR128:$src, (undef))))]>;
3322 def rm : S3SI<op, MRMSrcMem, (outs VR128:$dst), (ins f128mem:$src),
3323                     !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"),
3324                       [(set VR128:$dst, (rep_frag
3325                                          (memopv4f32 addr:$src), (undef)))]>;
3326 }
3327
3328 multiclass sse3_replicate_sfp_y<bits<8> op, PatFrag rep_frag,
3329                                 string OpcodeStr> {
3330 def rr : S3SI<op, MRMSrcReg, (outs VR256:$dst), (ins VR256:$src),
3331               !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"), []>;
3332 def rm : S3SI<op, MRMSrcMem, (outs VR256:$dst), (ins f256mem:$src),
3333               !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"), []>;
3334 }
3335
3336 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
3337   // FIXME: Merge above classes when we have patterns for the ymm version
3338   defm VMOVSHDUP  : sse3_replicate_sfp<0x16, movshdup, "vmovshdup">, VEX;
3339   defm VMOVSLDUP  : sse3_replicate_sfp<0x12, movsldup, "vmovsldup">, VEX;
3340   defm VMOVSHDUPY : sse3_replicate_sfp_y<0x16, movshdup, "vmovshdup">, VEX;
3341   defm VMOVSLDUPY : sse3_replicate_sfp_y<0x12, movsldup, "vmovsldup">, VEX;
3342 }
3343 defm MOVSHDUP : sse3_replicate_sfp<0x16, movshdup, "movshdup">;
3344 defm MOVSLDUP : sse3_replicate_sfp<0x12, movsldup, "movsldup">;
3345
3346 // Replicate Double FP
3347 multiclass sse3_replicate_dfp<string OpcodeStr> {
3348 def rr  : S3DI<0x12, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
3349                     !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"),
3350                     [(set VR128:$dst,(v2f64 (movddup VR128:$src, (undef))))]>;
3351 def rm  : S3DI<0x12, MRMSrcMem, (outs VR128:$dst), (ins f64mem:$src),
3352                     !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"),
3353                     [(set VR128:$dst,
3354                       (v2f64 (movddup (scalar_to_vector (loadf64 addr:$src)),
3355                                       (undef))))]>;
3356 }
3357
3358 multiclass sse3_replicate_dfp_y<string OpcodeStr> {
3359 def rr  : S3DI<0x12, MRMSrcReg, (outs VR256:$dst), (ins VR256:$src),
3360                     !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"),
3361                     []>;
3362 def rm  : S3DI<0x12, MRMSrcMem, (outs VR256:$dst), (ins f256mem:$src),
3363                     !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"),
3364                     []>;
3365 }
3366
3367 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
3368   // FIXME: Merge above classes when we have patterns for the ymm version
3369   defm VMOVDDUP  : sse3_replicate_dfp<"vmovddup">, VEX;
3370   defm VMOVDDUPY : sse3_replicate_dfp_y<"vmovddup">, VEX;
3371 }
3372 defm MOVDDUP : sse3_replicate_dfp<"movddup">;
3373
3374 // Move Unaligned Integer
3375 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
3376   def VLDDQUrm : S3DI<0xF0, MRMSrcMem, (outs VR128:$dst), (ins i128mem:$src),
3377                    "vlddqu\t{$src, $dst|$dst, $src}",
3378                    [(set VR128:$dst, (int_x86_sse3_ldu_dq addr:$src))]>, VEX;
3379   def VLDDQUYrm : S3DI<0xF0, MRMSrcMem, (outs VR256:$dst), (ins i256mem:$src),
3380                    "vlddqu\t{$src, $dst|$dst, $src}",
3381                    [(set VR256:$dst, (int_x86_avx_ldu_dq_256 addr:$src))]>, VEX;
3382 }
3383 def LDDQUrm : S3DI<0xF0, MRMSrcMem, (outs VR128:$dst), (ins i128mem:$src),
3384                    "lddqu\t{$src, $dst|$dst, $src}",
3385                    [(set VR128:$dst, (int_x86_sse3_ldu_dq addr:$src))]>;
3386
3387 def : Pat<(movddup (bc_v2f64 (v2i64 (scalar_to_vector (loadi64 addr:$src)))),
3388                    (undef)),
3389           (MOVDDUPrm addr:$src)>, Requires<[HasSSE3]>;
3390
3391 // Several Move patterns
3392 let AddedComplexity = 5 in {
3393 def : Pat<(movddup (memopv2f64 addr:$src), (undef)),
3394           (MOVDDUPrm addr:$src)>, Requires<[HasSSE3]>;
3395 def : Pat<(movddup (bc_v4f32 (memopv2f64 addr:$src)), (undef)),
3396           (MOVDDUPrm addr:$src)>, Requires<[HasSSE3]>;
3397 def : Pat<(movddup (memopv2i64 addr:$src), (undef)),
3398           (MOVDDUPrm addr:$src)>, Requires<[HasSSE3]>;
3399 def : Pat<(movddup (bc_v4i32 (memopv2i64 addr:$src)), (undef)),
3400           (MOVDDUPrm addr:$src)>, Requires<[HasSSE3]>;
3401 }
3402
3403 // vector_shuffle v1, <undef> <1, 1, 3, 3>
3404 let AddedComplexity = 15 in
3405 def : Pat<(v4i32 (movshdup VR128:$src, (undef))),
3406           (MOVSHDUPrr VR128:$src)>, Requires<[HasSSE3]>;
3407 let AddedComplexity = 20 in
3408 def : Pat<(v4i32 (movshdup (bc_v4i32 (memopv2i64 addr:$src)), (undef))),
3409           (MOVSHDUPrm addr:$src)>, Requires<[HasSSE3]>;
3410
3411 // vector_shuffle v1, <undef> <0, 0, 2, 2>
3412 let AddedComplexity = 15 in
3413   def : Pat<(v4i32 (movsldup VR128:$src, (undef))),
3414             (MOVSLDUPrr VR128:$src)>, Requires<[HasSSE3]>;
3415 let AddedComplexity = 20 in
3416   def : Pat<(v4i32 (movsldup (bc_v4i32 (memopv2i64 addr:$src)), (undef))),
3417             (MOVSLDUPrm addr:$src)>, Requires<[HasSSE3]>;
3418
3419 //===---------------------------------------------------------------------===//
3420 // SSE3 - Arithmetic
3421 //===---------------------------------------------------------------------===//
3422
3423 multiclass sse3_addsub<Intrinsic Int, string OpcodeStr, RegisterClass RC,
3424                        X86MemOperand x86memop, bit Is2Addr = 1> {
3425   def rr : I<0xD0, MRMSrcReg,
3426        (outs RC:$dst), (ins RC:$src1, RC:$src2),
3427        !if(Is2Addr,
3428            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
3429            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
3430        [(set RC:$dst, (Int RC:$src1, RC:$src2))]>;
3431   def rm : I<0xD0, MRMSrcMem,
3432        (outs RC:$dst), (ins RC:$src1, x86memop:$src2),
3433        !if(Is2Addr,
3434            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
3435            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
3436        [(set RC:$dst, (Int RC:$src1, (memop addr:$src2)))]>;
3437 }
3438
3439 let isAsmParserOnly = 1, Predicates = [HasAVX],
3440   ExeDomain = SSEPackedDouble in {
3441   defm VADDSUBPS : sse3_addsub<int_x86_sse3_addsub_ps, "vaddsubps", VR128,
3442                                f128mem, 0>, XD, VEX_4V;
3443   defm VADDSUBPD : sse3_addsub<int_x86_sse3_addsub_pd, "vaddsubpd", VR128,
3444                                f128mem, 0>, OpSize, VEX_4V;
3445   defm VADDSUBPSY : sse3_addsub<int_x86_avx_addsub_ps_256, "vaddsubps", VR256,
3446                                f256mem, 0>, XD, VEX_4V;
3447   defm VADDSUBPDY : sse3_addsub<int_x86_avx_addsub_pd_256, "vaddsubpd", VR256,
3448                                f256mem, 0>, OpSize, VEX_4V;
3449 }
3450 let Constraints = "$src1 = $dst", Predicates = [HasSSE3],
3451     ExeDomain = SSEPackedDouble in {
3452   defm ADDSUBPS : sse3_addsub<int_x86_sse3_addsub_ps, "addsubps", VR128,
3453                               f128mem>, XD;
3454   defm ADDSUBPD : sse3_addsub<int_x86_sse3_addsub_pd, "addsubpd", VR128,
3455                               f128mem>, TB, OpSize;
3456 }
3457
3458 //===---------------------------------------------------------------------===//
3459 // SSE3 Instructions
3460 //===---------------------------------------------------------------------===//
3461
3462 // Horizontal ops
3463 multiclass S3D_Int<bits<8> o, string OpcodeStr, ValueType vt, RegisterClass RC,
3464                    X86MemOperand x86memop, Intrinsic IntId, bit Is2Addr = 1> {
3465   def rr : S3DI<o, MRMSrcReg, (outs RC:$dst), (ins RC:$src1, RC:$src2),
3466        !if(Is2Addr,
3467          !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
3468          !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
3469       [(set RC:$dst, (vt (IntId RC:$src1, RC:$src2)))]>;
3470
3471   def rm : S3DI<o, MRMSrcMem, (outs RC:$dst), (ins RC:$src1, x86memop:$src2),
3472        !if(Is2Addr,
3473          !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
3474          !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
3475       [(set RC:$dst, (vt (IntId RC:$src1, (memop addr:$src2))))]>;
3476 }
3477 multiclass S3_Int<bits<8> o, string OpcodeStr, ValueType vt, RegisterClass RC,
3478                   X86MemOperand x86memop, Intrinsic IntId, bit Is2Addr = 1> {
3479   def rr : S3I<o, MRMSrcReg, (outs RC:$dst), (ins RC:$src1, RC:$src2),
3480        !if(Is2Addr,
3481          !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
3482          !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
3483       [(set RC:$dst, (vt (IntId RC:$src1, RC:$src2)))]>;
3484
3485   def rm : S3I<o, MRMSrcMem, (outs RC:$dst), (ins RC:$src1, x86memop:$src2),
3486        !if(Is2Addr,
3487          !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
3488          !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
3489       [(set RC:$dst, (vt (IntId RC:$src1, (memop addr:$src2))))]>;
3490 }
3491
3492 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
3493   defm VHADDPS  : S3D_Int<0x7C, "vhaddps", v4f32, VR128, f128mem,
3494                           int_x86_sse3_hadd_ps, 0>, VEX_4V;
3495   defm VHADDPD  : S3_Int <0x7C, "vhaddpd", v2f64, VR128, f128mem,
3496                           int_x86_sse3_hadd_pd, 0>, VEX_4V;
3497   defm VHSUBPS  : S3D_Int<0x7D, "vhsubps", v4f32, VR128, f128mem,
3498                           int_x86_sse3_hsub_ps, 0>, VEX_4V;
3499   defm VHSUBPD  : S3_Int <0x7D, "vhsubpd", v2f64, VR128, f128mem,
3500                           int_x86_sse3_hsub_pd, 0>, VEX_4V;
3501   defm VHADDPSY : S3D_Int<0x7C, "vhaddps", v8f32, VR256, f256mem,
3502                           int_x86_avx_hadd_ps_256, 0>, VEX_4V;
3503   defm VHADDPDY : S3_Int <0x7C, "vhaddpd", v4f64, VR256, f256mem,
3504                           int_x86_avx_hadd_pd_256, 0>, VEX_4V;
3505   defm VHSUBPSY : S3D_Int<0x7D, "vhsubps", v8f32, VR256, f256mem,
3506                           int_x86_avx_hsub_ps_256, 0>, VEX_4V;
3507   defm VHSUBPDY : S3_Int <0x7D, "vhsubpd", v4f64, VR256, f256mem,
3508                           int_x86_avx_hsub_pd_256, 0>, VEX_4V;
3509 }
3510
3511 let Constraints = "$src1 = $dst" in {
3512   defm HADDPS : S3D_Int<0x7C, "haddps", v4f32, VR128, f128mem,
3513                         int_x86_sse3_hadd_ps>;
3514   defm HADDPD : S3_Int<0x7C, "haddpd", v2f64, VR128, f128mem,
3515                        int_x86_sse3_hadd_pd>;
3516   defm HSUBPS : S3D_Int<0x7D, "hsubps", v4f32, VR128, f128mem,
3517                         int_x86_sse3_hsub_ps>;
3518   defm HSUBPD : S3_Int<0x7D, "hsubpd", v2f64, VR128, f128mem,
3519                        int_x86_sse3_hsub_pd>;
3520 }
3521
3522 //===---------------------------------------------------------------------===//
3523 // SSSE3 - Packed Absolute Instructions
3524 //===---------------------------------------------------------------------===//
3525
3526 /// SS3I_unop_rm_int - Simple SSSE3 unary op whose type can be v*{i8,i16,i32}.
3527 multiclass SS3I_unop_rm_int<bits<8> opc, string OpcodeStr,
3528                             PatFrag mem_frag64, PatFrag mem_frag128,
3529                             Intrinsic IntId64, Intrinsic IntId128> {
3530   def rr64 : SS38I<opc, MRMSrcReg, (outs VR64:$dst), (ins VR64:$src),
3531                    !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"),
3532                    [(set VR64:$dst, (IntId64 VR64:$src))]>;
3533
3534   def rm64 : SS38I<opc, MRMSrcMem, (outs VR64:$dst), (ins i64mem:$src),
3535                    !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"),
3536                    [(set VR64:$dst,
3537                      (IntId64 (bitconvert (mem_frag64 addr:$src))))]>;
3538
3539   def rr128 : SS38I<opc, MRMSrcReg, (outs VR128:$dst),
3540                     (ins VR128:$src),
3541                     !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"),
3542                     [(set VR128:$dst, (IntId128 VR128:$src))]>,
3543                     OpSize;
3544
3545   def rm128 : SS38I<opc, MRMSrcMem, (outs VR128:$dst),
3546                     (ins i128mem:$src),
3547                     !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"),
3548                     [(set VR128:$dst,
3549                       (IntId128
3550                        (bitconvert (mem_frag128 addr:$src))))]>, OpSize;
3551 }
3552
3553 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
3554   defm VPABSB  : SS3I_unop_rm_int<0x1C, "vpabsb", memopv8i8, memopv16i8,
3555                                   int_x86_ssse3_pabs_b,
3556                                   int_x86_ssse3_pabs_b_128>, VEX;
3557   defm VPABSW  : SS3I_unop_rm_int<0x1D, "vpabsw", memopv4i16, memopv8i16,
3558                                   int_x86_ssse3_pabs_w,
3559                                   int_x86_ssse3_pabs_w_128>, VEX;
3560   defm VPABSD  : SS3I_unop_rm_int<0x1E, "vpabsd", memopv2i32, memopv4i32,
3561                                   int_x86_ssse3_pabs_d,
3562                                   int_x86_ssse3_pabs_d_128>, VEX;
3563 }
3564
3565 defm PABSB       : SS3I_unop_rm_int<0x1C, "pabsb", memopv8i8, memopv16i8,
3566                                     int_x86_ssse3_pabs_b,
3567                                     int_x86_ssse3_pabs_b_128>;
3568 defm PABSW       : SS3I_unop_rm_int<0x1D, "pabsw", memopv4i16, memopv8i16,
3569                                     int_x86_ssse3_pabs_w,
3570                                     int_x86_ssse3_pabs_w_128>;
3571 defm PABSD       : SS3I_unop_rm_int<0x1E, "pabsd", memopv2i32, memopv4i32,
3572                                     int_x86_ssse3_pabs_d,
3573                                     int_x86_ssse3_pabs_d_128>;
3574
3575 //===---------------------------------------------------------------------===//
3576 // SSSE3 - Packed Binary Operator Instructions
3577 //===---------------------------------------------------------------------===//
3578
3579 /// SS3I_binop_rm_int - Simple SSSE3 bin op whose type can be v*{i8,i16,i32}.
3580 multiclass SS3I_binop_rm_int<bits<8> opc, string OpcodeStr,
3581                              PatFrag mem_frag64, PatFrag mem_frag128,
3582                              Intrinsic IntId64, Intrinsic IntId128,
3583                              bit Is2Addr = 1> {
3584   let isCommutable = 1 in
3585   def rr64 : SS38I<opc, MRMSrcReg, (outs VR64:$dst),
3586        (ins VR64:$src1, VR64:$src2),
3587        !if(Is2Addr,
3588          !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
3589          !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
3590        [(set VR64:$dst, (IntId64 VR64:$src1, VR64:$src2))]>;
3591   def rm64 : SS38I<opc, MRMSrcMem, (outs VR64:$dst),
3592        (ins VR64:$src1, i64mem:$src2),
3593        !if(Is2Addr,
3594          !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
3595          !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
3596        [(set VR64:$dst,
3597          (IntId64 VR64:$src1,
3598           (bitconvert (memopv8i8 addr:$src2))))]>;
3599
3600   let isCommutable = 1 in
3601   def rr128 : SS38I<opc, MRMSrcReg, (outs VR128:$dst),
3602        (ins VR128:$src1, VR128:$src2),
3603        !if(Is2Addr,
3604          !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
3605          !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
3606        [(set VR128:$dst, (IntId128 VR128:$src1, VR128:$src2))]>,
3607        OpSize;
3608   def rm128 : SS38I<opc, MRMSrcMem, (outs VR128:$dst),
3609        (ins VR128:$src1, i128mem:$src2),
3610        !if(Is2Addr,
3611          !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
3612          !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
3613        [(set VR128:$dst,
3614          (IntId128 VR128:$src1,
3615           (bitconvert (memopv16i8 addr:$src2))))]>, OpSize;
3616 }
3617
3618 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
3619 let isCommutable = 0 in {
3620   defm VPHADDW    : SS3I_binop_rm_int<0x01, "vphaddw", memopv4i16, memopv8i16,
3621                                       int_x86_ssse3_phadd_w,
3622                                       int_x86_ssse3_phadd_w_128, 0>, VEX_4V;
3623   defm VPHADDD    : SS3I_binop_rm_int<0x02, "vphaddd", memopv2i32, memopv4i32,
3624                                       int_x86_ssse3_phadd_d,
3625                                       int_x86_ssse3_phadd_d_128, 0>, VEX_4V;
3626   defm VPHADDSW   : SS3I_binop_rm_int<0x03, "vphaddsw", memopv4i16, memopv8i16,
3627                                       int_x86_ssse3_phadd_sw,
3628                                       int_x86_ssse3_phadd_sw_128, 0>, VEX_4V;
3629   defm VPHSUBW    : SS3I_binop_rm_int<0x05, "vphsubw", memopv4i16, memopv8i16,
3630                                       int_x86_ssse3_phsub_w,
3631                                       int_x86_ssse3_phsub_w_128, 0>, VEX_4V;
3632   defm VPHSUBD    : SS3I_binop_rm_int<0x06, "vphsubd", memopv2i32, memopv4i32,
3633                                       int_x86_ssse3_phsub_d,
3634                                       int_x86_ssse3_phsub_d_128, 0>, VEX_4V;
3635   defm VPHSUBSW   : SS3I_binop_rm_int<0x07, "vphsubsw", memopv4i16, memopv8i16,
3636                                       int_x86_ssse3_phsub_sw,
3637                                       int_x86_ssse3_phsub_sw_128, 0>, VEX_4V;
3638   defm VPMADDUBSW : SS3I_binop_rm_int<0x04, "vpmaddubsw", memopv8i8, memopv16i8,
3639                                       int_x86_ssse3_pmadd_ub_sw,
3640                                       int_x86_ssse3_pmadd_ub_sw_128, 0>, VEX_4V;
3641   defm VPSHUFB    : SS3I_binop_rm_int<0x00, "vpshufb", memopv8i8, memopv16i8,
3642                                       int_x86_ssse3_pshuf_b,
3643                                       int_x86_ssse3_pshuf_b_128, 0>, VEX_4V;
3644   defm VPSIGNB    : SS3I_binop_rm_int<0x08, "vpsignb", memopv8i8, memopv16i8,
3645                                       int_x86_ssse3_psign_b,
3646                                       int_x86_ssse3_psign_b_128, 0>, VEX_4V;
3647   defm VPSIGNW    : SS3I_binop_rm_int<0x09, "vpsignw", memopv4i16, memopv8i16,
3648                                       int_x86_ssse3_psign_w,
3649                                       int_x86_ssse3_psign_w_128, 0>, VEX_4V;
3650   defm VPSIGND    : SS3I_binop_rm_int<0x0A, "vpsignd", memopv2i32, memopv4i32,
3651                                       int_x86_ssse3_psign_d,
3652                                       int_x86_ssse3_psign_d_128, 0>, VEX_4V;
3653 }
3654 defm VPMULHRSW    : SS3I_binop_rm_int<0x0B, "vpmulhrsw", memopv4i16, memopv8i16,
3655                                       int_x86_ssse3_pmul_hr_sw,
3656                                       int_x86_ssse3_pmul_hr_sw_128, 0>, VEX_4V;
3657 }
3658
3659 // None of these have i8 immediate fields.
3660 let ImmT = NoImm, Constraints = "$src1 = $dst" in {
3661 let isCommutable = 0 in {
3662   defm PHADDW    : SS3I_binop_rm_int<0x01, "phaddw", memopv4i16, memopv8i16,
3663                                      int_x86_ssse3_phadd_w,
3664                                      int_x86_ssse3_phadd_w_128>;
3665   defm PHADDD    : SS3I_binop_rm_int<0x02, "phaddd", memopv2i32, memopv4i32,
3666                                      int_x86_ssse3_phadd_d,
3667                                      int_x86_ssse3_phadd_d_128>;
3668   defm PHADDSW   : SS3I_binop_rm_int<0x03, "phaddsw", memopv4i16, memopv8i16,
3669                                      int_x86_ssse3_phadd_sw,
3670                                      int_x86_ssse3_phadd_sw_128>;
3671   defm PHSUBW    : SS3I_binop_rm_int<0x05, "phsubw", memopv4i16, memopv8i16,
3672                                      int_x86_ssse3_phsub_w,
3673                                      int_x86_ssse3_phsub_w_128>;
3674   defm PHSUBD    : SS3I_binop_rm_int<0x06, "phsubd", memopv2i32, memopv4i32,
3675                                      int_x86_ssse3_phsub_d,
3676                                      int_x86_ssse3_phsub_d_128>;
3677   defm PHSUBSW   : SS3I_binop_rm_int<0x07, "phsubsw", memopv4i16, memopv8i16,
3678                                      int_x86_ssse3_phsub_sw,
3679                                      int_x86_ssse3_phsub_sw_128>;
3680   defm PMADDUBSW : SS3I_binop_rm_int<0x04, "pmaddubsw", memopv8i8, memopv16i8,
3681                                      int_x86_ssse3_pmadd_ub_sw,
3682                                      int_x86_ssse3_pmadd_ub_sw_128>;
3683   defm PSHUFB    : SS3I_binop_rm_int<0x00, "pshufb", memopv8i8, memopv16i8,
3684                                      int_x86_ssse3_pshuf_b,
3685                                      int_x86_ssse3_pshuf_b_128>;
3686   defm PSIGNB    : SS3I_binop_rm_int<0x08, "psignb", memopv8i8, memopv16i8,
3687                                      int_x86_ssse3_psign_b,
3688                                      int_x86_ssse3_psign_b_128>;
3689   defm PSIGNW    : SS3I_binop_rm_int<0x09, "psignw", memopv4i16, memopv8i16,
3690                                      int_x86_ssse3_psign_w,
3691                                      int_x86_ssse3_psign_w_128>;
3692   defm PSIGND    : SS3I_binop_rm_int<0x0A, "psignd", memopv2i32, memopv4i32,
3693                                        int_x86_ssse3_psign_d,
3694                                        int_x86_ssse3_psign_d_128>;
3695 }
3696 defm PMULHRSW    : SS3I_binop_rm_int<0x0B, "pmulhrsw", memopv4i16, memopv8i16,
3697                                      int_x86_ssse3_pmul_hr_sw,
3698                                      int_x86_ssse3_pmul_hr_sw_128>;
3699 }
3700
3701 def : Pat<(X86pshufb VR128:$src, VR128:$mask),
3702           (PSHUFBrr128 VR128:$src, VR128:$mask)>, Requires<[HasSSSE3]>;
3703 def : Pat<(X86pshufb VR128:$src, (bc_v16i8 (memopv2i64 addr:$mask))),
3704           (PSHUFBrm128 VR128:$src, addr:$mask)>, Requires<[HasSSSE3]>;
3705
3706 //===---------------------------------------------------------------------===//
3707 // SSSE3 - Packed Align Instruction Patterns
3708 //===---------------------------------------------------------------------===//
3709
3710 multiclass sse3_palign<string asm, bit Is2Addr = 1> {
3711   def R64rr  : SS3AI<0x0F, MRMSrcReg, (outs VR64:$dst),
3712       (ins VR64:$src1, VR64:$src2, i8imm:$src3),
3713       !if(Is2Addr,
3714         !strconcat(asm, "\t{$src3, $src2, $dst|$dst, $src2, $src3}"),
3715         !strconcat(asm,
3716                   "\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}")),
3717       []>;
3718   def R64rm  : SS3AI<0x0F, MRMSrcMem, (outs VR64:$dst),
3719       (ins VR64:$src1, i64mem:$src2, i8imm:$src3),
3720       !if(Is2Addr,
3721         !strconcat(asm, "\t{$src3, $src2, $dst|$dst, $src2, $src3}"),
3722         !strconcat(asm,
3723                   "\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}")),
3724       []>;
3725
3726   def R128rr : SS3AI<0x0F, MRMSrcReg, (outs VR128:$dst),
3727       (ins VR128:$src1, VR128:$src2, i8imm:$src3),
3728       !if(Is2Addr,
3729         !strconcat(asm, "\t{$src3, $src2, $dst|$dst, $src2, $src3}"),
3730         !strconcat(asm,
3731                   "\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}")),
3732       []>, OpSize;
3733   def R128rm : SS3AI<0x0F, MRMSrcMem, (outs VR128:$dst),
3734       (ins VR128:$src1, i128mem:$src2, i8imm:$src3),
3735       !if(Is2Addr,
3736         !strconcat(asm, "\t{$src3, $src2, $dst|$dst, $src2, $src3}"),
3737         !strconcat(asm,
3738                   "\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}")),
3739       []>, OpSize;
3740 }
3741
3742 let isAsmParserOnly = 1, Predicates = [HasAVX] in
3743   defm VPALIGN : sse3_palign<"vpalignr", 0>, VEX_4V;
3744 let Constraints = "$src1 = $dst" in
3745   defm PALIGN : sse3_palign<"palignr">;
3746
3747 let AddedComplexity = 5 in {
3748
3749 def : Pat<(v1i64 (palign:$src3 VR64:$src1, VR64:$src2)),
3750           (PALIGNR64rr VR64:$src2, VR64:$src1,
3751                        (SHUFFLE_get_palign_imm VR64:$src3))>,
3752           Requires<[HasSSSE3]>;
3753 def : Pat<(v2i32 (palign:$src3 VR64:$src1, VR64:$src2)),
3754           (PALIGNR64rr VR64:$src2, VR64:$src1,
3755                        (SHUFFLE_get_palign_imm VR64:$src3))>,
3756           Requires<[HasSSSE3]>;
3757 def : Pat<(v4i16 (palign:$src3 VR64:$src1, VR64:$src2)),
3758           (PALIGNR64rr VR64:$src2, VR64:$src1,
3759                        (SHUFFLE_get_palign_imm VR64:$src3))>,
3760           Requires<[HasSSSE3]>;
3761 def : Pat<(v8i8 (palign:$src3 VR64:$src1, VR64:$src2)),
3762           (PALIGNR64rr VR64:$src2, VR64:$src1,
3763                        (SHUFFLE_get_palign_imm VR64:$src3))>,
3764           Requires<[HasSSSE3]>;
3765
3766 def : Pat<(v4i32 (palign:$src3 VR128:$src1, VR128:$src2)),
3767           (PALIGNR128rr VR128:$src2, VR128:$src1,
3768                         (SHUFFLE_get_palign_imm VR128:$src3))>,
3769       Requires<[HasSSSE3]>;
3770 def : Pat<(v4f32 (palign:$src3 VR128:$src1, VR128:$src2)),
3771           (PALIGNR128rr VR128:$src2, VR128:$src1,
3772                         (SHUFFLE_get_palign_imm VR128:$src3))>,
3773       Requires<[HasSSSE3]>;
3774 def : Pat<(v8i16 (palign:$src3 VR128:$src1, VR128:$src2)),
3775           (PALIGNR128rr VR128:$src2, VR128:$src1,
3776                         (SHUFFLE_get_palign_imm VR128:$src3))>,
3777       Requires<[HasSSSE3]>;
3778 def : Pat<(v16i8 (palign:$src3 VR128:$src1, VR128:$src2)),
3779           (PALIGNR128rr VR128:$src2, VR128:$src1,
3780                         (SHUFFLE_get_palign_imm VR128:$src3))>,
3781       Requires<[HasSSSE3]>;
3782 }
3783
3784 //===---------------------------------------------------------------------===//
3785 // SSSE3 Misc Instructions
3786 //===---------------------------------------------------------------------===//
3787
3788 // Thread synchronization
3789 def MONITOR : I<0x01, MRM_C8, (outs), (ins), "monitor",
3790                 [(int_x86_sse3_monitor EAX, ECX, EDX)]>,TB, Requires<[HasSSE3]>;
3791 def MWAIT   : I<0x01, MRM_C9, (outs), (ins), "mwait",
3792                 [(int_x86_sse3_mwait ECX, EAX)]>, TB, Requires<[HasSSE3]>;
3793
3794 //===---------------------------------------------------------------------===//
3795 // Non-Instruction Patterns
3796 //===---------------------------------------------------------------------===//
3797
3798 // extload f32 -> f64.  This matches load+fextend because we have a hack in
3799 // the isel (PreprocessForFPConvert) that can introduce loads after dag
3800 // combine.
3801 // Since these loads aren't folded into the fextend, we have to match it
3802 // explicitly here.
3803 let Predicates = [HasSSE2] in
3804  def : Pat<(fextend (loadf32 addr:$src)),
3805            (CVTSS2SDrm addr:$src)>;
3806
3807 // bit_convert
3808 let Predicates = [HasSSE2] in {
3809   def : Pat<(v2i64 (bitconvert (v4i32 VR128:$src))), (v2i64 VR128:$src)>;
3810   def : Pat<(v2i64 (bitconvert (v8i16 VR128:$src))), (v2i64 VR128:$src)>;
3811   def : Pat<(v2i64 (bitconvert (v16i8 VR128:$src))), (v2i64 VR128:$src)>;
3812   def : Pat<(v2i64 (bitconvert (v2f64 VR128:$src))), (v2i64 VR128:$src)>;
3813   def : Pat<(v2i64 (bitconvert (v4f32 VR128:$src))), (v2i64 VR128:$src)>;
3814   def : Pat<(v4i32 (bitconvert (v2i64 VR128:$src))), (v4i32 VR128:$src)>;
3815   def : Pat<(v4i32 (bitconvert (v8i16 VR128:$src))), (v4i32 VR128:$src)>;
3816   def : Pat<(v4i32 (bitconvert (v16i8 VR128:$src))), (v4i32 VR128:$src)>;
3817   def : Pat<(v4i32 (bitconvert (v2f64 VR128:$src))), (v4i32 VR128:$src)>;
3818   def : Pat<(v4i32 (bitconvert (v4f32 VR128:$src))), (v4i32 VR128:$src)>;
3819   def : Pat<(v8i16 (bitconvert (v2i64 VR128:$src))), (v8i16 VR128:$src)>;
3820   def : Pat<(v8i16 (bitconvert (v4i32 VR128:$src))), (v8i16 VR128:$src)>;
3821   def : Pat<(v8i16 (bitconvert (v16i8 VR128:$src))), (v8i16 VR128:$src)>;
3822   def : Pat<(v8i16 (bitconvert (v2f64 VR128:$src))), (v8i16 VR128:$src)>;
3823   def : Pat<(v8i16 (bitconvert (v4f32 VR128:$src))), (v8i16 VR128:$src)>;
3824   def : Pat<(v16i8 (bitconvert (v2i64 VR128:$src))), (v16i8 VR128:$src)>;
3825   def : Pat<(v16i8 (bitconvert (v4i32 VR128:$src))), (v16i8 VR128:$src)>;
3826   def : Pat<(v16i8 (bitconvert (v8i16 VR128:$src))), (v16i8 VR128:$src)>;
3827   def : Pat<(v16i8 (bitconvert (v2f64 VR128:$src))), (v16i8 VR128:$src)>;
3828   def : Pat<(v16i8 (bitconvert (v4f32 VR128:$src))), (v16i8 VR128:$src)>;
3829   def : Pat<(v4f32 (bitconvert (v2i64 VR128:$src))), (v4f32 VR128:$src)>;
3830   def : Pat<(v4f32 (bitconvert (v4i32 VR128:$src))), (v4f32 VR128:$src)>;
3831   def : Pat<(v4f32 (bitconvert (v8i16 VR128:$src))), (v4f32 VR128:$src)>;
3832   def : Pat<(v4f32 (bitconvert (v16i8 VR128:$src))), (v4f32 VR128:$src)>;
3833   def : Pat<(v4f32 (bitconvert (v2f64 VR128:$src))), (v4f32 VR128:$src)>;
3834   def : Pat<(v2f64 (bitconvert (v2i64 VR128:$src))), (v2f64 VR128:$src)>;
3835   def : Pat<(v2f64 (bitconvert (v4i32 VR128:$src))), (v2f64 VR128:$src)>;
3836   def : Pat<(v2f64 (bitconvert (v8i16 VR128:$src))), (v2f64 VR128:$src)>;
3837   def : Pat<(v2f64 (bitconvert (v16i8 VR128:$src))), (v2f64 VR128:$src)>;
3838   def : Pat<(v2f64 (bitconvert (v4f32 VR128:$src))), (v2f64 VR128:$src)>;
3839 }
3840
3841 // Move scalar to XMM zero-extended
3842 // movd to XMM register zero-extends
3843 let AddedComplexity = 15 in {
3844 // Zeroing a VR128 then do a MOVS{S|D} to the lower bits.
3845 def : Pat<(v2f64 (X86vzmovl (v2f64 (scalar_to_vector FR64:$src)))),
3846           (MOVSDrr (v2f64 (V_SET0PS)), FR64:$src)>;
3847 def : Pat<(v4f32 (X86vzmovl (v4f32 (scalar_to_vector FR32:$src)))),
3848           (MOVSSrr (v4f32 (V_SET0PS)), FR32:$src)>;
3849 def : Pat<(v4f32 (X86vzmovl (v4f32 VR128:$src))),
3850           (MOVSSrr (v4f32 (V_SET0PS)),
3851                    (f32 (EXTRACT_SUBREG (v4f32 VR128:$src), sub_ss)))>;
3852 def : Pat<(v4i32 (X86vzmovl (v4i32 VR128:$src))),
3853           (MOVSSrr (v4i32 (V_SET0PI)),
3854                    (EXTRACT_SUBREG (v4i32 VR128:$src), sub_ss))>;
3855 }
3856
3857 // Splat v2f64 / v2i64
3858 let AddedComplexity = 10 in {
3859 def : Pat<(splat_lo (v2f64 VR128:$src), (undef)),
3860           (UNPCKLPDrr VR128:$src, VR128:$src)>,   Requires<[HasSSE2]>;
3861 def : Pat<(unpckh (v2f64 VR128:$src), (undef)),
3862           (UNPCKHPDrr VR128:$src, VR128:$src)>,   Requires<[HasSSE2]>;
3863 def : Pat<(splat_lo (v2i64 VR128:$src), (undef)),
3864           (PUNPCKLQDQrr VR128:$src, VR128:$src)>, Requires<[HasSSE2]>;
3865 def : Pat<(unpckh (v2i64 VR128:$src), (undef)),
3866           (PUNPCKHQDQrr VR128:$src, VR128:$src)>, Requires<[HasSSE2]>;
3867 }
3868
3869 // Special unary SHUFPSrri case.
3870 def : Pat<(v4f32 (pshufd:$src3 VR128:$src1, (undef))),
3871           (SHUFPSrri VR128:$src1, VR128:$src1,
3872                      (SHUFFLE_get_shuf_imm VR128:$src3))>;
3873 let AddedComplexity = 5 in
3874 def : Pat<(v4f32 (pshufd:$src2 VR128:$src1, (undef))),
3875           (PSHUFDri VR128:$src1, (SHUFFLE_get_shuf_imm VR128:$src2))>,
3876       Requires<[HasSSE2]>;
3877 // Special unary SHUFPDrri case.
3878 def : Pat<(v2i64 (pshufd:$src3 VR128:$src1, (undef))),
3879           (SHUFPDrri VR128:$src1, VR128:$src1,
3880                      (SHUFFLE_get_shuf_imm VR128:$src3))>,
3881       Requires<[HasSSE2]>;
3882 // Special unary SHUFPDrri case.
3883 def : Pat<(v2f64 (pshufd:$src3 VR128:$src1, (undef))),
3884           (SHUFPDrri VR128:$src1, VR128:$src1,
3885                      (SHUFFLE_get_shuf_imm VR128:$src3))>,
3886       Requires<[HasSSE2]>;
3887 // Unary v4f32 shuffle with PSHUF* in order to fold a load.
3888 def : Pat<(pshufd:$src2 (bc_v4i32 (memopv4f32 addr:$src1)), (undef)),
3889           (PSHUFDmi addr:$src1, (SHUFFLE_get_shuf_imm VR128:$src2))>,
3890       Requires<[HasSSE2]>;
3891
3892 // Special binary v4i32 shuffle cases with SHUFPS.
3893 def : Pat<(v4i32 (shufp:$src3 VR128:$src1, (v4i32 VR128:$src2))),
3894           (SHUFPSrri VR128:$src1, VR128:$src2,
3895                      (SHUFFLE_get_shuf_imm VR128:$src3))>,
3896            Requires<[HasSSE2]>;
3897 def : Pat<(v4i32 (shufp:$src3 VR128:$src1, (bc_v4i32 (memopv2i64 addr:$src2)))),
3898           (SHUFPSrmi VR128:$src1, addr:$src2,
3899                     (SHUFFLE_get_shuf_imm VR128:$src3))>,
3900            Requires<[HasSSE2]>;
3901 // Special binary v2i64 shuffle cases using SHUFPDrri.
3902 def : Pat<(v2i64 (shufp:$src3 VR128:$src1, VR128:$src2)),
3903           (SHUFPDrri VR128:$src1, VR128:$src2,
3904                      (SHUFFLE_get_shuf_imm VR128:$src3))>,
3905           Requires<[HasSSE2]>;
3906
3907 // vector_shuffle v1, <undef>, <0, 0, 1, 1, ...>
3908 let AddedComplexity = 15 in {
3909 def : Pat<(v4i32 (unpckl_undef:$src2 VR128:$src, (undef))),
3910           (PSHUFDri VR128:$src, (SHUFFLE_get_shuf_imm VR128:$src2))>,
3911           Requires<[OptForSpeed, HasSSE2]>;
3912 def : Pat<(v4f32 (unpckl_undef:$src2 VR128:$src, (undef))),
3913           (PSHUFDri VR128:$src, (SHUFFLE_get_shuf_imm VR128:$src2))>,
3914           Requires<[OptForSpeed, HasSSE2]>;
3915 }
3916 let AddedComplexity = 10 in {
3917 def : Pat<(v4f32 (unpckl_undef VR128:$src, (undef))),
3918           (UNPCKLPSrr VR128:$src, VR128:$src)>;
3919 def : Pat<(v16i8 (unpckl_undef VR128:$src, (undef))),
3920           (PUNPCKLBWrr VR128:$src, VR128:$src)>;
3921 def : Pat<(v8i16 (unpckl_undef VR128:$src, (undef))),
3922           (PUNPCKLWDrr VR128:$src, VR128:$src)>;
3923 def : Pat<(v4i32 (unpckl_undef VR128:$src, (undef))),
3924           (PUNPCKLDQrr VR128:$src, VR128:$src)>;
3925 }
3926
3927 // vector_shuffle v1, <undef>, <2, 2, 3, 3, ...>
3928 let AddedComplexity = 15 in {
3929 def : Pat<(v4i32 (unpckh_undef:$src2 VR128:$src, (undef))),
3930           (PSHUFDri VR128:$src, (SHUFFLE_get_shuf_imm VR128:$src2))>,
3931           Requires<[OptForSpeed, HasSSE2]>;
3932 def : Pat<(v4f32 (unpckh_undef:$src2 VR128:$src, (undef))),
3933           (PSHUFDri VR128:$src, (SHUFFLE_get_shuf_imm VR128:$src2))>,
3934           Requires<[OptForSpeed, HasSSE2]>;
3935 }
3936 let AddedComplexity = 10 in {
3937 def : Pat<(v4f32 (unpckh_undef VR128:$src, (undef))),
3938           (UNPCKHPSrr VR128:$src, VR128:$src)>;
3939 def : Pat<(v16i8 (unpckh_undef VR128:$src, (undef))),
3940           (PUNPCKHBWrr VR128:$src, VR128:$src)>;
3941 def : Pat<(v8i16 (unpckh_undef VR128:$src, (undef))),
3942           (PUNPCKHWDrr VR128:$src, VR128:$src)>;
3943 def : Pat<(v4i32 (unpckh_undef VR128:$src, (undef))),
3944           (PUNPCKHDQrr VR128:$src, VR128:$src)>;
3945 }
3946
3947 let AddedComplexity = 20 in {
3948 // vector_shuffle v1, v2 <0, 1, 4, 5> using MOVLHPS
3949 def : Pat<(v4i32 (movlhps VR128:$src1, VR128:$src2)),
3950           (MOVLHPSrr VR128:$src1, VR128:$src2)>;
3951
3952 // vector_shuffle v1, v2 <6, 7, 2, 3> using MOVHLPS
3953 def : Pat<(v4i32 (movhlps VR128:$src1, VR128:$src2)),
3954           (MOVHLPSrr VR128:$src1, VR128:$src2)>;
3955
3956 // vector_shuffle v1, undef <2, ?, ?, ?> using MOVHLPS
3957 def : Pat<(v4f32 (movhlps_undef VR128:$src1, (undef))),
3958           (MOVHLPSrr VR128:$src1, VR128:$src1)>;
3959 def : Pat<(v4i32 (movhlps_undef VR128:$src1, (undef))),
3960           (MOVHLPSrr VR128:$src1, VR128:$src1)>;
3961 }
3962
3963 let AddedComplexity = 20 in {
3964 // vector_shuffle v1, (load v2) <4, 5, 2, 3> using MOVLPS
3965 def : Pat<(v4f32 (movlp VR128:$src1, (load addr:$src2))),
3966           (MOVLPSrm VR128:$src1, addr:$src2)>;
3967 def : Pat<(v2f64 (movlp VR128:$src1, (load addr:$src2))),
3968           (MOVLPDrm VR128:$src1, addr:$src2)>;
3969 def : Pat<(v4i32 (movlp VR128:$src1, (load addr:$src2))),
3970           (MOVLPSrm VR128:$src1, addr:$src2)>;
3971 def : Pat<(v2i64 (movlp VR128:$src1, (load addr:$src2))),
3972           (MOVLPDrm VR128:$src1, addr:$src2)>;
3973 }
3974
3975 // (store (vector_shuffle (load addr), v2, <4, 5, 2, 3>), addr) using MOVLPS
3976 def : Pat<(store (v4f32 (movlp (load addr:$src1), VR128:$src2)), addr:$src1),
3977           (MOVLPSmr addr:$src1, VR128:$src2)>;
3978 def : Pat<(store (v2f64 (movlp (load addr:$src1), VR128:$src2)), addr:$src1),
3979           (MOVLPDmr addr:$src1, VR128:$src2)>;
3980 def : Pat<(store (v4i32 (movlp (bc_v4i32 (loadv2i64 addr:$src1)), VR128:$src2)),
3981                  addr:$src1),
3982           (MOVLPSmr addr:$src1, VR128:$src2)>;
3983 def : Pat<(store (v2i64 (movlp (load addr:$src1), VR128:$src2)), addr:$src1),
3984           (MOVLPDmr addr:$src1, VR128:$src2)>;
3985
3986 let AddedComplexity = 15 in {
3987 // Setting the lowest element in the vector.
3988 def : Pat<(v4i32 (movl VR128:$src1, VR128:$src2)),
3989           (MOVSSrr (v4i32 VR128:$src1),
3990                    (EXTRACT_SUBREG (v4i32 VR128:$src2), sub_ss))>;
3991 def : Pat<(v2i64 (movl VR128:$src1, VR128:$src2)),
3992           (MOVSDrr (v2i64 VR128:$src1),
3993                    (EXTRACT_SUBREG (v2i64 VR128:$src2), sub_sd))>;
3994
3995 // vector_shuffle v1, v2 <4, 5, 2, 3> using movsd
3996 def : Pat<(v4f32 (movlp VR128:$src1, VR128:$src2)),
3997           (MOVSDrr VR128:$src1, (EXTRACT_SUBREG VR128:$src2, sub_sd))>,
3998       Requires<[HasSSE2]>;
3999 def : Pat<(v4i32 (movlp VR128:$src1, VR128:$src2)),
4000           (MOVSDrr VR128:$src1, (EXTRACT_SUBREG VR128:$src2, sub_sd))>,
4001       Requires<[HasSSE2]>;
4002 }
4003
4004 // vector_shuffle v1, v2 <4, 5, 2, 3> using SHUFPSrri (we prefer movsd, but
4005 // fall back to this for SSE1)
4006 def : Pat<(v4f32 (movlp:$src3 VR128:$src1, (v4f32 VR128:$src2))),
4007           (SHUFPSrri VR128:$src2, VR128:$src1,
4008                      (SHUFFLE_get_shuf_imm VR128:$src3))>;
4009
4010 // Set lowest element and zero upper elements.
4011 def : Pat<(v2f64 (X86vzmovl (v2f64 VR128:$src))),
4012           (MOVZPQILo2PQIrr VR128:$src)>, Requires<[HasSSE2]>;
4013
4014 // Some special case pandn patterns.
4015 def : Pat<(v2i64 (and (xor VR128:$src1, (bc_v2i64 (v4i32 immAllOnesV))),
4016                   VR128:$src2)),
4017           (PANDNrr VR128:$src1, VR128:$src2)>, Requires<[HasSSE2]>;
4018 def : Pat<(v2i64 (and (xor VR128:$src1, (bc_v2i64 (v8i16 immAllOnesV))),
4019                   VR128:$src2)),
4020           (PANDNrr VR128:$src1, VR128:$src2)>, Requires<[HasSSE2]>;
4021 def : Pat<(v2i64 (and (xor VR128:$src1, (bc_v2i64 (v16i8 immAllOnesV))),
4022                   VR128:$src2)),
4023           (PANDNrr VR128:$src1, VR128:$src2)>, Requires<[HasSSE2]>;
4024
4025 def : Pat<(v2i64 (and (xor VR128:$src1, (bc_v2i64 (v4i32 immAllOnesV))),
4026                   (memop addr:$src2))),
4027           (PANDNrm VR128:$src1, addr:$src2)>, Requires<[HasSSE2]>;
4028 def : Pat<(v2i64 (and (xor VR128:$src1, (bc_v2i64 (v8i16 immAllOnesV))),
4029                   (memop addr:$src2))),
4030           (PANDNrm VR128:$src1, addr:$src2)>, Requires<[HasSSE2]>;
4031 def : Pat<(v2i64 (and (xor VR128:$src1, (bc_v2i64 (v16i8 immAllOnesV))),
4032                   (memop addr:$src2))),
4033           (PANDNrm VR128:$src1, addr:$src2)>, Requires<[HasSSE2]>;
4034
4035 // vector -> vector casts
4036 def : Pat<(v4f32 (sint_to_fp (v4i32 VR128:$src))),
4037           (Int_CVTDQ2PSrr VR128:$src)>, Requires<[HasSSE2]>;
4038 def : Pat<(v4i32 (fp_to_sint (v4f32 VR128:$src))),
4039           (Int_CVTTPS2DQrr VR128:$src)>, Requires<[HasSSE2]>;
4040 def : Pat<(v2f64 (sint_to_fp (v2i32 VR64:$src))),
4041           (Int_CVTPI2PDrr VR64:$src)>, Requires<[HasSSE2]>;
4042 def : Pat<(v2i32 (fp_to_sint (v2f64 VR128:$src))),
4043           (Int_CVTTPD2PIrr VR128:$src)>, Requires<[HasSSE2]>;
4044
4045 // Use movaps / movups for SSE integer load / store (one byte shorter).
4046 def : Pat<(alignedloadv4i32 addr:$src),
4047           (MOVAPSrm addr:$src)>;
4048 def : Pat<(loadv4i32 addr:$src),
4049           (MOVUPSrm addr:$src)>;
4050 def : Pat<(alignedloadv2i64 addr:$src),
4051           (MOVAPSrm addr:$src)>;
4052 def : Pat<(loadv2i64 addr:$src),
4053           (MOVUPSrm addr:$src)>;
4054
4055 def : Pat<(alignedstore (v2i64 VR128:$src), addr:$dst),
4056           (MOVAPSmr addr:$dst, VR128:$src)>;
4057 def : Pat<(alignedstore (v4i32 VR128:$src), addr:$dst),
4058           (MOVAPSmr addr:$dst, VR128:$src)>;
4059 def : Pat<(alignedstore (v8i16 VR128:$src), addr:$dst),
4060           (MOVAPSmr addr:$dst, VR128:$src)>;
4061 def : Pat<(alignedstore (v16i8 VR128:$src), addr:$dst),
4062           (MOVAPSmr addr:$dst, VR128:$src)>;
4063 def : Pat<(store (v2i64 VR128:$src), addr:$dst),
4064           (MOVUPSmr addr:$dst, VR128:$src)>;
4065 def : Pat<(store (v4i32 VR128:$src), addr:$dst),
4066           (MOVUPSmr addr:$dst, VR128:$src)>;
4067 def : Pat<(store (v8i16 VR128:$src), addr:$dst),
4068           (MOVUPSmr addr:$dst, VR128:$src)>;
4069 def : Pat<(store (v16i8 VR128:$src), addr:$dst),
4070           (MOVUPSmr addr:$dst, VR128:$src)>;
4071
4072 //===----------------------------------------------------------------------===//
4073 // SSE4.1 - Packed Move with Sign/Zero Extend
4074 //===----------------------------------------------------------------------===//
4075
4076 multiclass SS41I_binop_rm_int8<bits<8> opc, string OpcodeStr, Intrinsic IntId> {
4077   def rr : SS48I<opc, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
4078                  !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"),
4079                  [(set VR128:$dst, (IntId VR128:$src))]>, OpSize;
4080
4081   def rm : SS48I<opc, MRMSrcMem, (outs VR128:$dst), (ins i64mem:$src),
4082                  !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"),
4083        [(set VR128:$dst,
4084          (IntId (bitconvert (v2i64 (scalar_to_vector (loadi64 addr:$src))))))]>,
4085        OpSize;
4086 }
4087
4088 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
4089 defm VPMOVSXBW : SS41I_binop_rm_int8<0x20, "vpmovsxbw", int_x86_sse41_pmovsxbw>,
4090                                      VEX;
4091 defm VPMOVSXWD : SS41I_binop_rm_int8<0x23, "vpmovsxwd", int_x86_sse41_pmovsxwd>,
4092                                      VEX;
4093 defm VPMOVSXDQ : SS41I_binop_rm_int8<0x25, "vpmovsxdq", int_x86_sse41_pmovsxdq>,
4094                                      VEX;
4095 defm VPMOVZXBW : SS41I_binop_rm_int8<0x30, "vpmovzxbw", int_x86_sse41_pmovzxbw>,
4096                                      VEX;
4097 defm VPMOVZXWD : SS41I_binop_rm_int8<0x33, "vpmovzxwd", int_x86_sse41_pmovzxwd>,
4098                                      VEX;
4099 defm VPMOVZXDQ : SS41I_binop_rm_int8<0x35, "vpmovzxdq", int_x86_sse41_pmovzxdq>,
4100                                      VEX;
4101 }
4102
4103 defm PMOVSXBW   : SS41I_binop_rm_int8<0x20, "pmovsxbw", int_x86_sse41_pmovsxbw>;
4104 defm PMOVSXWD   : SS41I_binop_rm_int8<0x23, "pmovsxwd", int_x86_sse41_pmovsxwd>;
4105 defm PMOVSXDQ   : SS41I_binop_rm_int8<0x25, "pmovsxdq", int_x86_sse41_pmovsxdq>;
4106 defm PMOVZXBW   : SS41I_binop_rm_int8<0x30, "pmovzxbw", int_x86_sse41_pmovzxbw>;
4107 defm PMOVZXWD   : SS41I_binop_rm_int8<0x33, "pmovzxwd", int_x86_sse41_pmovzxwd>;
4108 defm PMOVZXDQ   : SS41I_binop_rm_int8<0x35, "pmovzxdq", int_x86_sse41_pmovzxdq>;
4109
4110 // Common patterns involving scalar load.
4111 def : Pat<(int_x86_sse41_pmovsxbw (vzmovl_v2i64 addr:$src)),
4112           (PMOVSXBWrm addr:$src)>, Requires<[HasSSE41]>;
4113 def : Pat<(int_x86_sse41_pmovsxbw (vzload_v2i64 addr:$src)),
4114           (PMOVSXBWrm addr:$src)>, Requires<[HasSSE41]>;
4115
4116 def : Pat<(int_x86_sse41_pmovsxwd (vzmovl_v2i64 addr:$src)),
4117           (PMOVSXWDrm addr:$src)>, Requires<[HasSSE41]>;
4118 def : Pat<(int_x86_sse41_pmovsxwd (vzload_v2i64 addr:$src)),
4119           (PMOVSXWDrm addr:$src)>, Requires<[HasSSE41]>;
4120
4121 def : Pat<(int_x86_sse41_pmovsxdq (vzmovl_v2i64 addr:$src)),
4122           (PMOVSXDQrm addr:$src)>, Requires<[HasSSE41]>;
4123 def : Pat<(int_x86_sse41_pmovsxdq (vzload_v2i64 addr:$src)),
4124           (PMOVSXDQrm addr:$src)>, Requires<[HasSSE41]>;
4125
4126 def : Pat<(int_x86_sse41_pmovzxbw (vzmovl_v2i64 addr:$src)),
4127           (PMOVZXBWrm addr:$src)>, Requires<[HasSSE41]>;
4128 def : Pat<(int_x86_sse41_pmovzxbw (vzload_v2i64 addr:$src)),
4129           (PMOVZXBWrm addr:$src)>, Requires<[HasSSE41]>;
4130
4131 def : Pat<(int_x86_sse41_pmovzxwd (vzmovl_v2i64 addr:$src)),
4132           (PMOVZXWDrm addr:$src)>, Requires<[HasSSE41]>;
4133 def : Pat<(int_x86_sse41_pmovzxwd (vzload_v2i64 addr:$src)),
4134           (PMOVZXWDrm addr:$src)>, Requires<[HasSSE41]>;
4135
4136 def : Pat<(int_x86_sse41_pmovzxdq (vzmovl_v2i64 addr:$src)),
4137           (PMOVZXDQrm addr:$src)>, Requires<[HasSSE41]>;
4138 def : Pat<(int_x86_sse41_pmovzxdq (vzload_v2i64 addr:$src)),
4139           (PMOVZXDQrm addr:$src)>, Requires<[HasSSE41]>;
4140
4141
4142 multiclass SS41I_binop_rm_int4<bits<8> opc, string OpcodeStr, Intrinsic IntId> {
4143   def rr : SS48I<opc, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
4144                  !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"),
4145                  [(set VR128:$dst, (IntId VR128:$src))]>, OpSize;
4146
4147   def rm : SS48I<opc, MRMSrcMem, (outs VR128:$dst), (ins i32mem:$src),
4148                  !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"),
4149        [(set VR128:$dst,
4150          (IntId (bitconvert (v4i32 (scalar_to_vector (loadi32 addr:$src))))))]>,
4151           OpSize;
4152 }
4153
4154 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
4155 defm VPMOVSXBD : SS41I_binop_rm_int4<0x21, "vpmovsxbd", int_x86_sse41_pmovsxbd>,
4156                                      VEX;
4157 defm VPMOVSXWQ : SS41I_binop_rm_int4<0x24, "vpmovsxwq", int_x86_sse41_pmovsxwq>,
4158                                      VEX;
4159 defm VPMOVZXBD : SS41I_binop_rm_int4<0x31, "vpmovzxbd", int_x86_sse41_pmovzxbd>,
4160                                      VEX;
4161 defm VPMOVZXWQ : SS41I_binop_rm_int4<0x34, "vpmovzxwq", int_x86_sse41_pmovzxwq>,
4162                                      VEX;
4163 }
4164
4165 defm PMOVSXBD   : SS41I_binop_rm_int4<0x21, "pmovsxbd", int_x86_sse41_pmovsxbd>;
4166 defm PMOVSXWQ   : SS41I_binop_rm_int4<0x24, "pmovsxwq", int_x86_sse41_pmovsxwq>;
4167 defm PMOVZXBD   : SS41I_binop_rm_int4<0x31, "pmovzxbd", int_x86_sse41_pmovzxbd>;
4168 defm PMOVZXWQ   : SS41I_binop_rm_int4<0x34, "pmovzxwq", int_x86_sse41_pmovzxwq>;
4169
4170 // Common patterns involving scalar load
4171 def : Pat<(int_x86_sse41_pmovsxbd (vzmovl_v4i32 addr:$src)),
4172           (PMOVSXBDrm addr:$src)>, Requires<[HasSSE41]>;
4173 def : Pat<(int_x86_sse41_pmovsxwq (vzmovl_v4i32 addr:$src)),
4174           (PMOVSXWQrm addr:$src)>, Requires<[HasSSE41]>;
4175
4176 def : Pat<(int_x86_sse41_pmovzxbd (vzmovl_v4i32 addr:$src)),
4177           (PMOVZXBDrm addr:$src)>, Requires<[HasSSE41]>;
4178 def : Pat<(int_x86_sse41_pmovzxwq (vzmovl_v4i32 addr:$src)),
4179           (PMOVZXWQrm addr:$src)>, Requires<[HasSSE41]>;
4180
4181
4182 multiclass SS41I_binop_rm_int2<bits<8> opc, string OpcodeStr, Intrinsic IntId> {
4183   def rr : SS48I<opc, MRMSrcReg, (outs VR128:$dst), (ins VR128:$src),
4184                  !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"),
4185                  [(set VR128:$dst, (IntId VR128:$src))]>, OpSize;
4186
4187   // Expecting a i16 load any extended to i32 value.
4188   def rm : SS48I<opc, MRMSrcMem, (outs VR128:$dst), (ins i16mem:$src),
4189                  !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"),
4190                  [(set VR128:$dst, (IntId (bitconvert
4191                      (v4i32 (scalar_to_vector (loadi16_anyext addr:$src))))))]>,
4192                  OpSize;
4193 }
4194
4195 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
4196 defm VPMOVSXBQ : SS41I_binop_rm_int2<0x22, "vpmovsxbq", int_x86_sse41_pmovsxbq>,
4197                                      VEX;
4198 defm VPMOVZXBQ : SS41I_binop_rm_int2<0x32, "vpmovzxbq", int_x86_sse41_pmovzxbq>,
4199                                      VEX;
4200 }
4201 defm PMOVSXBQ   : SS41I_binop_rm_int2<0x22, "pmovsxbq", int_x86_sse41_pmovsxbq>;
4202 defm PMOVZXBQ   : SS41I_binop_rm_int2<0x32, "pmovzxbq", int_x86_sse41_pmovzxbq>;
4203
4204 // Common patterns involving scalar load
4205 def : Pat<(int_x86_sse41_pmovsxbq
4206             (bitconvert (v4i32 (X86vzmovl
4207                              (v4i32 (scalar_to_vector (loadi32 addr:$src))))))),
4208           (PMOVSXBQrm addr:$src)>, Requires<[HasSSE41]>;
4209
4210 def : Pat<(int_x86_sse41_pmovzxbq
4211             (bitconvert (v4i32 (X86vzmovl
4212                              (v4i32 (scalar_to_vector (loadi32 addr:$src))))))),
4213           (PMOVZXBQrm addr:$src)>, Requires<[HasSSE41]>;
4214
4215 //===----------------------------------------------------------------------===//
4216 // SSE4.1 - Extract Instructions
4217 //===----------------------------------------------------------------------===//
4218
4219 /// SS41I_binop_ext8 - SSE 4.1 extract 8 bits to 32 bit reg or 8 bit mem
4220 multiclass SS41I_extract8<bits<8> opc, string OpcodeStr> {
4221   def rr : SS4AIi8<opc, MRMDestReg, (outs GR32:$dst),
4222                  (ins VR128:$src1, i32i8imm:$src2),
4223                  !strconcat(OpcodeStr,
4224                   "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
4225                  [(set GR32:$dst, (X86pextrb (v16i8 VR128:$src1), imm:$src2))]>,
4226                  OpSize;
4227   def mr : SS4AIi8<opc, MRMDestMem, (outs),
4228                  (ins i8mem:$dst, VR128:$src1, i32i8imm:$src2),
4229                  !strconcat(OpcodeStr,
4230                   "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
4231                  []>, OpSize;
4232 // FIXME:
4233 // There's an AssertZext in the way of writing the store pattern
4234 // (store (i8 (trunc (X86pextrb (v16i8 VR128:$src1), imm:$src2))), addr:$dst)
4235 }
4236
4237 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
4238   defm VPEXTRB : SS41I_extract8<0x14, "vpextrb">, VEX;
4239   def  VPEXTRBrr64 : SS4AIi8<0x14, MRMDestReg, (outs GR64:$dst),
4240          (ins VR128:$src1, i32i8imm:$src2),
4241          "vpextrb\t{$src2, $src1, $dst|$dst, $src1, $src2}", []>, OpSize, VEX;
4242 }
4243
4244 defm PEXTRB      : SS41I_extract8<0x14, "pextrb">;
4245
4246
4247 /// SS41I_extract16 - SSE 4.1 extract 16 bits to memory destination
4248 multiclass SS41I_extract16<bits<8> opc, string OpcodeStr> {
4249   def mr : SS4AIi8<opc, MRMDestMem, (outs),
4250                  (ins i16mem:$dst, VR128:$src1, i32i8imm:$src2),
4251                  !strconcat(OpcodeStr,
4252                   "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
4253                  []>, OpSize;
4254 // FIXME:
4255 // There's an AssertZext in the way of writing the store pattern
4256 // (store (i16 (trunc (X86pextrw (v16i8 VR128:$src1), imm:$src2))), addr:$dst)
4257 }
4258
4259 let isAsmParserOnly = 1, Predicates = [HasAVX] in
4260   defm VPEXTRW : SS41I_extract16<0x15, "vpextrw">, VEX;
4261
4262 defm PEXTRW      : SS41I_extract16<0x15, "pextrw">;
4263
4264
4265 /// SS41I_extract32 - SSE 4.1 extract 32 bits to int reg or memory destination
4266 multiclass SS41I_extract32<bits<8> opc, string OpcodeStr> {
4267   def rr : SS4AIi8<opc, MRMDestReg, (outs GR32:$dst),
4268                  (ins VR128:$src1, i32i8imm:$src2),
4269                  !strconcat(OpcodeStr,
4270                   "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
4271                  [(set GR32:$dst,
4272                   (extractelt (v4i32 VR128:$src1), imm:$src2))]>, OpSize;
4273   def mr : SS4AIi8<opc, MRMDestMem, (outs),
4274                  (ins i32mem:$dst, VR128:$src1, i32i8imm:$src2),
4275                  !strconcat(OpcodeStr,
4276                   "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
4277                  [(store (extractelt (v4i32 VR128:$src1), imm:$src2),
4278                           addr:$dst)]>, OpSize;
4279 }
4280
4281 let isAsmParserOnly = 1, Predicates = [HasAVX] in
4282   defm VPEXTRD : SS41I_extract32<0x16, "vpextrd">, VEX;
4283
4284 defm PEXTRD      : SS41I_extract32<0x16, "pextrd">;
4285
4286 /// SS41I_extract32 - SSE 4.1 extract 32 bits to int reg or memory destination
4287 multiclass SS41I_extract64<bits<8> opc, string OpcodeStr> {
4288   def rr : SS4AIi8<opc, MRMDestReg, (outs GR64:$dst),
4289                  (ins VR128:$src1, i32i8imm:$src2),
4290                  !strconcat(OpcodeStr,
4291                   "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
4292                  [(set GR64:$dst,
4293                   (extractelt (v2i64 VR128:$src1), imm:$src2))]>, OpSize, REX_W;
4294   def mr : SS4AIi8<opc, MRMDestMem, (outs),
4295                  (ins i64mem:$dst, VR128:$src1, i32i8imm:$src2),
4296                  !strconcat(OpcodeStr,
4297                   "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
4298                  [(store (extractelt (v2i64 VR128:$src1), imm:$src2),
4299                           addr:$dst)]>, OpSize, REX_W;
4300 }
4301
4302 let isAsmParserOnly = 1, Predicates = [HasAVX] in
4303   defm VPEXTRQ : SS41I_extract64<0x16, "vpextrq">, VEX, VEX_W;
4304
4305 defm PEXTRQ      : SS41I_extract64<0x16, "pextrq">;
4306
4307 /// SS41I_extractf32 - SSE 4.1 extract 32 bits fp value to int reg or memory
4308 /// destination
4309 multiclass SS41I_extractf32<bits<8> opc, string OpcodeStr> {
4310   def rr : SS4AIi8<opc, MRMDestReg, (outs GR32:$dst),
4311                  (ins VR128:$src1, i32i8imm:$src2),
4312                  !strconcat(OpcodeStr,
4313                   "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
4314                  [(set GR32:$dst,
4315                     (extractelt (bc_v4i32 (v4f32 VR128:$src1)), imm:$src2))]>,
4316            OpSize;
4317   def mr : SS4AIi8<opc, MRMDestMem, (outs),
4318                  (ins f32mem:$dst, VR128:$src1, i32i8imm:$src2),
4319                  !strconcat(OpcodeStr,
4320                   "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
4321                  [(store (extractelt (bc_v4i32 (v4f32 VR128:$src1)), imm:$src2),
4322                           addr:$dst)]>, OpSize;
4323 }
4324
4325 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
4326   defm VEXTRACTPS : SS41I_extractf32<0x17, "vextractps">, VEX;
4327   def VEXTRACTPSrr64 : SS4AIi8<0x17, MRMDestReg, (outs GR64:$dst),
4328                   (ins VR128:$src1, i32i8imm:$src2),
4329                   "vextractps \t{$src2, $src1, $dst|$dst, $src1, $src2}",
4330                   []>, OpSize, VEX;
4331 }
4332 defm EXTRACTPS   : SS41I_extractf32<0x17, "extractps">;
4333
4334 // Also match an EXTRACTPS store when the store is done as f32 instead of i32.
4335 def : Pat<(store (f32 (bitconvert (extractelt (bc_v4i32 (v4f32 VR128:$src1)),
4336                                               imm:$src2))),
4337                  addr:$dst),
4338           (EXTRACTPSmr addr:$dst, VR128:$src1, imm:$src2)>,
4339          Requires<[HasSSE41]>;
4340
4341 //===----------------------------------------------------------------------===//
4342 // SSE4.1 - Insert Instructions
4343 //===----------------------------------------------------------------------===//
4344
4345 multiclass SS41I_insert8<bits<8> opc, string asm, bit Is2Addr = 1> {
4346   def rr : SS4AIi8<opc, MRMSrcReg, (outs VR128:$dst),
4347       (ins VR128:$src1, GR32:$src2, i32i8imm:$src3),
4348       !if(Is2Addr,
4349         !strconcat(asm, "\t{$src3, $src2, $dst|$dst, $src2, $src3}"),
4350         !strconcat(asm,
4351                    "\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}")),
4352       [(set VR128:$dst,
4353         (X86pinsrb VR128:$src1, GR32:$src2, imm:$src3))]>, OpSize;
4354   def rm : SS4AIi8<opc, MRMSrcMem, (outs VR128:$dst),
4355       (ins VR128:$src1, i8mem:$src2, i32i8imm:$src3),
4356       !if(Is2Addr,
4357         !strconcat(asm, "\t{$src3, $src2, $dst|$dst, $src2, $src3}"),
4358         !strconcat(asm,
4359                    "\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}")),
4360       [(set VR128:$dst,
4361         (X86pinsrb VR128:$src1, (extloadi8 addr:$src2),
4362                    imm:$src3))]>, OpSize;
4363 }
4364
4365 let isAsmParserOnly = 1, Predicates = [HasAVX] in
4366   defm VPINSRB : SS41I_insert8<0x20, "vpinsrb", 0>, VEX_4V;
4367 let Constraints = "$src1 = $dst" in
4368   defm PINSRB  : SS41I_insert8<0x20, "pinsrb">;
4369
4370 multiclass SS41I_insert32<bits<8> opc, string asm, bit Is2Addr = 1> {
4371   def rr : SS4AIi8<opc, MRMSrcReg, (outs VR128:$dst),
4372       (ins VR128:$src1, GR32:$src2, i32i8imm:$src3),
4373       !if(Is2Addr,
4374         !strconcat(asm, "\t{$src3, $src2, $dst|$dst, $src2, $src3}"),
4375         !strconcat(asm,
4376                    "\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}")),
4377       [(set VR128:$dst,
4378         (v4i32 (insertelt VR128:$src1, GR32:$src2, imm:$src3)))]>,
4379       OpSize;
4380   def rm : SS4AIi8<opc, MRMSrcMem, (outs VR128:$dst),
4381       (ins VR128:$src1, i32mem:$src2, i32i8imm:$src3),
4382       !if(Is2Addr,
4383         !strconcat(asm, "\t{$src3, $src2, $dst|$dst, $src2, $src3}"),
4384         !strconcat(asm,
4385                    "\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}")),
4386       [(set VR128:$dst,
4387         (v4i32 (insertelt VR128:$src1, (loadi32 addr:$src2),
4388                           imm:$src3)))]>, OpSize;
4389 }
4390
4391 let isAsmParserOnly = 1, Predicates = [HasAVX] in
4392   defm VPINSRD : SS41I_insert32<0x22, "vpinsrd", 0>, VEX_4V;
4393 let Constraints = "$src1 = $dst" in
4394   defm PINSRD : SS41I_insert32<0x22, "pinsrd">;
4395
4396 multiclass SS41I_insert64<bits<8> opc, string asm, bit Is2Addr = 1> {
4397   def rr : SS4AIi8<opc, MRMSrcReg, (outs VR128:$dst),
4398       (ins VR128:$src1, GR64:$src2, i32i8imm:$src3),
4399       !if(Is2Addr,
4400         !strconcat(asm, "\t{$src3, $src2, $dst|$dst, $src2, $src3}"),
4401         !strconcat(asm,
4402                    "\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}")),
4403       [(set VR128:$dst,
4404         (v2i64 (insertelt VR128:$src1, GR64:$src2, imm:$src3)))]>,
4405       OpSize;
4406   def rm : SS4AIi8<opc, MRMSrcMem, (outs VR128:$dst),
4407       (ins VR128:$src1, i64mem:$src2, i32i8imm:$src3),
4408       !if(Is2Addr,
4409         !strconcat(asm, "\t{$src3, $src2, $dst|$dst, $src2, $src3}"),
4410         !strconcat(asm,
4411                    "\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}")),
4412       [(set VR128:$dst,
4413         (v2i64 (insertelt VR128:$src1, (loadi64 addr:$src2),
4414                           imm:$src3)))]>, OpSize;
4415 }
4416
4417 let isAsmParserOnly = 1, Predicates = [HasAVX] in
4418   defm VPINSRQ : SS41I_insert64<0x22, "vpinsrq", 0>, VEX_4V, VEX_W;
4419 let Constraints = "$src1 = $dst" in
4420   defm PINSRQ : SS41I_insert64<0x22, "pinsrq">, REX_W;
4421
4422 // insertps has a few different modes, there's the first two here below which
4423 // are optimized inserts that won't zero arbitrary elements in the destination
4424 // vector. The next one matches the intrinsic and could zero arbitrary elements
4425 // in the target vector.
4426 multiclass SS41I_insertf32<bits<8> opc, string asm, bit Is2Addr = 1> {
4427   def rr : SS4AIi8<opc, MRMSrcReg, (outs VR128:$dst),
4428       (ins VR128:$src1, VR128:$src2, i32i8imm:$src3),
4429       !if(Is2Addr,
4430         !strconcat(asm, "\t{$src3, $src2, $dst|$dst, $src2, $src3}"),
4431         !strconcat(asm,
4432                    "\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}")),
4433       [(set VR128:$dst,
4434         (X86insrtps VR128:$src1, VR128:$src2, imm:$src3))]>,
4435       OpSize;
4436   def rm : SS4AIi8<opc, MRMSrcMem, (outs VR128:$dst),
4437       (ins VR128:$src1, f32mem:$src2, i32i8imm:$src3),
4438       !if(Is2Addr,
4439         !strconcat(asm, "\t{$src3, $src2, $dst|$dst, $src2, $src3}"),
4440         !strconcat(asm,
4441                    "\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}")),
4442       [(set VR128:$dst,
4443         (X86insrtps VR128:$src1,
4444                    (v4f32 (scalar_to_vector (loadf32 addr:$src2))),
4445                     imm:$src3))]>, OpSize;
4446 }
4447
4448 let Constraints = "$src1 = $dst" in
4449   defm INSERTPS : SS41I_insertf32<0x21, "insertps">;
4450 let isAsmParserOnly = 1, Predicates = [HasAVX] in
4451   defm VINSERTPS : SS41I_insertf32<0x21, "vinsertps", 0>, VEX_4V;
4452
4453 def : Pat<(int_x86_sse41_insertps VR128:$src1, VR128:$src2, imm:$src3),
4454           (VINSERTPSrr VR128:$src1, VR128:$src2, imm:$src3)>,
4455           Requires<[HasAVX]>;
4456 def : Pat<(int_x86_sse41_insertps VR128:$src1, VR128:$src2, imm:$src3),
4457           (INSERTPSrr VR128:$src1, VR128:$src2, imm:$src3)>,
4458           Requires<[HasSSE41]>;
4459
4460 //===----------------------------------------------------------------------===//
4461 // SSE4.1 - Round Instructions
4462 //===----------------------------------------------------------------------===//
4463
4464 multiclass sse41_fp_unop_rm<bits<8> opcps, bits<8> opcpd, string OpcodeStr,
4465                             X86MemOperand x86memop, RegisterClass RC,
4466                             PatFrag mem_frag32, PatFrag mem_frag64,
4467                             Intrinsic V4F32Int, Intrinsic V2F64Int> {
4468   // Intrinsic operation, reg.
4469   // Vector intrinsic operation, reg
4470   def PSr_Int : SS4AIi8<opcps, MRMSrcReg,
4471                     (outs RC:$dst), (ins RC:$src1, i32i8imm:$src2),
4472                     !strconcat(OpcodeStr,
4473                     "ps\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
4474                     [(set RC:$dst, (V4F32Int RC:$src1, imm:$src2))]>,
4475                     OpSize;
4476
4477   // Vector intrinsic operation, mem
4478   def PSm_Int : Ii8<opcps, MRMSrcMem,
4479                     (outs RC:$dst), (ins f256mem:$src1, i32i8imm:$src2),
4480                     !strconcat(OpcodeStr,
4481                     "ps\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
4482                     [(set RC:$dst,
4483                           (V4F32Int (mem_frag32 addr:$src1),imm:$src2))]>,
4484                     TA, OpSize,
4485                 Requires<[HasSSE41]>;
4486
4487   // Vector intrinsic operation, reg
4488   def PDr_Int : SS4AIi8<opcpd, MRMSrcReg,
4489                     (outs RC:$dst), (ins RC:$src1, i32i8imm:$src2),
4490                     !strconcat(OpcodeStr,
4491                     "pd\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
4492                     [(set RC:$dst, (V2F64Int RC:$src1, imm:$src2))]>,
4493                     OpSize;
4494
4495   // Vector intrinsic operation, mem
4496   def PDm_Int : SS4AIi8<opcpd, MRMSrcMem,
4497                     (outs RC:$dst), (ins f256mem:$src1, i32i8imm:$src2),
4498                     !strconcat(OpcodeStr,
4499                     "pd\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
4500                     [(set RC:$dst,
4501                           (V2F64Int (mem_frag64 addr:$src1),imm:$src2))]>,
4502                     OpSize;
4503 }
4504
4505 multiclass sse41_fp_unop_rm_avx_p<bits<8> opcps, bits<8> opcpd,
4506                    RegisterClass RC, X86MemOperand x86memop, string OpcodeStr> {
4507   // Intrinsic operation, reg.
4508   // Vector intrinsic operation, reg
4509   def PSr : SS4AIi8<opcps, MRMSrcReg,
4510                     (outs RC:$dst), (ins RC:$src1, i32i8imm:$src2),
4511                     !strconcat(OpcodeStr,
4512                     "ps\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
4513                     []>, OpSize;
4514
4515   // Vector intrinsic operation, mem
4516   def PSm : Ii8<opcps, MRMSrcMem,
4517                     (outs RC:$dst), (ins x86memop:$src1, i32i8imm:$src2),
4518                     !strconcat(OpcodeStr,
4519                     "ps\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
4520                     []>, TA, OpSize, Requires<[HasSSE41]>;
4521
4522   // Vector intrinsic operation, reg
4523   def PDr : SS4AIi8<opcpd, MRMSrcReg,
4524                     (outs RC:$dst), (ins RC:$src1, i32i8imm:$src2),
4525                     !strconcat(OpcodeStr,
4526                     "pd\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
4527                     []>, OpSize;
4528
4529   // Vector intrinsic operation, mem
4530   def PDm : SS4AIi8<opcpd, MRMSrcMem,
4531                     (outs RC:$dst), (ins x86memop:$src1, i32i8imm:$src2),
4532                     !strconcat(OpcodeStr,
4533                     "pd\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
4534                     []>, OpSize;
4535 }
4536
4537 multiclass sse41_fp_binop_rm<bits<8> opcss, bits<8> opcsd,
4538                             string OpcodeStr,
4539                             Intrinsic F32Int,
4540                             Intrinsic F64Int, bit Is2Addr = 1> {
4541   // Intrinsic operation, reg.
4542   def SSr_Int : SS4AIi8<opcss, MRMSrcReg,
4543         (outs VR128:$dst), (ins VR128:$src1, VR128:$src2, i32i8imm:$src3),
4544         !if(Is2Addr,
4545             !strconcat(OpcodeStr,
4546                 "ss\t{$src3, $src2, $dst|$dst, $src2, $src3}"),
4547             !strconcat(OpcodeStr,
4548                 "ss\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}")),
4549         [(set VR128:$dst, (F32Int VR128:$src1, VR128:$src2, imm:$src3))]>,
4550         OpSize;
4551
4552   // Intrinsic operation, mem.
4553   def SSm_Int : SS4AIi8<opcss, MRMSrcMem,
4554         (outs VR128:$dst), (ins VR128:$src1, ssmem:$src2, i32i8imm:$src3),
4555         !if(Is2Addr,
4556             !strconcat(OpcodeStr,
4557                 "ss\t{$src3, $src2, $dst|$dst, $src2, $src3}"),
4558             !strconcat(OpcodeStr,
4559                 "ss\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}")),
4560         [(set VR128:$dst,
4561              (F32Int VR128:$src1, sse_load_f32:$src2, imm:$src3))]>,
4562         OpSize;
4563
4564   // Intrinsic operation, reg.
4565   def SDr_Int : SS4AIi8<opcsd, MRMSrcReg,
4566         (outs VR128:$dst), (ins VR128:$src1, VR128:$src2, i32i8imm:$src3),
4567         !if(Is2Addr,
4568             !strconcat(OpcodeStr,
4569                 "sd\t{$src3, $src2, $dst|$dst, $src2, $src3}"),
4570             !strconcat(OpcodeStr,
4571                 "sd\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}")),
4572         [(set VR128:$dst, (F64Int VR128:$src1, VR128:$src2, imm:$src3))]>,
4573         OpSize;
4574
4575   // Intrinsic operation, mem.
4576   def SDm_Int : SS4AIi8<opcsd, MRMSrcMem,
4577         (outs VR128:$dst), (ins VR128:$src1, sdmem:$src2, i32i8imm:$src3),
4578         !if(Is2Addr,
4579             !strconcat(OpcodeStr,
4580                 "sd\t{$src3, $src2, $dst|$dst, $src2, $src3}"),
4581             !strconcat(OpcodeStr,
4582                 "sd\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}")),
4583         [(set VR128:$dst,
4584               (F64Int VR128:$src1, sse_load_f64:$src2, imm:$src3))]>,
4585         OpSize;
4586 }
4587
4588 multiclass sse41_fp_binop_rm_avx_s<bits<8> opcss, bits<8> opcsd,
4589                                    string OpcodeStr> {
4590   // Intrinsic operation, reg.
4591   def SSr : SS4AIi8<opcss, MRMSrcReg,
4592         (outs VR128:$dst), (ins VR128:$src1, VR128:$src2, i32i8imm:$src3),
4593         !strconcat(OpcodeStr,
4594                 "ss\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}"),
4595         []>, OpSize;
4596
4597   // Intrinsic operation, mem.
4598   def SSm : SS4AIi8<opcss, MRMSrcMem,
4599         (outs VR128:$dst), (ins VR128:$src1, ssmem:$src2, i32i8imm:$src3),
4600         !strconcat(OpcodeStr,
4601                 "ss\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}"),
4602         []>, OpSize;
4603
4604   // Intrinsic operation, reg.
4605   def SDr : SS4AIi8<opcsd, MRMSrcReg,
4606         (outs VR128:$dst), (ins VR128:$src1, VR128:$src2, i32i8imm:$src3),
4607             !strconcat(OpcodeStr,
4608                 "sd\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}"),
4609         []>, OpSize;
4610
4611   // Intrinsic operation, mem.
4612   def SDm : SS4AIi8<opcsd, MRMSrcMem,
4613         (outs VR128:$dst), (ins VR128:$src1, sdmem:$src2, i32i8imm:$src3),
4614             !strconcat(OpcodeStr,
4615                 "sd\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}"),
4616         []>, OpSize;
4617 }
4618
4619 // FP round - roundss, roundps, roundsd, roundpd
4620 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
4621   // Intrinsic form
4622   defm VROUND  : sse41_fp_unop_rm<0x08, 0x09, "vround", f128mem, VR128,
4623                                   memopv4f32, memopv2f64,
4624                                   int_x86_sse41_round_ps,
4625                                   int_x86_sse41_round_pd>, VEX;
4626   defm VROUNDY : sse41_fp_unop_rm<0x08, 0x09, "vround", f256mem, VR256,
4627                                   memopv8f32, memopv4f64,
4628                                   int_x86_avx_round_ps_256,
4629                                   int_x86_avx_round_pd_256>, VEX;
4630   defm VROUND  : sse41_fp_binop_rm<0x0A, 0x0B, "vround",
4631                                   int_x86_sse41_round_ss,
4632                                   int_x86_sse41_round_sd, 0>, VEX_4V;
4633
4634   // Instructions for the assembler
4635   defm VROUND  : sse41_fp_unop_rm_avx_p<0x08, 0x09, VR128, f128mem, "vround">,
4636                                         VEX;
4637   defm VROUNDY : sse41_fp_unop_rm_avx_p<0x08, 0x09, VR256, f256mem, "vround">,
4638                                         VEX;
4639   defm VROUND  : sse41_fp_binop_rm_avx_s<0x0A, 0x0B, "vround">, VEX_4V;
4640 }
4641
4642 defm ROUND  : sse41_fp_unop_rm<0x08, 0x09, "round", f128mem, VR128,
4643                                memopv4f32, memopv2f64,
4644                                int_x86_sse41_round_ps, int_x86_sse41_round_pd>;
4645 let Constraints = "$src1 = $dst" in
4646 defm ROUND  : sse41_fp_binop_rm<0x0A, 0x0B, "round",
4647                                int_x86_sse41_round_ss, int_x86_sse41_round_sd>;
4648
4649 //===----------------------------------------------------------------------===//
4650 // SSE4.1 - Packed Bit Test
4651 //===----------------------------------------------------------------------===//
4652
4653 // ptest instruction we'll lower to this in X86ISelLowering primarily from
4654 // the intel intrinsic that corresponds to this.
4655 let Defs = [EFLAGS], isAsmParserOnly = 1, Predicates = [HasAVX] in {
4656 def VPTESTrr  : SS48I<0x17, MRMSrcReg, (outs), (ins VR128:$src1, VR128:$src2),
4657                 "vptest\t{$src2, $src1|$src1, $src2}",
4658                 [(set EFLAGS, (X86ptest VR128:$src1, (v4f32 VR128:$src2)))]>,
4659                 OpSize, VEX;
4660 def VPTESTrm  : SS48I<0x17, MRMSrcMem, (outs), (ins VR128:$src1, f128mem:$src2),
4661                 "vptest\t{$src2, $src1|$src1, $src2}",
4662                 [(set EFLAGS,(X86ptest VR128:$src1, (memopv4f32 addr:$src2)))]>,
4663                 OpSize, VEX;
4664
4665 def VPTESTYrr : SS48I<0x17, MRMSrcReg, (outs), (ins VR256:$src1, VR256:$src2),
4666                 "vptest\t{$src2, $src1|$src1, $src2}",
4667                 [(set EFLAGS, (X86ptest VR256:$src1, (v4i64 VR256:$src2)))]>,
4668                 OpSize, VEX;
4669 def VPTESTYrm : SS48I<0x17, MRMSrcMem, (outs), (ins VR256:$src1, i256mem:$src2),
4670                 "vptest\t{$src2, $src1|$src1, $src2}",
4671                 [(set EFLAGS,(X86ptest VR256:$src1, (memopv4i64 addr:$src2)))]>,
4672                 OpSize, VEX;
4673 }
4674
4675 let Defs = [EFLAGS] in {
4676 def PTESTrr : SS48I<0x17, MRMSrcReg, (outs), (ins VR128:$src1, VR128:$src2),
4677               "ptest \t{$src2, $src1|$src1, $src2}",
4678               [(set EFLAGS, (X86ptest VR128:$src1, (v4f32 VR128:$src2)))]>,
4679               OpSize;
4680 def PTESTrm : SS48I<0x17, MRMSrcMem, (outs), (ins VR128:$src1, f128mem:$src2),
4681               "ptest \t{$src2, $src1|$src1, $src2}",
4682               [(set EFLAGS, (X86ptest VR128:$src1, (memopv4f32 addr:$src2)))]>,
4683               OpSize;
4684 }
4685
4686 // The bit test instructions below are AVX only
4687 multiclass avx_bittest<bits<8> opc, string OpcodeStr, RegisterClass RC,
4688                        X86MemOperand x86memop, PatFrag mem_frag, ValueType vt> {
4689   def rr : SS48I<opc, MRMSrcReg, (outs), (ins RC:$src1, RC:$src2),
4690             !strconcat(OpcodeStr, "\t{$src2, $src1|$src1, $src2}"),
4691             [(set EFLAGS, (X86testp RC:$src1, (vt RC:$src2)))]>, OpSize, VEX;
4692   def rm : SS48I<opc, MRMSrcMem, (outs), (ins RC:$src1, x86memop:$src2),
4693             !strconcat(OpcodeStr, "\t{$src2, $src1|$src1, $src2}"),
4694             [(set EFLAGS, (X86testp RC:$src1, (mem_frag addr:$src2)))]>,
4695             OpSize, VEX;
4696 }
4697
4698 let Defs = [EFLAGS], isAsmParserOnly = 1, Predicates = [HasAVX] in {
4699 defm VTESTPS  : avx_bittest<0x0E, "vtestps", VR128, f128mem, memopv4f32, v4f32>;
4700 defm VTESTPSY : avx_bittest<0x0E, "vtestps", VR256, f256mem, memopv8f32, v8f32>;
4701 defm VTESTPD  : avx_bittest<0x0F, "vtestpd", VR128, f128mem, memopv2f64, v2f64>;
4702 defm VTESTPDY : avx_bittest<0x0F, "vtestpd", VR256, f256mem, memopv4f64, v4f64>;
4703 }
4704
4705 //===----------------------------------------------------------------------===//
4706 // SSE4.1 - Misc Instructions
4707 //===----------------------------------------------------------------------===//
4708
4709 // SS41I_unop_rm_int_v16 - SSE 4.1 unary operator whose type is v8i16.
4710 multiclass SS41I_unop_rm_int_v16<bits<8> opc, string OpcodeStr,
4711                                  Intrinsic IntId128> {
4712   def rr128 : SS48I<opc, MRMSrcReg, (outs VR128:$dst),
4713                     (ins VR128:$src),
4714                     !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"),
4715                     [(set VR128:$dst, (IntId128 VR128:$src))]>, OpSize;
4716   def rm128 : SS48I<opc, MRMSrcMem, (outs VR128:$dst),
4717                      (ins i128mem:$src),
4718                      !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"),
4719                      [(set VR128:$dst,
4720                        (IntId128
4721                        (bitconvert (memopv8i16 addr:$src))))]>, OpSize;
4722 }
4723
4724 let isAsmParserOnly = 1, Predicates = [HasAVX] in
4725 defm VPHMINPOSUW : SS41I_unop_rm_int_v16 <0x41, "vphminposuw",
4726                                          int_x86_sse41_phminposuw>, VEX;
4727 defm PHMINPOSUW : SS41I_unop_rm_int_v16 <0x41, "phminposuw",
4728                                          int_x86_sse41_phminposuw>;
4729
4730 /// SS41I_binop_rm_int - Simple SSE 4.1 binary operator
4731 multiclass SS41I_binop_rm_int<bits<8> opc, string OpcodeStr,
4732                               Intrinsic IntId128, bit Is2Addr = 1> {
4733   let isCommutable = 1 in
4734   def rr : SS48I<opc, MRMSrcReg, (outs VR128:$dst),
4735        (ins VR128:$src1, VR128:$src2),
4736        !if(Is2Addr,
4737            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
4738            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
4739        [(set VR128:$dst, (IntId128 VR128:$src1, VR128:$src2))]>, OpSize;
4740   def rm : SS48I<opc, MRMSrcMem, (outs VR128:$dst),
4741        (ins VR128:$src1, i128mem:$src2),
4742        !if(Is2Addr,
4743            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
4744            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
4745        [(set VR128:$dst,
4746          (IntId128 VR128:$src1,
4747           (bitconvert (memopv16i8 addr:$src2))))]>, OpSize;
4748 }
4749
4750 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
4751   let isCommutable = 0 in
4752   defm VPACKUSDW : SS41I_binop_rm_int<0x2B, "vpackusdw", int_x86_sse41_packusdw,
4753                                                          0>, VEX_4V;
4754   defm VPCMPEQQ  : SS41I_binop_rm_int<0x29, "vpcmpeqq",  int_x86_sse41_pcmpeqq,
4755                                                          0>, VEX_4V;
4756   defm VPMINSB   : SS41I_binop_rm_int<0x38, "vpminsb",   int_x86_sse41_pminsb,
4757                                                          0>, VEX_4V;
4758   defm VPMINSD   : SS41I_binop_rm_int<0x39, "vpminsd",   int_x86_sse41_pminsd,
4759                                                          0>, VEX_4V;
4760   defm VPMINUD   : SS41I_binop_rm_int<0x3B, "vpminud",   int_x86_sse41_pminud,
4761                                                          0>, VEX_4V;
4762   defm VPMINUW   : SS41I_binop_rm_int<0x3A, "vpminuw",   int_x86_sse41_pminuw,
4763                                                          0>, VEX_4V;
4764   defm VPMAXSB   : SS41I_binop_rm_int<0x3C, "vpmaxsb",   int_x86_sse41_pmaxsb,
4765                                                          0>, VEX_4V;
4766   defm VPMAXSD   : SS41I_binop_rm_int<0x3D, "vpmaxsd",   int_x86_sse41_pmaxsd,
4767                                                          0>, VEX_4V;
4768   defm VPMAXUD   : SS41I_binop_rm_int<0x3F, "vpmaxud",   int_x86_sse41_pmaxud,
4769                                                          0>, VEX_4V;
4770   defm VPMAXUW   : SS41I_binop_rm_int<0x3E, "vpmaxuw",   int_x86_sse41_pmaxuw,
4771                                                          0>, VEX_4V;
4772   defm VPMULDQ   : SS41I_binop_rm_int<0x28, "vpmuldq",   int_x86_sse41_pmuldq,
4773                                                          0>, VEX_4V;
4774 }
4775
4776 let Constraints = "$src1 = $dst" in {
4777   let isCommutable = 0 in
4778   defm PACKUSDW : SS41I_binop_rm_int<0x2B, "packusdw", int_x86_sse41_packusdw>;
4779   defm PCMPEQQ  : SS41I_binop_rm_int<0x29, "pcmpeqq",  int_x86_sse41_pcmpeqq>;
4780   defm PMINSB   : SS41I_binop_rm_int<0x38, "pminsb",   int_x86_sse41_pminsb>;
4781   defm PMINSD   : SS41I_binop_rm_int<0x39, "pminsd",   int_x86_sse41_pminsd>;
4782   defm PMINUD   : SS41I_binop_rm_int<0x3B, "pminud",   int_x86_sse41_pminud>;
4783   defm PMINUW   : SS41I_binop_rm_int<0x3A, "pminuw",   int_x86_sse41_pminuw>;
4784   defm PMAXSB   : SS41I_binop_rm_int<0x3C, "pmaxsb",   int_x86_sse41_pmaxsb>;
4785   defm PMAXSD   : SS41I_binop_rm_int<0x3D, "pmaxsd",   int_x86_sse41_pmaxsd>;
4786   defm PMAXUD   : SS41I_binop_rm_int<0x3F, "pmaxud",   int_x86_sse41_pmaxud>;
4787   defm PMAXUW   : SS41I_binop_rm_int<0x3E, "pmaxuw",   int_x86_sse41_pmaxuw>;
4788   defm PMULDQ   : SS41I_binop_rm_int<0x28, "pmuldq",   int_x86_sse41_pmuldq>;
4789 }
4790
4791 def : Pat<(v2i64 (X86pcmpeqq VR128:$src1, VR128:$src2)),
4792           (PCMPEQQrr VR128:$src1, VR128:$src2)>;
4793 def : Pat<(v2i64 (X86pcmpeqq VR128:$src1, (memop addr:$src2))),
4794           (PCMPEQQrm VR128:$src1, addr:$src2)>;
4795
4796 /// SS48I_binop_rm - Simple SSE41 binary operator.
4797 multiclass SS48I_binop_rm<bits<8> opc, string OpcodeStr, SDNode OpNode,
4798                         ValueType OpVT, bit Is2Addr = 1> {
4799   let isCommutable = 1 in
4800   def rr : SS48I<opc, MRMSrcReg, (outs VR128:$dst),
4801        (ins VR128:$src1, VR128:$src2),
4802        !if(Is2Addr,
4803            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
4804            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
4805        [(set VR128:$dst, (OpVT (OpNode VR128:$src1, VR128:$src2)))]>,
4806        OpSize;
4807   def rm : SS48I<opc, MRMSrcMem, (outs VR128:$dst),
4808        (ins VR128:$src1, i128mem:$src2),
4809        !if(Is2Addr,
4810            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
4811            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
4812        [(set VR128:$dst, (OpNode VR128:$src1,
4813                                   (bc_v4i32 (memopv2i64 addr:$src2))))]>,
4814        OpSize;
4815 }
4816
4817 let isAsmParserOnly = 1, Predicates = [HasAVX] in
4818   defm VPMULLD : SS48I_binop_rm<0x40, "vpmulld", mul, v4i32, 0>, VEX_4V;
4819 let Constraints = "$src1 = $dst" in
4820   defm PMULLD : SS48I_binop_rm<0x40, "pmulld", mul, v4i32>;
4821
4822 /// SS41I_binop_rmi_int - SSE 4.1 binary operator with 8-bit immediate
4823 multiclass SS41I_binop_rmi_int<bits<8> opc, string OpcodeStr,
4824                  Intrinsic IntId, RegisterClass RC, PatFrag memop_frag,
4825                  X86MemOperand x86memop, bit Is2Addr = 1> {
4826   let isCommutable = 1 in
4827   def rri : SS4AIi8<opc, MRMSrcReg, (outs RC:$dst),
4828         (ins RC:$src1, RC:$src2, i32i8imm:$src3),
4829         !if(Is2Addr,
4830             !strconcat(OpcodeStr,
4831                 "\t{$src3, $src2, $dst|$dst, $src2, $src3}"),
4832             !strconcat(OpcodeStr,
4833                 "\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}")),
4834         [(set RC:$dst, (IntId RC:$src1, RC:$src2, imm:$src3))]>,
4835         OpSize;
4836   def rmi : SS4AIi8<opc, MRMSrcMem, (outs RC:$dst),
4837         (ins RC:$src1, x86memop:$src2, i32i8imm:$src3),
4838         !if(Is2Addr,
4839             !strconcat(OpcodeStr,
4840                 "\t{$src3, $src2, $dst|$dst, $src2, $src3}"),
4841             !strconcat(OpcodeStr,
4842                 "\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}")),
4843         [(set RC:$dst,
4844           (IntId RC:$src1,
4845            (bitconvert (memop_frag addr:$src2)), imm:$src3))]>,
4846         OpSize;
4847 }
4848
4849 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
4850   let isCommutable = 0 in {
4851   defm VBLENDPS : SS41I_binop_rmi_int<0x0C, "vblendps", int_x86_sse41_blendps,
4852                                       VR128, memopv16i8, i128mem, 0>, VEX_4V;
4853   defm VBLENDPD : SS41I_binop_rmi_int<0x0D, "vblendpd", int_x86_sse41_blendpd,
4854                                       VR128, memopv16i8, i128mem, 0>, VEX_4V;
4855   defm VBLENDPSY : SS41I_binop_rmi_int<0x0C, "vblendps",
4856             int_x86_avx_blend_ps_256, VR256, memopv32i8, i256mem, 0>, VEX_4V;
4857   defm VBLENDPDY : SS41I_binop_rmi_int<0x0D, "vblendpd",
4858             int_x86_avx_blend_pd_256, VR256, memopv32i8, i256mem, 0>, VEX_4V;
4859   defm VPBLENDW : SS41I_binop_rmi_int<0x0E, "vpblendw", int_x86_sse41_pblendw,
4860                                       VR128, memopv16i8, i128mem, 0>, VEX_4V;
4861   defm VMPSADBW : SS41I_binop_rmi_int<0x42, "vmpsadbw", int_x86_sse41_mpsadbw,
4862                                       VR128, memopv16i8, i128mem, 0>, VEX_4V;
4863   }
4864   defm VDPPS : SS41I_binop_rmi_int<0x40, "vdpps", int_x86_sse41_dpps,
4865                                    VR128, memopv16i8, i128mem, 0>, VEX_4V;
4866   defm VDPPD : SS41I_binop_rmi_int<0x41, "vdppd", int_x86_sse41_dppd,
4867                                    VR128, memopv16i8, i128mem, 0>, VEX_4V;
4868   defm VDPPSY : SS41I_binop_rmi_int<0x40, "vdpps", int_x86_avx_dp_ps_256,
4869                                    VR256, memopv32i8, i256mem, 0>, VEX_4V;
4870 }
4871
4872 let Constraints = "$src1 = $dst" in {
4873   let isCommutable = 0 in {
4874   defm BLENDPS : SS41I_binop_rmi_int<0x0C, "blendps", int_x86_sse41_blendps,
4875                                      VR128, memopv16i8, i128mem>;
4876   defm BLENDPD : SS41I_binop_rmi_int<0x0D, "blendpd", int_x86_sse41_blendpd,
4877                                      VR128, memopv16i8, i128mem>;
4878   defm PBLENDW : SS41I_binop_rmi_int<0x0E, "pblendw", int_x86_sse41_pblendw,
4879                                      VR128, memopv16i8, i128mem>;
4880   defm MPSADBW : SS41I_binop_rmi_int<0x42, "mpsadbw", int_x86_sse41_mpsadbw,
4881                                      VR128, memopv16i8, i128mem>;
4882   }
4883   defm DPPS : SS41I_binop_rmi_int<0x40, "dpps", int_x86_sse41_dpps,
4884                                   VR128, memopv16i8, i128mem>;
4885   defm DPPD : SS41I_binop_rmi_int<0x41, "dppd", int_x86_sse41_dppd,
4886                                   VR128, memopv16i8, i128mem>;
4887 }
4888
4889 /// SS41I_quaternary_int_avx - AVX SSE 4.1 with 4 operators
4890 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
4891 multiclass SS41I_quaternary_int_avx<bits<8> opc, string OpcodeStr,
4892                                     RegisterClass RC, X86MemOperand x86memop,
4893                                     PatFrag mem_frag, Intrinsic IntId> {
4894   def rr : I<opc, MRMSrcReg, (outs RC:$dst),
4895                   (ins RC:$src1, RC:$src2, RC:$src3),
4896                   !strconcat(OpcodeStr,
4897                     "\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}"),
4898                   [(set RC:$dst, (IntId RC:$src1, RC:$src2, RC:$src3))],
4899                   SSEPackedInt>, OpSize, TA, VEX_4V, VEX_I8IMM;
4900
4901   def rm : I<opc, MRMSrcMem, (outs RC:$dst),
4902                   (ins RC:$src1, x86memop:$src2, RC:$src3),
4903                   !strconcat(OpcodeStr,
4904                     "\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}"),
4905                   [(set RC:$dst,
4906                         (IntId RC:$src1, (bitconvert (mem_frag addr:$src2)),
4907                                RC:$src3))],
4908                   SSEPackedInt>, OpSize, TA, VEX_4V, VEX_I8IMM;
4909 }
4910 }
4911
4912 defm VBLENDVPD  : SS41I_quaternary_int_avx<0x4B, "vblendvpd", VR128, i128mem,
4913                                            memopv16i8, int_x86_sse41_blendvpd>;
4914 defm VBLENDVPS  : SS41I_quaternary_int_avx<0x4A, "vblendvps", VR128, i128mem,
4915                                            memopv16i8, int_x86_sse41_blendvps>;
4916 defm VPBLENDVB  : SS41I_quaternary_int_avx<0x4C, "vpblendvb", VR128, i128mem,
4917                                            memopv16i8, int_x86_sse41_pblendvb>;
4918 defm VBLENDVPDY : SS41I_quaternary_int_avx<0x4B, "vblendvpd", VR256, i256mem,
4919                                          memopv32i8, int_x86_avx_blendv_pd_256>;
4920 defm VBLENDVPSY : SS41I_quaternary_int_avx<0x4A, "vblendvps", VR256, i256mem,
4921                                          memopv32i8, int_x86_avx_blendv_ps_256>;
4922
4923 /// SS41I_ternary_int - SSE 4.1 ternary operator
4924 let Uses = [XMM0], Constraints = "$src1 = $dst" in {
4925   multiclass SS41I_ternary_int<bits<8> opc, string OpcodeStr, Intrinsic IntId> {
4926     def rr0 : SS48I<opc, MRMSrcReg, (outs VR128:$dst),
4927                     (ins VR128:$src1, VR128:$src2),
4928                     !strconcat(OpcodeStr,
4929                      "\t{%xmm0, $src2, $dst|$dst, $src2, %xmm0}"),
4930                     [(set VR128:$dst, (IntId VR128:$src1, VR128:$src2, XMM0))]>,
4931                     OpSize;
4932
4933     def rm0 : SS48I<opc, MRMSrcMem, (outs VR128:$dst),
4934                     (ins VR128:$src1, i128mem:$src2),
4935                     !strconcat(OpcodeStr,
4936                      "\t{%xmm0, $src2, $dst|$dst, $src2, %xmm0}"),
4937                     [(set VR128:$dst,
4938                       (IntId VR128:$src1,
4939                        (bitconvert (memopv16i8 addr:$src2)), XMM0))]>, OpSize;
4940   }
4941 }
4942
4943 defm BLENDVPD     : SS41I_ternary_int<0x15, "blendvpd", int_x86_sse41_blendvpd>;
4944 defm BLENDVPS     : SS41I_ternary_int<0x14, "blendvps", int_x86_sse41_blendvps>;
4945 defm PBLENDVB     : SS41I_ternary_int<0x10, "pblendvb", int_x86_sse41_pblendvb>;
4946
4947 let isAsmParserOnly = 1, Predicates = [HasAVX] in
4948 def VMOVNTDQArm : SS48I<0x2A, MRMSrcMem, (outs VR128:$dst), (ins i128mem:$src),
4949                        "vmovntdqa\t{$src, $dst|$dst, $src}",
4950                        [(set VR128:$dst, (int_x86_sse41_movntdqa addr:$src))]>,
4951                        OpSize, VEX;
4952 def MOVNTDQArm : SS48I<0x2A, MRMSrcMem, (outs VR128:$dst), (ins i128mem:$src),
4953                        "movntdqa\t{$src, $dst|$dst, $src}",
4954                        [(set VR128:$dst, (int_x86_sse41_movntdqa addr:$src))]>,
4955                        OpSize;
4956
4957 //===----------------------------------------------------------------------===//
4958 // SSE4.2 - Compare Instructions
4959 //===----------------------------------------------------------------------===//
4960
4961 /// SS42I_binop_rm_int - Simple SSE 4.2 binary operator
4962 multiclass SS42I_binop_rm_int<bits<8> opc, string OpcodeStr,
4963                               Intrinsic IntId128, bit Is2Addr = 1> {
4964   def rr : SS428I<opc, MRMSrcReg, (outs VR128:$dst),
4965        (ins VR128:$src1, VR128:$src2),
4966        !if(Is2Addr,
4967            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
4968            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
4969        [(set VR128:$dst, (IntId128 VR128:$src1, VR128:$src2))]>,
4970        OpSize;
4971   def rm : SS428I<opc, MRMSrcMem, (outs VR128:$dst),
4972        (ins VR128:$src1, i128mem:$src2),
4973        !if(Is2Addr,
4974            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
4975            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
4976        [(set VR128:$dst,
4977          (IntId128 VR128:$src1,
4978           (bitconvert (memopv16i8 addr:$src2))))]>, OpSize;
4979 }
4980
4981 let isAsmParserOnly = 1, Predicates = [HasAVX] in
4982   defm VPCMPGTQ : SS42I_binop_rm_int<0x37, "vpcmpgtq", int_x86_sse42_pcmpgtq,
4983                                      0>, VEX_4V;
4984 let Constraints = "$src1 = $dst" in
4985   defm PCMPGTQ : SS42I_binop_rm_int<0x37, "pcmpgtq", int_x86_sse42_pcmpgtq>;
4986
4987 def : Pat<(v2i64 (X86pcmpgtq VR128:$src1, VR128:$src2)),
4988           (PCMPGTQrr VR128:$src1, VR128:$src2)>;
4989 def : Pat<(v2i64 (X86pcmpgtq VR128:$src1, (memop addr:$src2))),
4990           (PCMPGTQrm VR128:$src1, addr:$src2)>;
4991
4992 //===----------------------------------------------------------------------===//
4993 // SSE4.2 - String/text Processing Instructions
4994 //===----------------------------------------------------------------------===//
4995
4996 // Packed Compare Implicit Length Strings, Return Mask
4997 multiclass pseudo_pcmpistrm<string asm> {
4998   def REG : Ii8<0, Pseudo, (outs VR128:$dst),
4999     (ins VR128:$src1, VR128:$src2, i8imm:$src3), !strconcat(asm, "rr PSEUDO"),
5000     [(set VR128:$dst, (int_x86_sse42_pcmpistrm128 VR128:$src1, VR128:$src2,
5001                                                   imm:$src3))]>;
5002   def MEM : Ii8<0, Pseudo, (outs VR128:$dst),
5003     (ins VR128:$src1, i128mem:$src2, i8imm:$src3), !strconcat(asm, "rm PSEUDO"),
5004     [(set VR128:$dst, (int_x86_sse42_pcmpistrm128
5005                        VR128:$src1, (load addr:$src2), imm:$src3))]>;
5006 }
5007
5008 let Defs = [EFLAGS], usesCustomInserter = 1 in {
5009   defm PCMPISTRM128 : pseudo_pcmpistrm<"#PCMPISTRM128">, Requires<[HasSSE42]>;
5010   defm VPCMPISTRM128 : pseudo_pcmpistrm<"#VPCMPISTRM128">, Requires<[HasAVX]>;
5011 }
5012
5013 let Defs = [XMM0, EFLAGS], isAsmParserOnly = 1,
5014     Predicates = [HasAVX] in {
5015   def VPCMPISTRM128rr : SS42AI<0x62, MRMSrcReg, (outs),
5016       (ins VR128:$src1, VR128:$src2, i8imm:$src3),
5017       "vpcmpistrm\t{$src3, $src2, $src1|$src1, $src2, $src3}", []>, OpSize, VEX;
5018   def VPCMPISTRM128rm : SS42AI<0x62, MRMSrcMem, (outs),
5019       (ins VR128:$src1, i128mem:$src2, i8imm:$src3),
5020       "vpcmpistrm\t{$src3, $src2, $src1|$src1, $src2, $src3}", []>, OpSize, VEX;
5021 }
5022
5023 let Defs = [XMM0, EFLAGS] in {
5024   def PCMPISTRM128rr : SS42AI<0x62, MRMSrcReg, (outs),
5025       (ins VR128:$src1, VR128:$src2, i8imm:$src3),
5026       "pcmpistrm\t{$src3, $src2, $src1|$src1, $src2, $src3}", []>, OpSize;
5027   def PCMPISTRM128rm : SS42AI<0x62, MRMSrcMem, (outs),
5028       (ins VR128:$src1, i128mem:$src2, i8imm:$src3),
5029       "pcmpistrm\t{$src3, $src2, $src1|$src1, $src2, $src3}", []>, OpSize;
5030 }
5031
5032 // Packed Compare Explicit Length Strings, Return Mask
5033 multiclass pseudo_pcmpestrm<string asm> {
5034   def REG : Ii8<0, Pseudo, (outs VR128:$dst),
5035     (ins VR128:$src1, VR128:$src3, i8imm:$src5), !strconcat(asm, "rr PSEUDO"),
5036     [(set VR128:$dst, (int_x86_sse42_pcmpestrm128
5037                        VR128:$src1, EAX, VR128:$src3, EDX, imm:$src5))]>;
5038   def MEM : Ii8<0, Pseudo, (outs VR128:$dst),
5039     (ins VR128:$src1, i128mem:$src3, i8imm:$src5), !strconcat(asm, "rm PSEUDO"),
5040     [(set VR128:$dst, (int_x86_sse42_pcmpestrm128
5041                        VR128:$src1, EAX, (load addr:$src3), EDX, imm:$src5))]>;
5042 }
5043
5044 let Defs = [EFLAGS], Uses = [EAX, EDX], usesCustomInserter = 1 in {
5045   defm PCMPESTRM128 : pseudo_pcmpestrm<"#PCMPESTRM128">, Requires<[HasSSE42]>;
5046   defm VPCMPESTRM128 : pseudo_pcmpestrm<"#VPCMPESTRM128">, Requires<[HasAVX]>;
5047 }
5048
5049 let isAsmParserOnly = 1, Predicates = [HasAVX],
5050     Defs = [XMM0, EFLAGS], Uses = [EAX, EDX] in {
5051   def VPCMPESTRM128rr : SS42AI<0x60, MRMSrcReg, (outs),
5052       (ins VR128:$src1, VR128:$src3, i8imm:$src5),
5053       "vpcmpestrm\t{$src5, $src3, $src1|$src1, $src3, $src5}", []>, OpSize, VEX;
5054   def VPCMPESTRM128rm : SS42AI<0x60, MRMSrcMem, (outs),
5055       (ins VR128:$src1, i128mem:$src3, i8imm:$src5),
5056       "vpcmpestrm\t{$src5, $src3, $src1|$src1, $src3, $src5}", []>, OpSize, VEX;
5057 }
5058
5059 let Defs = [XMM0, EFLAGS], Uses = [EAX, EDX] in {
5060   def PCMPESTRM128rr : SS42AI<0x60, MRMSrcReg, (outs),
5061       (ins VR128:$src1, VR128:$src3, i8imm:$src5),
5062       "pcmpestrm\t{$src5, $src3, $src1|$src1, $src3, $src5}", []>, OpSize;
5063   def PCMPESTRM128rm : SS42AI<0x60, MRMSrcMem, (outs),
5064       (ins VR128:$src1, i128mem:$src3, i8imm:$src5),
5065       "pcmpestrm\t{$src5, $src3, $src1|$src1, $src3, $src5}", []>, OpSize;
5066 }
5067
5068 // Packed Compare Implicit Length Strings, Return Index
5069 let Defs = [ECX, EFLAGS] in {
5070   multiclass SS42AI_pcmpistri<Intrinsic IntId128, string asm = "pcmpistri"> {
5071     def rr : SS42AI<0x63, MRMSrcReg, (outs),
5072       (ins VR128:$src1, VR128:$src2, i8imm:$src3),
5073       !strconcat(asm, "\t{$src3, $src2, $src1|$src1, $src2, $src3}"),
5074       [(set ECX, (IntId128 VR128:$src1, VR128:$src2, imm:$src3)),
5075        (implicit EFLAGS)]>, OpSize;
5076     def rm : SS42AI<0x63, MRMSrcMem, (outs),
5077       (ins VR128:$src1, i128mem:$src2, i8imm:$src3),
5078       !strconcat(asm, "\t{$src3, $src2, $src1|$src1, $src2, $src3}"),
5079       [(set ECX, (IntId128 VR128:$src1, (load addr:$src2), imm:$src3)),
5080        (implicit EFLAGS)]>, OpSize;
5081   }
5082 }
5083
5084 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
5085 defm VPCMPISTRI  : SS42AI_pcmpistri<int_x86_sse42_pcmpistri128, "vpcmpistri">,
5086                                     VEX;
5087 defm VPCMPISTRIA : SS42AI_pcmpistri<int_x86_sse42_pcmpistria128, "vpcmpistri">,
5088                                     VEX;
5089 defm VPCMPISTRIC : SS42AI_pcmpistri<int_x86_sse42_pcmpistric128, "vpcmpistri">,
5090                                     VEX;
5091 defm VPCMPISTRIO : SS42AI_pcmpistri<int_x86_sse42_pcmpistrio128, "vpcmpistri">,
5092                                     VEX;
5093 defm VPCMPISTRIS : SS42AI_pcmpistri<int_x86_sse42_pcmpistris128, "vpcmpistri">,
5094                                     VEX;
5095 defm VPCMPISTRIZ : SS42AI_pcmpistri<int_x86_sse42_pcmpistriz128, "vpcmpistri">,
5096                                     VEX;
5097 }
5098
5099 defm PCMPISTRI  : SS42AI_pcmpistri<int_x86_sse42_pcmpistri128>;
5100 defm PCMPISTRIA : SS42AI_pcmpistri<int_x86_sse42_pcmpistria128>;
5101 defm PCMPISTRIC : SS42AI_pcmpistri<int_x86_sse42_pcmpistric128>;
5102 defm PCMPISTRIO : SS42AI_pcmpistri<int_x86_sse42_pcmpistrio128>;
5103 defm PCMPISTRIS : SS42AI_pcmpistri<int_x86_sse42_pcmpistris128>;
5104 defm PCMPISTRIZ : SS42AI_pcmpistri<int_x86_sse42_pcmpistriz128>;
5105
5106 // Packed Compare Explicit Length Strings, Return Index
5107 let Defs = [ECX, EFLAGS], Uses = [EAX, EDX] in {
5108   multiclass SS42AI_pcmpestri<Intrinsic IntId128, string asm = "pcmpestri"> {
5109     def rr : SS42AI<0x61, MRMSrcReg, (outs),
5110       (ins VR128:$src1, VR128:$src3, i8imm:$src5),
5111       !strconcat(asm, "\t{$src5, $src3, $src1|$src1, $src3, $src5}"),
5112       [(set ECX, (IntId128 VR128:$src1, EAX, VR128:$src3, EDX, imm:$src5)),
5113        (implicit EFLAGS)]>, OpSize;
5114     def rm : SS42AI<0x61, MRMSrcMem, (outs),
5115       (ins VR128:$src1, i128mem:$src3, i8imm:$src5),
5116       !strconcat(asm, "\t{$src5, $src3, $src1|$src1, $src3, $src5}"),
5117        [(set ECX,
5118              (IntId128 VR128:$src1, EAX, (load addr:$src3), EDX, imm:$src5)),
5119         (implicit EFLAGS)]>, OpSize;
5120   }
5121 }
5122
5123 let isAsmParserOnly = 1, Predicates = [HasAVX] in {
5124 defm VPCMPESTRI  : SS42AI_pcmpestri<int_x86_sse42_pcmpestri128, "vpcmpestri">,
5125                                     VEX;
5126 defm VPCMPESTRIA : SS42AI_pcmpestri<int_x86_sse42_pcmpestria128, "vpcmpestri">,
5127                                     VEX;
5128 defm VPCMPESTRIC : SS42AI_pcmpestri<int_x86_sse42_pcmpestric128, "vpcmpestri">,
5129                                     VEX;
5130 defm VPCMPESTRIO : SS42AI_pcmpestri<int_x86_sse42_pcmpestrio128, "vpcmpestri">,
5131                                     VEX;
5132 defm VPCMPESTRIS : SS42AI_pcmpestri<int_x86_sse42_pcmpestris128, "vpcmpestri">,
5133                                     VEX;
5134 defm VPCMPESTRIZ : SS42AI_pcmpestri<int_x86_sse42_pcmpestriz128, "vpcmpestri">,
5135                                     VEX;
5136 }
5137
5138 defm PCMPESTRI  : SS42AI_pcmpestri<int_x86_sse42_pcmpestri128>;
5139 defm PCMPESTRIA : SS42AI_pcmpestri<int_x86_sse42_pcmpestria128>;
5140 defm PCMPESTRIC : SS42AI_pcmpestri<int_x86_sse42_pcmpestric128>;
5141 defm PCMPESTRIO : SS42AI_pcmpestri<int_x86_sse42_pcmpestrio128>;
5142 defm PCMPESTRIS : SS42AI_pcmpestri<int_x86_sse42_pcmpestris128>;
5143 defm PCMPESTRIZ : SS42AI_pcmpestri<int_x86_sse42_pcmpestriz128>;
5144
5145 //===----------------------------------------------------------------------===//
5146 // SSE4.2 - CRC Instructions
5147 //===----------------------------------------------------------------------===//
5148
5149 // No CRC instructions have AVX equivalents
5150
5151 // crc intrinsic instruction
5152 // This set of instructions are only rm, the only difference is the size
5153 // of r and m.
5154 let Constraints = "$src1 = $dst" in {
5155   def CRC32m8  : SS42FI<0xF0, MRMSrcMem, (outs GR32:$dst),
5156                       (ins GR32:$src1, i8mem:$src2),
5157                       "crc32{b} \t{$src2, $src1|$src1, $src2}",
5158                        [(set GR32:$dst,
5159                          (int_x86_sse42_crc32_8 GR32:$src1,
5160                          (load addr:$src2)))]>;
5161   def CRC32r8  : SS42FI<0xF0, MRMSrcReg, (outs GR32:$dst),
5162                       (ins GR32:$src1, GR8:$src2),
5163                       "crc32{b} \t{$src2, $src1|$src1, $src2}",
5164                        [(set GR32:$dst,
5165                          (int_x86_sse42_crc32_8 GR32:$src1, GR8:$src2))]>;
5166   def CRC32m16  : SS42FI<0xF1, MRMSrcMem, (outs GR32:$dst),
5167                       (ins GR32:$src1, i16mem:$src2),
5168                       "crc32{w} \t{$src2, $src1|$src1, $src2}",
5169                        [(set GR32:$dst,
5170                          (int_x86_sse42_crc32_16 GR32:$src1,
5171                          (load addr:$src2)))]>,
5172                          OpSize;
5173   def CRC32r16  : SS42FI<0xF1, MRMSrcReg, (outs GR32:$dst),
5174                       (ins GR32:$src1, GR16:$src2),
5175                       "crc32{w} \t{$src2, $src1|$src1, $src2}",
5176                        [(set GR32:$dst,
5177                          (int_x86_sse42_crc32_16 GR32:$src1, GR16:$src2))]>,
5178                          OpSize;
5179   def CRC32m32  : SS42FI<0xF1, MRMSrcMem, (outs GR32:$dst),
5180                       (ins GR32:$src1, i32mem:$src2),
5181                       "crc32{l} \t{$src2, $src1|$src1, $src2}",
5182                        [(set GR32:$dst,
5183                          (int_x86_sse42_crc32_32 GR32:$src1,
5184                          (load addr:$src2)))]>;
5185   def CRC32r32  : SS42FI<0xF1, MRMSrcReg, (outs GR32:$dst),
5186                       (ins GR32:$src1, GR32:$src2),
5187                       "crc32{l} \t{$src2, $src1|$src1, $src2}",
5188                        [(set GR32:$dst,
5189                          (int_x86_sse42_crc32_32 GR32:$src1, GR32:$src2))]>;
5190   def CRC64m8  : SS42FI<0xF0, MRMSrcMem, (outs GR64:$dst),
5191                       (ins GR64:$src1, i8mem:$src2),
5192                       "crc32{b} \t{$src2, $src1|$src1, $src2}",
5193                        [(set GR64:$dst,
5194                          (int_x86_sse42_crc64_8 GR64:$src1,
5195                          (load addr:$src2)))]>,
5196                          REX_W;
5197   def CRC64r8  : SS42FI<0xF0, MRMSrcReg, (outs GR64:$dst),
5198                       (ins GR64:$src1, GR8:$src2),
5199                       "crc32{b} \t{$src2, $src1|$src1, $src2}",
5200                        [(set GR64:$dst,
5201                          (int_x86_sse42_crc64_8 GR64:$src1, GR8:$src2))]>,
5202                          REX_W;
5203   def CRC64m64  : SS42FI<0xF1, MRMSrcMem, (outs GR64:$dst),
5204                       (ins GR64:$src1, i64mem:$src2),
5205                       "crc32{q} \t{$src2, $src1|$src1, $src2}",
5206                        [(set GR64:$dst,
5207                          (int_x86_sse42_crc64_64 GR64:$src1,
5208                          (load addr:$src2)))]>,
5209                          REX_W;
5210   def CRC64r64  : SS42FI<0xF1, MRMSrcReg, (outs GR64:$dst),
5211                       (ins GR64:$src1, GR64:$src2),
5212                       "crc32{q} \t{$src2, $src1|$src1, $src2}",
5213                        [(set GR64:$dst,
5214                          (int_x86_sse42_crc64_64 GR64:$src1, GR64:$src2))]>,
5215                          REX_W;
5216 }
5217
5218 //===----------------------------------------------------------------------===//
5219 // AES-NI Instructions
5220 //===----------------------------------------------------------------------===//
5221
5222 multiclass AESI_binop_rm_int<bits<8> opc, string OpcodeStr,
5223                               Intrinsic IntId128, bit Is2Addr = 1> {
5224   def rr : AES8I<opc, MRMSrcReg, (outs VR128:$dst),
5225        (ins VR128:$src1, VR128:$src2),
5226        !if(Is2Addr,
5227            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
5228            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
5229        [(set VR128:$dst, (IntId128 VR128:$src1, VR128:$src2))]>,
5230        OpSize;
5231   def rm : AES8I<opc, MRMSrcMem, (outs VR128:$dst),
5232        (ins VR128:$src1, i128mem:$src2),
5233        !if(Is2Addr,
5234            !strconcat(OpcodeStr, "\t{$src2, $dst|$dst, $src2}"),
5235            !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}")),
5236        [(set VR128:$dst,
5237          (IntId128 VR128:$src1,
5238           (bitconvert (memopv16i8 addr:$src2))))]>, OpSize;
5239 }
5240
5241 // Perform One Round of an AES Encryption/Decryption Flow
5242 let isAsmParserOnly = 1, Predicates = [HasAVX, HasAES] in {
5243   defm VAESENC          : AESI_binop_rm_int<0xDC, "vaesenc",
5244                          int_x86_aesni_aesenc, 0>, VEX_4V;
5245   defm VAESENCLAST      : AESI_binop_rm_int<0xDD, "vaesenclast",
5246                          int_x86_aesni_aesenclast, 0>, VEX_4V;
5247   defm VAESDEC          : AESI_binop_rm_int<0xDE, "vaesdec",
5248                          int_x86_aesni_aesdec, 0>, VEX_4V;
5249   defm VAESDECLAST      : AESI_binop_rm_int<0xDF, "vaesdeclast",
5250                          int_x86_aesni_aesdeclast, 0>, VEX_4V;
5251 }
5252
5253 let Constraints = "$src1 = $dst" in {
5254   defm AESENC          : AESI_binop_rm_int<0xDC, "aesenc",
5255                          int_x86_aesni_aesenc>;
5256   defm AESENCLAST      : AESI_binop_rm_int<0xDD, "aesenclast",
5257                          int_x86_aesni_aesenclast>;
5258   defm AESDEC          : AESI_binop_rm_int<0xDE, "aesdec",
5259                          int_x86_aesni_aesdec>;
5260   defm AESDECLAST      : AESI_binop_rm_int<0xDF, "aesdeclast",
5261                          int_x86_aesni_aesdeclast>;
5262 }
5263
5264 def : Pat<(v2i64 (int_x86_aesni_aesenc VR128:$src1, VR128:$src2)),
5265           (AESENCrr VR128:$src1, VR128:$src2)>;
5266 def : Pat<(v2i64 (int_x86_aesni_aesenc VR128:$src1, (memop addr:$src2))),
5267           (AESENCrm VR128:$src1, addr:$src2)>;
5268 def : Pat<(v2i64 (int_x86_aesni_aesenclast VR128:$src1, VR128:$src2)),
5269           (AESENCLASTrr VR128:$src1, VR128:$src2)>;
5270 def : Pat<(v2i64 (int_x86_aesni_aesenclast VR128:$src1, (memop addr:$src2))),
5271           (AESENCLASTrm VR128:$src1, addr:$src2)>;
5272 def : Pat<(v2i64 (int_x86_aesni_aesdec VR128:$src1, VR128:$src2)),
5273           (AESDECrr VR128:$src1, VR128:$src2)>;
5274 def : Pat<(v2i64 (int_x86_aesni_aesdec VR128:$src1, (memop addr:$src2))),
5275           (AESDECrm VR128:$src1, addr:$src2)>;
5276 def : Pat<(v2i64 (int_x86_aesni_aesdeclast VR128:$src1, VR128:$src2)),
5277           (AESDECLASTrr VR128:$src1, VR128:$src2)>;
5278 def : Pat<(v2i64 (int_x86_aesni_aesdeclast VR128:$src1, (memop addr:$src2))),
5279           (AESDECLASTrm VR128:$src1, addr:$src2)>;
5280
5281 // Perform the AES InvMixColumn Transformation
5282 let isAsmParserOnly = 1, Predicates = [HasAVX, HasAES] in {
5283   def VAESIMCrr : AES8I<0xDB, MRMSrcReg, (outs VR128:$dst),
5284       (ins VR128:$src1),
5285       "vaesimc\t{$src1, $dst|$dst, $src1}",
5286       [(set VR128:$dst,
5287         (int_x86_aesni_aesimc VR128:$src1))]>,
5288       OpSize, VEX;
5289   def VAESIMCrm : AES8I<0xDB, MRMSrcMem, (outs VR128:$dst),
5290       (ins i128mem:$src1),
5291       "vaesimc\t{$src1, $dst|$dst, $src1}",
5292       [(set VR128:$dst,
5293         (int_x86_aesni_aesimc (bitconvert (memopv2i64 addr:$src1))))]>,
5294       OpSize, VEX;
5295 }
5296 def AESIMCrr : AES8I<0xDB, MRMSrcReg, (outs VR128:$dst),
5297   (ins VR128:$src1),
5298   "aesimc\t{$src1, $dst|$dst, $src1}",
5299   [(set VR128:$dst,
5300     (int_x86_aesni_aesimc VR128:$src1))]>,
5301   OpSize;
5302 def AESIMCrm : AES8I<0xDB, MRMSrcMem, (outs VR128:$dst),
5303   (ins i128mem:$src1),
5304   "aesimc\t{$src1, $dst|$dst, $src1}",
5305   [(set VR128:$dst,
5306     (int_x86_aesni_aesimc (bitconvert (memopv2i64 addr:$src1))))]>,
5307   OpSize;
5308
5309 // AES Round Key Generation Assist
5310 let isAsmParserOnly = 1, Predicates = [HasAVX, HasAES] in {
5311   def VAESKEYGENASSIST128rr : AESAI<0xDF, MRMSrcReg, (outs VR128:$dst),
5312       (ins VR128:$src1, i8imm:$src2),
5313       "vaeskeygenassist\t{$src2, $src1, $dst|$dst, $src1, $src2}",
5314       [(set VR128:$dst,
5315         (int_x86_aesni_aeskeygenassist VR128:$src1, imm:$src2))]>,
5316       OpSize, VEX;
5317   def VAESKEYGENASSIST128rm : AESAI<0xDF, MRMSrcMem, (outs VR128:$dst),
5318       (ins i128mem:$src1, i8imm:$src2),
5319       "vaeskeygenassist\t{$src2, $src1, $dst|$dst, $src1, $src2}",
5320       [(set VR128:$dst,
5321         (int_x86_aesni_aeskeygenassist (bitconvert (memopv2i64 addr:$src1)),
5322                                         imm:$src2))]>,
5323       OpSize, VEX;
5324 }
5325 def AESKEYGENASSIST128rr : AESAI<0xDF, MRMSrcReg, (outs VR128:$dst),
5326   (ins VR128:$src1, i8imm:$src2),
5327   "aeskeygenassist\t{$src2, $src1, $dst|$dst, $src1, $src2}",
5328   [(set VR128:$dst,
5329     (int_x86_aesni_aeskeygenassist VR128:$src1, imm:$src2))]>,
5330   OpSize;
5331 def AESKEYGENASSIST128rm : AESAI<0xDF, MRMSrcMem, (outs VR128:$dst),
5332   (ins i128mem:$src1, i8imm:$src2),
5333   "aeskeygenassist\t{$src2, $src1, $dst|$dst, $src1, $src2}",
5334   [(set VR128:$dst,
5335     (int_x86_aesni_aeskeygenassist (bitconvert (memopv2i64 addr:$src1)),
5336                                     imm:$src2))]>,
5337   OpSize;
5338
5339 //===----------------------------------------------------------------------===//
5340 // CLMUL Instructions
5341 //===----------------------------------------------------------------------===//
5342
5343 // Only the AVX version of CLMUL instructions are described here.
5344
5345 // Carry-less Multiplication instructions
5346 let isAsmParserOnly = 1 in {
5347 def VPCLMULQDQrr : CLMULIi8<0x44, MRMSrcReg, (outs VR128:$dst),
5348            (ins VR128:$src1, VR128:$src2, i8imm:$src3),
5349            "vpclmulqdq\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}",
5350            []>;
5351
5352 def VPCLMULQDQrm : CLMULIi8<0x44, MRMSrcMem, (outs VR128:$dst),
5353            (ins VR128:$src1, i128mem:$src2, i8imm:$src3),
5354            "vpclmulqdq\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}",
5355            []>;
5356
5357 // Assembler Only
5358 multiclass avx_vpclmul<string asm> {
5359   def rr : I<0, Pseudo, (outs VR128:$dst), (ins VR128:$src1, VR128:$src2),
5360              !strconcat(asm, "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
5361              []>;
5362
5363   def rm : I<0, Pseudo, (outs VR128:$dst), (ins VR128:$src1, i128mem:$src2),
5364              !strconcat(asm, "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
5365              []>;
5366 }
5367 defm VPCLMULHQHQDQ : avx_vpclmul<"vpclmulhqhqdq">;
5368 defm VPCLMULHQLQDQ : avx_vpclmul<"vpclmulhqlqdq">;
5369 defm VPCLMULLQHQDQ : avx_vpclmul<"vpclmullqhqdq">;
5370 defm VPCLMULLQLQDQ : avx_vpclmul<"vpclmullqlqdq">;
5371
5372 } // isAsmParserOnly
5373
5374 //===----------------------------------------------------------------------===//
5375 // AVX Instructions
5376 //===----------------------------------------------------------------------===//
5377
5378 let isAsmParserOnly = 1 in {
5379
5380 // Load from memory and broadcast to all elements of the destination operand
5381 class avx_broadcast<bits<8> opc, string OpcodeStr, RegisterClass RC,
5382                     X86MemOperand x86memop, Intrinsic Int> :
5383   AVX8I<opc, MRMSrcMem, (outs RC:$dst), (ins x86memop:$src),
5384         !strconcat(OpcodeStr, "\t{$src, $dst|$dst, $src}"),
5385         [(set RC:$dst, (Int addr:$src))]>, VEX;
5386
5387 def VBROADCASTSS   : avx_broadcast<0x18, "vbroadcastss", VR128, f32mem,
5388                                    int_x86_avx_vbroadcastss>;
5389 def VBROADCASTSSY  : avx_broadcast<0x18, "vbroadcastss", VR256, f32mem,
5390                                    int_x86_avx_vbroadcastss_256>;
5391 def VBROADCASTSD   : avx_broadcast<0x19, "vbroadcastsd", VR256, f64mem,
5392                                    int_x86_avx_vbroadcast_sd_256>;
5393 def VBROADCASTF128 : avx_broadcast<0x1A, "vbroadcastf128", VR256, f128mem,
5394                                    int_x86_avx_vbroadcastf128_pd_256>;
5395
5396 // Insert packed floating-point values
5397 def VINSERTF128rr : AVXAIi8<0x18, MRMSrcReg, (outs VR256:$dst),
5398           (ins VR256:$src1, VR128:$src2, i8imm:$src3),
5399           "vinsertf128\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}",
5400           []>, VEX_4V;
5401 def VINSERTF128rm : AVXAIi8<0x18, MRMSrcMem, (outs VR256:$dst),
5402           (ins VR256:$src1, f128mem:$src2, i8imm:$src3),
5403           "vinsertf128\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}",
5404           []>, VEX_4V;
5405
5406 // Extract packed floating-point values
5407 def VEXTRACTF128rr : AVXAIi8<0x19, MRMDestReg, (outs VR128:$dst),
5408           (ins VR256:$src1, i8imm:$src2),
5409           "vextractf128\t{$src2, $src1, $dst|$dst, $src1, $src2}",
5410           []>, VEX;
5411 def VEXTRACTF128mr : AVXAIi8<0x19, MRMDestMem, (outs),
5412           (ins f128mem:$dst, VR256:$src1, i8imm:$src2),
5413           "vextractf128\t{$src2, $src1, $dst|$dst, $src1, $src2}",
5414           []>, VEX;
5415
5416 // Conditional SIMD Packed Loads and Stores
5417 multiclass avx_movmask_rm<bits<8> opc_rm, bits<8> opc_mr, string OpcodeStr,
5418                           Intrinsic IntLd, Intrinsic IntLd256,
5419                           Intrinsic IntSt, Intrinsic IntSt256,
5420                           PatFrag pf128, PatFrag pf256> {
5421   def rm  : AVX8I<opc_rm, MRMSrcMem, (outs VR128:$dst),
5422              (ins VR128:$src1, f128mem:$src2),
5423              !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
5424              [(set VR128:$dst, (IntLd addr:$src2, VR128:$src1))]>,
5425              VEX_4V;
5426   def Yrm : AVX8I<opc_rm, MRMSrcMem, (outs VR256:$dst),
5427              (ins VR256:$src1, f256mem:$src2),
5428              !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
5429              [(set VR256:$dst, (IntLd256 addr:$src2, VR256:$src1))]>,
5430              VEX_4V;
5431   def mr  : AVX8I<opc_mr, MRMDestMem, (outs),
5432              (ins f128mem:$dst, VR128:$src1, VR128:$src2),
5433              !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
5434              [(IntSt addr:$dst, VR128:$src1, VR128:$src2)]>, VEX_4V;
5435   def Ymr : AVX8I<opc_mr, MRMDestMem, (outs),
5436              (ins f256mem:$dst, VR256:$src1, VR256:$src2),
5437              !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
5438              [(IntSt256 addr:$dst, VR256:$src1, VR256:$src2)]>, VEX_4V;
5439 }
5440
5441 defm VMASKMOVPS : avx_movmask_rm<0x2C, 0x2E, "vmaskmovps",
5442                                  int_x86_avx_maskload_ps,
5443                                  int_x86_avx_maskload_ps_256,
5444                                  int_x86_avx_maskstore_ps,
5445                                  int_x86_avx_maskstore_ps_256,
5446                                  memopv4f32, memopv8f32>;
5447 defm VMASKMOVPD : avx_movmask_rm<0x2D, 0x2F, "vmaskmovpd",
5448                                  int_x86_avx_maskload_pd,
5449                                  int_x86_avx_maskload_pd_256,
5450                                  int_x86_avx_maskstore_pd,
5451                                  int_x86_avx_maskstore_pd_256,
5452                                  memopv2f64, memopv4f64>;
5453
5454 // Permute Floating-Point Values
5455 multiclass avx_permil<bits<8> opc_rm, bits<8> opc_rmi, string OpcodeStr,
5456                       RegisterClass RC, X86MemOperand x86memop_f,
5457                       X86MemOperand x86memop_i, PatFrag f_frag, PatFrag i_frag,
5458                       Intrinsic IntVar, Intrinsic IntImm> {
5459   def rr  : AVX8I<opc_rm, MRMSrcReg, (outs RC:$dst),
5460              (ins RC:$src1, RC:$src2),
5461              !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
5462              [(set RC:$dst, (IntVar RC:$src1, RC:$src2))]>, VEX_4V;
5463   def rm  : AVX8I<opc_rm, MRMSrcMem, (outs RC:$dst),
5464              (ins RC:$src1, x86memop_i:$src2),
5465              !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
5466              [(set RC:$dst, (IntVar RC:$src1, (i_frag addr:$src2)))]>, VEX_4V;
5467
5468   def ri  : AVXAIi8<opc_rmi, MRMSrcReg, (outs RC:$dst),
5469              (ins RC:$src1, i8imm:$src2),
5470              !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
5471              [(set RC:$dst, (IntImm RC:$src1, imm:$src2))]>, VEX;
5472   def mi  : AVXAIi8<opc_rmi, MRMSrcMem, (outs RC:$dst),
5473              (ins x86memop_f:$src1, i8imm:$src2),
5474              !strconcat(OpcodeStr, "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
5475              [(set RC:$dst, (IntImm (f_frag addr:$src1), imm:$src2))]>, VEX;
5476 }
5477
5478 defm VPERMILPS  : avx_permil<0x0C, 0x04, "vpermilps", VR128, f128mem, i128mem,
5479                              memopv4f32, memopv4i32,
5480                              int_x86_avx_vpermilvar_ps,
5481                              int_x86_avx_vpermil_ps>;
5482 defm VPERMILPSY : avx_permil<0x0C, 0x04, "vpermilps", VR256, f256mem, i256mem,
5483                              memopv8f32, memopv8i32,
5484                              int_x86_avx_vpermilvar_ps_256,
5485                              int_x86_avx_vpermil_ps_256>;
5486 defm VPERMILPD  : avx_permil<0x0D, 0x05, "vpermilpd", VR128, f128mem, i128mem,
5487                              memopv2f64, memopv2i64,
5488                              int_x86_avx_vpermilvar_pd,
5489                              int_x86_avx_vpermil_pd>;
5490 defm VPERMILPDY : avx_permil<0x0D, 0x05, "vpermilpd", VR256, f256mem, i256mem,
5491                              memopv4f64, memopv4i64,
5492                              int_x86_avx_vpermilvar_pd_256,
5493                              int_x86_avx_vpermil_pd_256>;
5494
5495 def VPERM2F128rr : AVXAIi8<0x06, MRMSrcReg, (outs VR256:$dst),
5496           (ins VR256:$src1, VR256:$src2, i8imm:$src3),
5497           "vperm2f128\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}",
5498           []>, VEX_4V;
5499 def VPERM2F128rm : AVXAIi8<0x06, MRMSrcMem, (outs VR256:$dst),
5500           (ins VR256:$src1, f256mem:$src2, i8imm:$src3),
5501           "vperm2f128\t{$src3, $src2, $src1, $dst|$dst, $src1, $src2, $src3}",
5502           []>, VEX_4V;
5503
5504 // Zero All YMM registers
5505 def VZEROALL : I<0x77, RawFrm, (outs), (ins), "vzeroall",
5506                  [(int_x86_avx_vzeroall)]>, VEX, VEX_L, Requires<[HasAVX]>;
5507
5508 // Zero Upper bits of YMM registers
5509 def VZEROUPPER : I<0x77, RawFrm, (outs), (ins), "vzeroupper",
5510                    [(int_x86_avx_vzeroupper)]>, VEX, Requires<[HasAVX]>;
5511
5512 } // isAsmParserOnly
5513
5514 def : Pat<(int_x86_avx_vinsertf128_pd_256 VR256:$src1, VR128:$src2, imm:$src3),
5515           (VINSERTF128rr VR256:$src1, VR128:$src2, imm:$src3)>;
5516 def : Pat<(int_x86_avx_vinsertf128_ps_256 VR256:$src1, VR128:$src2, imm:$src3),
5517           (VINSERTF128rr VR256:$src1, VR128:$src2, imm:$src3)>;
5518 def : Pat<(int_x86_avx_vinsertf128_si_256 VR256:$src1, VR128:$src2, imm:$src3),
5519           (VINSERTF128rr VR256:$src1, VR128:$src2, imm:$src3)>;
5520
5521 def : Pat<(int_x86_avx_vextractf128_pd_256 VR256:$src1, imm:$src2),
5522           (VEXTRACTF128rr VR256:$src1, imm:$src2)>;
5523 def : Pat<(int_x86_avx_vextractf128_ps_256 VR256:$src1, imm:$src2),
5524           (VEXTRACTF128rr VR256:$src1, imm:$src2)>;
5525 def : Pat<(int_x86_avx_vextractf128_si_256 VR256:$src1, imm:$src2),
5526           (VEXTRACTF128rr VR256:$src1, imm:$src2)>;
5527
5528 def : Pat<(int_x86_avx_vbroadcastf128_ps_256 addr:$src),
5529           (VBROADCASTF128 addr:$src)>;
5530
5531 def : Pat<(int_x86_avx_vperm2f128_ps_256 VR256:$src1, VR256:$src2, imm:$src3),
5532           (VPERM2F128rr VR256:$src1, VR256:$src2, imm:$src3)>;
5533 def : Pat<(int_x86_avx_vperm2f128_pd_256 VR256:$src1, VR256:$src2, imm:$src3),
5534           (VPERM2F128rr VR256:$src1, VR256:$src2, imm:$src3)>;
5535 def : Pat<(int_x86_avx_vperm2f128_si_256 VR256:$src1, VR256:$src2, imm:$src3),
5536           (VPERM2F128rr VR256:$src1, VR256:$src2, imm:$src3)>;
5537
5538 def : Pat<(int_x86_avx_vperm2f128_ps_256
5539                   VR256:$src1, (memopv8f32 addr:$src2), imm:$src3),
5540           (VPERM2F128rm VR256:$src1, addr:$src2, imm:$src3)>;
5541 def : Pat<(int_x86_avx_vperm2f128_pd_256
5542                   VR256:$src1, (memopv4f64 addr:$src2), imm:$src3),
5543           (VPERM2F128rm VR256:$src1, addr:$src2, imm:$src3)>;
5544 def : Pat<(int_x86_avx_vperm2f128_si_256
5545                   VR256:$src1, (memopv8i32 addr:$src2), imm:$src3),
5546           (VPERM2F128rm VR256:$src1, addr:$src2, imm:$src3)>;
5547