move more pseudo instructions out to X86InstrCompiler.td
[oota-llvm.git] / lib / Target / X86 / X86Instr64bit.td
1 //====- X86Instr64bit.td - Describe X86-64 Instructions ----*- 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-64 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 // Operand Definitions.
18 //
19
20 // 64-bits but only 32 bits are significant.
21 def i64i32imm  : Operand<i64> {
22   let ParserMatchClass = ImmSExti64i32AsmOperand;
23 }
24
25 // 64-bits but only 32 bits are significant, and those bits are treated as being
26 // pc relative.
27 def i64i32imm_pcrel : Operand<i64> {
28   let PrintMethod = "print_pcrel_imm";
29   let ParserMatchClass = X86AbsMemAsmOperand;
30 }
31
32
33 // 64-bits but only 8 bits are significant.
34 def i64i8imm   : Operand<i64> {
35   let ParserMatchClass = ImmSExti64i8AsmOperand;
36 }
37
38 def lea64_32mem : Operand<i32> {
39   let PrintMethod = "printi32mem";
40   let AsmOperandLowerMethod = "lower_lea64_32mem";
41   let MIOperandInfo = (ops GR32, i8imm, GR32_NOSP, i32imm, i8imm);
42   let ParserMatchClass = X86MemAsmOperand;
43 }
44
45
46 // Special i64mem for addresses of load folding tail calls. These are not
47 // allowed to use callee-saved registers since they must be scheduled
48 // after callee-saved register are popped.
49 def i64mem_TC : Operand<i64> {
50   let PrintMethod = "printi64mem";
51   let MIOperandInfo = (ops GR64_TC, i8imm, GR64_TC, i32imm, i8imm);
52   let ParserMatchClass = X86MemAsmOperand;
53 }
54
55 //===----------------------------------------------------------------------===//
56 // Complex Pattern Definitions.
57 //
58 def lea64addr : ComplexPattern<i64, 5, "SelectLEAAddr",
59                         [add, sub, mul, X86mul_imm, shl, or, frameindex,
60                          X86WrapperRIP], []>;
61
62 def tls64addr : ComplexPattern<i64, 5, "SelectTLSADDRAddr",
63                                [tglobaltlsaddr], []>;
64                                
65 //===----------------------------------------------------------------------===//
66 // Pattern fragments.
67 //
68
69 def i64immSExt8  : PatLeaf<(i64 immSext8)>;
70
71 def GetLo32XForm : SDNodeXForm<imm, [{
72   // Transformation function: get the low 32 bits.
73   return getI32Imm((unsigned)N->getZExtValue());
74 }]>;
75
76 def i64immSExt32  : PatLeaf<(i64 imm), [{ return i64immSExt32(N); }]>;
77
78
79 def i64immZExt32  : PatLeaf<(i64 imm), [{
80   // i64immZExt32 predicate - True if the 64-bit immediate fits in a 32-bit
81   // unsignedsign extended field.
82   return (uint64_t)N->getZExtValue() == (uint32_t)N->getZExtValue();
83 }]>;
84
85 def sextloadi64i8  : PatFrag<(ops node:$ptr), (i64 (sextloadi8 node:$ptr))>;
86 def sextloadi64i16 : PatFrag<(ops node:$ptr), (i64 (sextloadi16 node:$ptr))>;
87 def sextloadi64i32 : PatFrag<(ops node:$ptr), (i64 (sextloadi32 node:$ptr))>;
88
89 def zextloadi64i1  : PatFrag<(ops node:$ptr), (i64 (zextloadi1 node:$ptr))>;
90 def zextloadi64i8  : PatFrag<(ops node:$ptr), (i64 (zextloadi8 node:$ptr))>;
91 def zextloadi64i16 : PatFrag<(ops node:$ptr), (i64 (zextloadi16 node:$ptr))>;
92 def zextloadi64i32 : PatFrag<(ops node:$ptr), (i64 (zextloadi32 node:$ptr))>;
93
94 def extloadi64i1   : PatFrag<(ops node:$ptr), (i64 (extloadi1 node:$ptr))>;
95 def extloadi64i8   : PatFrag<(ops node:$ptr), (i64 (extloadi8 node:$ptr))>;
96 def extloadi64i16  : PatFrag<(ops node:$ptr), (i64 (extloadi16 node:$ptr))>;
97 def extloadi64i32  : PatFrag<(ops node:$ptr), (i64 (extloadi32 node:$ptr))>;
98
99 //===----------------------------------------------------------------------===//
100 // Instruction list...
101 //
102
103
104 //===----------------------------------------------------------------------===//
105 //  Miscellaneous Instructions...
106 //
107
108 def POPCNT64rr : RI<0xB8, MRMSrcReg, (outs GR64:$dst), (ins GR64:$src),
109                     "popcnt{q}\t{$src, $dst|$dst, $src}", []>, XS;
110 let mayLoad = 1 in
111 def POPCNT64rm : RI<0xB8, MRMSrcMem, (outs GR64:$dst), (ins i64mem:$src),
112                     "popcnt{q}\t{$src, $dst|$dst, $src}", []>, XS;
113
114 let Defs = [RBP,RSP], Uses = [RBP,RSP], mayLoad = 1, neverHasSideEffects = 1 in
115 def LEAVE64  : I<0xC9, RawFrm,
116                  (outs), (ins), "leave", []>, Requires<[In64BitMode]>;
117 let Defs = [RSP], Uses = [RSP], neverHasSideEffects=1 in {
118 let mayLoad = 1 in {
119 def POP64r   : I<0x58, AddRegFrm,
120                  (outs GR64:$reg), (ins), "pop{q}\t$reg", []>;
121 def POP64rmr: I<0x8F, MRM0r, (outs GR64:$reg), (ins), "pop{q}\t$reg", []>;
122 def POP64rmm: I<0x8F, MRM0m, (outs i64mem:$dst), (ins), "pop{q}\t$dst", []>;
123 }
124 let mayStore = 1 in {
125 def PUSH64r  : I<0x50, AddRegFrm,
126                  (outs), (ins GR64:$reg), "push{q}\t$reg", []>;
127 def PUSH64rmr: I<0xFF, MRM6r, (outs), (ins GR64:$reg), "push{q}\t$reg", []>;
128 def PUSH64rmm: I<0xFF, MRM6m, (outs), (ins i64mem:$src), "push{q}\t$src", []>;
129 }
130 }
131
132 let Defs = [RSP], Uses = [RSP], neverHasSideEffects = 1, mayStore = 1 in {
133 def PUSH64i8   : Ii8<0x6a, RawFrm, (outs), (ins i8imm:$imm), 
134                      "push{q}\t$imm", []>;
135 def PUSH64i16  : Ii16<0x68, RawFrm, (outs), (ins i16imm:$imm), 
136                       "push{q}\t$imm", []>;
137 def PUSH64i32  : Ii32<0x68, RawFrm, (outs), (ins i64i32imm:$imm),
138                       "push{q}\t$imm", []>;
139 }
140
141 let Defs = [RSP, EFLAGS], Uses = [RSP], mayLoad = 1, neverHasSideEffects=1 in
142 def POPF64   : I<0x9D, RawFrm, (outs), (ins), "popfq", []>,
143                Requires<[In64BitMode]>;
144 let Defs = [RSP], Uses = [RSP, EFLAGS], mayStore = 1, neverHasSideEffects=1 in
145 def PUSHF64    : I<0x9C, RawFrm, (outs), (ins), "pushfq", []>,
146                  Requires<[In64BitMode]>;
147
148 def LEA64_32r : I<0x8D, MRMSrcMem,
149                   (outs GR32:$dst), (ins lea64_32mem:$src),
150                   "lea{l}\t{$src|$dst}, {$dst|$src}",
151                   [(set GR32:$dst, lea32addr:$src)]>, Requires<[In64BitMode]>;
152
153 let isReMaterializable = 1 in
154 def LEA64r   : RI<0x8D, MRMSrcMem, (outs GR64:$dst), (ins i64mem:$src),
155                   "lea{q}\t{$src|$dst}, {$dst|$src}",
156                   [(set GR64:$dst, lea64addr:$src)]>;
157
158 let Constraints = "$src = $dst" in
159 def BSWAP64r : RI<0xC8, AddRegFrm, (outs GR64:$dst), (ins GR64:$src),
160                   "bswap{q}\t$dst", 
161                   [(set GR64:$dst, (bswap GR64:$src))]>, TB;
162
163 // Bit scan instructions.
164 let Defs = [EFLAGS] in {
165 def BSF64rr  : RI<0xBC, MRMSrcReg, (outs GR64:$dst), (ins GR64:$src),
166                   "bsf{q}\t{$src, $dst|$dst, $src}",
167                   [(set GR64:$dst, EFLAGS, (X86bsf GR64:$src))]>, TB;
168 def BSF64rm  : RI<0xBC, MRMSrcMem, (outs GR64:$dst), (ins i64mem:$src),
169                   "bsf{q}\t{$src, $dst|$dst, $src}",
170                   [(set GR64:$dst, EFLAGS, (X86bsf (loadi64 addr:$src)))]>, TB;
171
172 def BSR64rr  : RI<0xBD, MRMSrcReg, (outs GR64:$dst), (ins GR64:$src),
173                   "bsr{q}\t{$src, $dst|$dst, $src}",
174                   [(set GR64:$dst, EFLAGS, (X86bsr GR64:$src))]>, TB;
175 def BSR64rm  : RI<0xBD, MRMSrcMem, (outs GR64:$dst), (ins i64mem:$src),
176                   "bsr{q}\t{$src, $dst|$dst, $src}",
177                   [(set GR64:$dst, EFLAGS, (X86bsr (loadi64 addr:$src)))]>, TB;
178 } // Defs = [EFLAGS]
179
180 // Repeat string ops
181 let Defs = [RCX,RDI,RSI], Uses = [RCX,RDI,RSI], isCodeGenOnly = 1 in
182 def REP_MOVSQ : RI<0xA5, RawFrm, (outs), (ins), "{rep;movsq|rep movsq}",
183                    [(X86rep_movs i64)]>, REP;
184 let Defs = [RCX,RDI], Uses = [RAX,RCX,RDI], isCodeGenOnly = 1 in
185 def REP_STOSQ : RI<0xAB, RawFrm, (outs), (ins), "{rep;stosq|rep stosq}",
186                    [(X86rep_stos i64)]>, REP;
187
188 let Defs = [EDI,ESI], Uses = [EDI,ESI,EFLAGS] in
189 def MOVSQ : RI<0xA5, RawFrm, (outs), (ins), "movsq", []>;
190
191 let Defs = [RCX,RDI], Uses = [RAX,RCX,RDI,EFLAGS] in
192 def STOSQ : RI<0xAB, RawFrm, (outs), (ins), "stosq", []>;
193
194 def SCAS64 : RI<0xAF, RawFrm, (outs), (ins), "scasq", []>;
195
196 def CMPS64 : RI<0xA7, RawFrm, (outs), (ins), "cmpsq", []>;
197
198
199 //===----------------------------------------------------------------------===//
200 //  Move Instructions...
201 //
202
203 let neverHasSideEffects = 1 in
204 def MOV64rr : RI<0x89, MRMDestReg, (outs GR64:$dst), (ins GR64:$src),
205                  "mov{q}\t{$src, $dst|$dst, $src}", []>;
206
207 let isReMaterializable = 1, isAsCheapAsAMove = 1  in {
208 def MOV64ri : RIi64<0xB8, AddRegFrm, (outs GR64:$dst), (ins i64imm:$src),
209                     "movabs{q}\t{$src, $dst|$dst, $src}",
210                     [(set GR64:$dst, imm:$src)]>;
211 def MOV64ri32 : RIi32<0xC7, MRM0r, (outs GR64:$dst), (ins i64i32imm:$src),
212                       "mov{q}\t{$src, $dst|$dst, $src}",
213                       [(set GR64:$dst, i64immSExt32:$src)]>;
214 }
215
216 // The assembler accepts movq of a 64-bit immediate as an alternate spelling of
217 // movabsq.
218 let isAsmParserOnly = 1 in {
219 def MOV64ri_alt : RIi64<0xB8, AddRegFrm, (outs GR64:$dst), (ins i64imm:$src),
220                     "mov{q}\t{$src, $dst|$dst, $src}", []>;
221 }
222
223 let isCodeGenOnly = 1 in {
224 def MOV64rr_REV : RI<0x8B, MRMSrcReg, (outs GR64:$dst), (ins GR64:$src),
225                      "mov{q}\t{$src, $dst|$dst, $src}", []>;
226 }
227
228 let canFoldAsLoad = 1, isReMaterializable = 1 in
229 def MOV64rm : RI<0x8B, MRMSrcMem, (outs GR64:$dst), (ins i64mem:$src),
230                  "mov{q}\t{$src, $dst|$dst, $src}",
231                  [(set GR64:$dst, (load addr:$src))]>;
232
233 def MOV64mr : RI<0x89, MRMDestMem, (outs), (ins i64mem:$dst, GR64:$src),
234                  "mov{q}\t{$src, $dst|$dst, $src}",
235                  [(store GR64:$src, addr:$dst)]>;
236 def MOV64mi32 : RIi32<0xC7, MRM0m, (outs), (ins i64mem:$dst, i64i32imm:$src),
237                       "mov{q}\t{$src, $dst|$dst, $src}",
238                       [(store i64immSExt32:$src, addr:$dst)]>;
239
240 /// Versions of MOV64rr, MOV64rm, and MOV64mr for i64mem_TC and GR64_TC.
241 let isCodeGenOnly = 1 in {
242 let neverHasSideEffects = 1 in
243 def MOV64rr_TC : RI<0x89, MRMDestReg, (outs GR64_TC:$dst), (ins GR64_TC:$src),
244                 "mov{q}\t{$src, $dst|$dst, $src}", []>;
245
246 let mayLoad = 1,
247     canFoldAsLoad = 1, isReMaterializable = 1 in
248 def MOV64rm_TC : RI<0x8B, MRMSrcMem, (outs GR64_TC:$dst), (ins i64mem_TC:$src),
249                 "mov{q}\t{$src, $dst|$dst, $src}",
250                 []>;
251
252 let mayStore = 1 in
253 def MOV64mr_TC : RI<0x89, MRMDestMem, (outs), (ins i64mem_TC:$dst, GR64_TC:$src),
254                 "mov{q}\t{$src, $dst|$dst, $src}",
255                 []>;
256 }
257
258 // FIXME: These definitions are utterly broken
259 // Just leave them commented out for now because they're useless outside
260 // of the large code model, and most compilers won't generate the instructions
261 // in question.
262 /*
263 def MOV64o8a : RIi8<0xA0, RawFrm, (outs), (ins offset8:$src),
264                       "mov{q}\t{$src, %rax|%rax, $src}", []>;
265 def MOV64o64a : RIi32<0xA1, RawFrm, (outs), (ins offset64:$src),
266                        "mov{q}\t{$src, %rax|%rax, $src}", []>;
267 def MOV64ao8 : RIi8<0xA2, RawFrm, (outs offset8:$dst), (ins),
268                        "mov{q}\t{%rax, $dst|$dst, %rax}", []>;
269 def MOV64ao64 : RIi32<0xA3, RawFrm, (outs offset64:$dst), (ins),
270                        "mov{q}\t{%rax, $dst|$dst, %rax}", []>;
271 */
272
273
274 // Sign/Zero extenders
275
276 // MOVSX64rr8 always has a REX prefix and it has an 8-bit register
277 // operand, which makes it a rare instruction with an 8-bit register
278 // operand that can never access an h register. If support for h registers
279 // were generalized, this would require a special register class.
280 def MOVSX64rr8 : RI<0xBE, MRMSrcReg, (outs GR64:$dst), (ins GR8 :$src),
281                     "movs{bq|x}\t{$src, $dst|$dst, $src}",
282                     [(set GR64:$dst, (sext GR8:$src))]>, TB;
283 def MOVSX64rm8 : RI<0xBE, MRMSrcMem, (outs GR64:$dst), (ins i8mem :$src),
284                     "movs{bq|x}\t{$src, $dst|$dst, $src}",
285                     [(set GR64:$dst, (sextloadi64i8 addr:$src))]>, TB;
286 def MOVSX64rr16: RI<0xBF, MRMSrcReg, (outs GR64:$dst), (ins GR16:$src),
287                     "movs{wq|x}\t{$src, $dst|$dst, $src}",
288                     [(set GR64:$dst, (sext GR16:$src))]>, TB;
289 def MOVSX64rm16: RI<0xBF, MRMSrcMem, (outs GR64:$dst), (ins i16mem:$src),
290                     "movs{wq|x}\t{$src, $dst|$dst, $src}",
291                     [(set GR64:$dst, (sextloadi64i16 addr:$src))]>, TB;
292 def MOVSX64rr32: RI<0x63, MRMSrcReg, (outs GR64:$dst), (ins GR32:$src),
293                     "movs{lq|xd}\t{$src, $dst|$dst, $src}",
294                     [(set GR64:$dst, (sext GR32:$src))]>;
295 def MOVSX64rm32: RI<0x63, MRMSrcMem, (outs GR64:$dst), (ins i32mem:$src),
296                     "movs{lq|xd}\t{$src, $dst|$dst, $src}",
297                     [(set GR64:$dst, (sextloadi64i32 addr:$src))]>;
298
299 // movzbq and movzwq encodings for the disassembler
300 def MOVZX64rr8_Q : RI<0xB6, MRMSrcReg, (outs GR64:$dst), (ins GR8:$src),
301                        "movz{bq|x}\t{$src, $dst|$dst, $src}", []>, TB;
302 def MOVZX64rm8_Q : RI<0xB6, MRMSrcMem, (outs GR64:$dst), (ins i8mem:$src),
303                        "movz{bq|x}\t{$src, $dst|$dst, $src}", []>, TB;
304 def MOVZX64rr16_Q : RI<0xB7, MRMSrcReg, (outs GR64:$dst), (ins GR16:$src),
305                        "movz{wq|x}\t{$src, $dst|$dst, $src}", []>, TB;
306 def MOVZX64rm16_Q : RI<0xB7, MRMSrcMem, (outs GR64:$dst), (ins i16mem:$src),
307                        "movz{wq|x}\t{$src, $dst|$dst, $src}", []>, TB;
308
309 // Use movzbl instead of movzbq when the destination is a register; it's
310 // equivalent due to implicit zero-extending, and it has a smaller encoding.
311 def MOVZX64rr8 : I<0xB6, MRMSrcReg, (outs GR64:$dst), (ins GR8 :$src),
312                    "", [(set GR64:$dst, (zext GR8:$src))]>, TB;
313 def MOVZX64rm8 : I<0xB6, MRMSrcMem, (outs GR64:$dst), (ins i8mem :$src),
314                    "", [(set GR64:$dst, (zextloadi64i8 addr:$src))]>, TB;
315 // Use movzwl instead of movzwq when the destination is a register; it's
316 // equivalent due to implicit zero-extending, and it has a smaller encoding.
317 def MOVZX64rr16: I<0xB7, MRMSrcReg, (outs GR64:$dst), (ins GR16:$src),
318                    "", [(set GR64:$dst, (zext GR16:$src))]>, TB;
319 def MOVZX64rm16: I<0xB7, MRMSrcMem, (outs GR64:$dst), (ins i16mem:$src),
320                    "", [(set GR64:$dst, (zextloadi64i16 addr:$src))]>, TB;
321
322 // There's no movzlq instruction, but movl can be used for this purpose, using
323 // implicit zero-extension. The preferred way to do 32-bit-to-64-bit zero
324 // extension on x86-64 is to use a SUBREG_TO_REG to utilize implicit
325 // zero-extension, however this isn't possible when the 32-bit value is
326 // defined by a truncate or is copied from something where the high bits aren't
327 // necessarily all zero. In such cases, we fall back to these explicit zext
328 // instructions.
329 def MOVZX64rr32 : I<0x89, MRMDestReg, (outs GR64:$dst), (ins GR32:$src),
330                     "", [(set GR64:$dst, (zext GR32:$src))]>;
331 def MOVZX64rm32 : I<0x8B, MRMSrcMem, (outs GR64:$dst), (ins i32mem:$src),
332                     "", [(set GR64:$dst, (zextloadi64i32 addr:$src))]>;
333
334 // Any instruction that defines a 32-bit result leaves the high half of the
335 // register. Truncate can be lowered to EXTRACT_SUBREG. CopyFromReg may
336 // be copying from a truncate. And x86's cmov doesn't do anything if the
337 // condition is false. But any other 32-bit operation will zero-extend
338 // up to 64 bits.
339 def def32 : PatLeaf<(i32 GR32:$src), [{
340   return N->getOpcode() != ISD::TRUNCATE &&
341          N->getOpcode() != TargetOpcode::EXTRACT_SUBREG &&
342          N->getOpcode() != ISD::CopyFromReg &&
343          N->getOpcode() != X86ISD::CMOV;
344 }]>;
345
346 // In the case of a 32-bit def that is known to implicitly zero-extend,
347 // we can use a SUBREG_TO_REG.
348 def : Pat<(i64 (zext def32:$src)),
349           (SUBREG_TO_REG (i64 0), GR32:$src, sub_32bit)>;
350
351 let neverHasSideEffects = 1 in {
352   let Defs = [RAX], Uses = [EAX] in
353   def CDQE : RI<0x98, RawFrm, (outs), (ins),
354                "{cltq|cdqe}", []>;     // RAX = signext(EAX)
355
356   let Defs = [RAX,RDX], Uses = [RAX] in
357   def CQO  : RI<0x99, RawFrm, (outs), (ins),
358                 "{cqto|cqo}", []>; // RDX:RAX = signext(RAX)
359 }
360
361 //===----------------------------------------------------------------------===//
362 //  Arithmetic Instructions...
363 //
364
365 let Defs = [EFLAGS] in {
366
367 def ADD64i32 : RIi32<0x05, RawFrm, (outs), (ins i64i32imm:$src),
368                      "add{q}\t{$src, %rax|%rax, $src}", []>;
369
370 let Constraints = "$src1 = $dst" in {
371 let isConvertibleToThreeAddress = 1 in {
372 let isCommutable = 1 in
373 // Register-Register Addition
374 def ADD64rr    : RI<0x01, MRMDestReg, (outs GR64:$dst), 
375                     (ins GR64:$src1, GR64:$src2),
376                     "add{q}\t{$src2, $dst|$dst, $src2}",
377                     [(set GR64:$dst, EFLAGS,
378                           (X86add_flag GR64:$src1, GR64:$src2))]>;
379
380 // These are alternate spellings for use by the disassembler, we mark them as
381 // code gen only to ensure they aren't matched by the assembler.
382 let isCodeGenOnly = 1 in {
383   def ADD64rr_alt  : RI<0x03, MRMSrcReg, (outs GR64:$dst), 
384                        (ins GR64:$src1, GR64:$src2),
385                        "add{l}\t{$src2, $dst|$dst, $src2}", []>;
386 }
387
388 // Register-Integer Addition
389 def ADD64ri8  : RIi8<0x83, MRM0r, (outs GR64:$dst), 
390                      (ins GR64:$src1, i64i8imm:$src2),
391                      "add{q}\t{$src2, $dst|$dst, $src2}",
392                      [(set GR64:$dst, EFLAGS,
393                            (X86add_flag GR64:$src1, i64immSExt8:$src2))]>;
394 def ADD64ri32 : RIi32<0x81, MRM0r, (outs GR64:$dst), 
395                       (ins GR64:$src1, i64i32imm:$src2),
396                       "add{q}\t{$src2, $dst|$dst, $src2}",
397                       [(set GR64:$dst, EFLAGS,
398                             (X86add_flag GR64:$src1, i64immSExt32:$src2))]>;
399 } // isConvertibleToThreeAddress
400
401 // Register-Memory Addition
402 def ADD64rm     : RI<0x03, MRMSrcMem, (outs GR64:$dst), 
403                      (ins GR64:$src1, i64mem:$src2),
404                      "add{q}\t{$src2, $dst|$dst, $src2}",
405                      [(set GR64:$dst, EFLAGS,
406                            (X86add_flag GR64:$src1, (load addr:$src2)))]>;
407
408 } // Constraints = "$src1 = $dst"
409
410 // Memory-Register Addition
411 def ADD64mr  : RI<0x01, MRMDestMem, (outs), (ins i64mem:$dst, GR64:$src2),
412                   "add{q}\t{$src2, $dst|$dst, $src2}",
413                   [(store (add (load addr:$dst), GR64:$src2), addr:$dst),
414                    (implicit EFLAGS)]>;
415 def ADD64mi8 : RIi8<0x83, MRM0m, (outs), (ins i64mem:$dst, i64i8imm :$src2),
416                     "add{q}\t{$src2, $dst|$dst, $src2}",
417                 [(store (add (load addr:$dst), i64immSExt8:$src2), addr:$dst),
418                  (implicit EFLAGS)]>;
419 def ADD64mi32 : RIi32<0x81, MRM0m, (outs), (ins i64mem:$dst, i64i32imm :$src2),
420                       "add{q}\t{$src2, $dst|$dst, $src2}",
421                [(store (add (load addr:$dst), i64immSExt32:$src2), addr:$dst),
422                 (implicit EFLAGS)]>;
423
424 let Uses = [EFLAGS] in {
425
426 def ADC64i32 : RIi32<0x15, RawFrm, (outs), (ins i64i32imm:$src),
427                      "adc{q}\t{$src, %rax|%rax, $src}", []>;
428
429 let Constraints = "$src1 = $dst" in {
430 let isCommutable = 1 in
431 def ADC64rr  : RI<0x11, MRMDestReg, (outs GR64:$dst), 
432                   (ins GR64:$src1, GR64:$src2),
433                   "adc{q}\t{$src2, $dst|$dst, $src2}",
434                   [(set GR64:$dst, (adde GR64:$src1, GR64:$src2))]>;
435
436 let isCodeGenOnly = 1 in {
437 def ADC64rr_REV : RI<0x13, MRMSrcReg , (outs GR32:$dst), 
438                      (ins GR64:$src1, GR64:$src2),
439                     "adc{q}\t{$src2, $dst|$dst, $src2}", []>;
440 }
441
442 def ADC64rm  : RI<0x13, MRMSrcMem , (outs GR64:$dst), 
443                   (ins GR64:$src1, i64mem:$src2),
444                   "adc{q}\t{$src2, $dst|$dst, $src2}",
445                   [(set GR64:$dst, (adde GR64:$src1, (load addr:$src2)))]>;
446
447 def ADC64ri8 : RIi8<0x83, MRM2r, (outs GR64:$dst), 
448                     (ins GR64:$src1, i64i8imm:$src2),
449                     "adc{q}\t{$src2, $dst|$dst, $src2}",
450                     [(set GR64:$dst, (adde GR64:$src1, i64immSExt8:$src2))]>;
451 def ADC64ri32 : RIi32<0x81, MRM2r, (outs GR64:$dst), 
452                       (ins GR64:$src1, i64i32imm:$src2),
453                       "adc{q}\t{$src2, $dst|$dst, $src2}",
454                       [(set GR64:$dst, (adde GR64:$src1, i64immSExt32:$src2))]>;
455 } // Constraints = "$src1 = $dst"
456
457 def ADC64mr  : RI<0x11, MRMDestMem, (outs), (ins i64mem:$dst, GR64:$src2),
458                   "adc{q}\t{$src2, $dst|$dst, $src2}",
459                   [(store (adde (load addr:$dst), GR64:$src2), addr:$dst)]>;
460 def ADC64mi8 : RIi8<0x83, MRM2m, (outs), (ins i64mem:$dst, i64i8imm :$src2),
461                     "adc{q}\t{$src2, $dst|$dst, $src2}",
462                  [(store (adde (load addr:$dst), i64immSExt8:$src2), 
463                   addr:$dst)]>;
464 def ADC64mi32 : RIi32<0x81, MRM2m, (outs), (ins i64mem:$dst, i64i32imm:$src2),
465                       "adc{q}\t{$src2, $dst|$dst, $src2}",
466                  [(store (adde (load addr:$dst), i64immSExt32:$src2), 
467                   addr:$dst)]>;
468 } // Uses = [EFLAGS]
469
470 let Constraints = "$src1 = $dst" in {
471 // Register-Register Subtraction
472 def SUB64rr  : RI<0x29, MRMDestReg, (outs GR64:$dst), 
473                   (ins GR64:$src1, GR64:$src2),
474                   "sub{q}\t{$src2, $dst|$dst, $src2}",
475                   [(set GR64:$dst, EFLAGS,
476                         (X86sub_flag GR64:$src1, GR64:$src2))]>;
477
478 let isCodeGenOnly = 1 in {
479 def SUB64rr_REV : RI<0x2B, MRMSrcReg, (outs GR64:$dst), 
480                      (ins GR64:$src1, GR64:$src2),
481                      "sub{q}\t{$src2, $dst|$dst, $src2}", []>;
482 }
483
484 // Register-Memory Subtraction
485 def SUB64rm  : RI<0x2B, MRMSrcMem, (outs GR64:$dst), 
486                   (ins GR64:$src1, i64mem:$src2),
487                   "sub{q}\t{$src2, $dst|$dst, $src2}",
488                   [(set GR64:$dst, EFLAGS, 
489                         (X86sub_flag GR64:$src1, (load addr:$src2)))]>;
490
491 // Register-Integer Subtraction
492 def SUB64ri8 : RIi8<0x83, MRM5r, (outs GR64:$dst),
493                                  (ins GR64:$src1, i64i8imm:$src2),
494                     "sub{q}\t{$src2, $dst|$dst, $src2}",
495                     [(set GR64:$dst, EFLAGS,
496                           (X86sub_flag GR64:$src1, i64immSExt8:$src2))]>;
497 def SUB64ri32 : RIi32<0x81, MRM5r, (outs GR64:$dst),
498                                    (ins GR64:$src1, i64i32imm:$src2),
499                       "sub{q}\t{$src2, $dst|$dst, $src2}",
500                       [(set GR64:$dst, EFLAGS,
501                             (X86sub_flag GR64:$src1, i64immSExt32:$src2))]>;
502 } // Constraints = "$src1 = $dst"
503
504 def SUB64i32 : RIi32<0x2D, RawFrm, (outs), (ins i64i32imm:$src),
505                      "sub{q}\t{$src, %rax|%rax, $src}", []>;
506
507 // Memory-Register Subtraction
508 def SUB64mr  : RI<0x29, MRMDestMem, (outs), (ins i64mem:$dst, GR64:$src2), 
509                   "sub{q}\t{$src2, $dst|$dst, $src2}",
510                   [(store (sub (load addr:$dst), GR64:$src2), addr:$dst),
511                    (implicit EFLAGS)]>;
512
513 // Memory-Integer Subtraction
514 def SUB64mi8 : RIi8<0x83, MRM5m, (outs), (ins i64mem:$dst, i64i8imm :$src2), 
515                     "sub{q}\t{$src2, $dst|$dst, $src2}",
516                     [(store (sub (load addr:$dst), i64immSExt8:$src2),
517                             addr:$dst),
518                      (implicit EFLAGS)]>;
519 def SUB64mi32 : RIi32<0x81, MRM5m, (outs), (ins i64mem:$dst, i64i32imm:$src2),
520                       "sub{q}\t{$src2, $dst|$dst, $src2}",
521                       [(store (sub (load addr:$dst), i64immSExt32:$src2),
522                               addr:$dst),
523                        (implicit EFLAGS)]>;
524
525 let Uses = [EFLAGS] in {
526 let Constraints = "$src1 = $dst" in {
527 def SBB64rr    : RI<0x19, MRMDestReg, (outs GR64:$dst), 
528                     (ins GR64:$src1, GR64:$src2),
529                     "sbb{q}\t{$src2, $dst|$dst, $src2}",
530                     [(set GR64:$dst, (sube GR64:$src1, GR64:$src2))]>;
531
532 let isCodeGenOnly = 1 in {
533 def SBB64rr_REV : RI<0x1B, MRMSrcReg, (outs GR64:$dst), 
534                      (ins GR64:$src1, GR64:$src2),
535                      "sbb{q}\t{$src2, $dst|$dst, $src2}", []>;
536 }
537                      
538 def SBB64rm  : RI<0x1B, MRMSrcMem, (outs GR64:$dst), 
539                   (ins GR64:$src1, i64mem:$src2),
540                   "sbb{q}\t{$src2, $dst|$dst, $src2}",
541                   [(set GR64:$dst, (sube GR64:$src1, (load addr:$src2)))]>;
542
543 def SBB64ri8 : RIi8<0x83, MRM3r, (outs GR64:$dst), 
544                     (ins GR64:$src1, i64i8imm:$src2),
545                     "sbb{q}\t{$src2, $dst|$dst, $src2}",
546                     [(set GR64:$dst, (sube GR64:$src1, i64immSExt8:$src2))]>;
547 def SBB64ri32 : RIi32<0x81, MRM3r, (outs GR64:$dst), 
548                       (ins GR64:$src1, i64i32imm:$src2),
549                       "sbb{q}\t{$src2, $dst|$dst, $src2}",
550                       [(set GR64:$dst, (sube GR64:$src1, i64immSExt32:$src2))]>;
551 } // Constraints = "$src1 = $dst"
552
553 def SBB64i32 : RIi32<0x1D, RawFrm, (outs), (ins i64i32imm:$src),
554                      "sbb{q}\t{$src, %rax|%rax, $src}", []>;
555
556 def SBB64mr  : RI<0x19, MRMDestMem, (outs), (ins i64mem:$dst, GR64:$src2), 
557                   "sbb{q}\t{$src2, $dst|$dst, $src2}",
558                   [(store (sube (load addr:$dst), GR64:$src2), addr:$dst)]>;
559 def SBB64mi8 : RIi8<0x83, MRM3m, (outs), (ins i64mem:$dst, i64i8imm :$src2), 
560                     "sbb{q}\t{$src2, $dst|$dst, $src2}",
561                [(store (sube (load addr:$dst), i64immSExt8:$src2), addr:$dst)]>;
562 def SBB64mi32 : RIi32<0x81, MRM3m, (outs), (ins i64mem:$dst, i64i32imm:$src2), 
563                       "sbb{q}\t{$src2, $dst|$dst, $src2}",
564               [(store (sube (load addr:$dst), i64immSExt32:$src2), addr:$dst)]>;
565 } // Uses = [EFLAGS]
566 } // Defs = [EFLAGS]
567
568 // Unsigned multiplication
569 let Defs = [RAX,RDX,EFLAGS], Uses = [RAX], neverHasSideEffects = 1 in {
570 def MUL64r : RI<0xF7, MRM4r, (outs), (ins GR64:$src),
571                 "mul{q}\t$src", []>;         // RAX,RDX = RAX*GR64
572 let mayLoad = 1 in
573 def MUL64m : RI<0xF7, MRM4m, (outs), (ins i64mem:$src),
574                 "mul{q}\t$src", []>;         // RAX,RDX = RAX*[mem64]
575
576 // Signed multiplication
577 def IMUL64r : RI<0xF7, MRM5r, (outs), (ins GR64:$src),
578                  "imul{q}\t$src", []>;         // RAX,RDX = RAX*GR64
579 let mayLoad = 1 in
580 def IMUL64m : RI<0xF7, MRM5m, (outs), (ins i64mem:$src),
581                  "imul{q}\t$src", []>;         // RAX,RDX = RAX*[mem64]
582 }
583
584 let Defs = [EFLAGS] in {
585 let Constraints = "$src1 = $dst" in {
586 let isCommutable = 1 in
587 // Register-Register Signed Integer Multiplication
588 def IMUL64rr : RI<0xAF, MRMSrcReg, (outs GR64:$dst),
589                                    (ins GR64:$src1, GR64:$src2),
590                   "imul{q}\t{$src2, $dst|$dst, $src2}",
591                   [(set GR64:$dst, EFLAGS,
592                         (X86smul_flag GR64:$src1, GR64:$src2))]>, TB;
593
594 // Register-Memory Signed Integer Multiplication
595 def IMUL64rm : RI<0xAF, MRMSrcMem, (outs GR64:$dst),
596                                    (ins GR64:$src1, i64mem:$src2),
597                   "imul{q}\t{$src2, $dst|$dst, $src2}",
598                   [(set GR64:$dst, EFLAGS,
599                         (X86smul_flag GR64:$src1, (load addr:$src2)))]>, TB;
600 } // Constraints = "$src1 = $dst"
601
602 // Suprisingly enough, these are not two address instructions!
603
604 // Register-Integer Signed Integer Multiplication
605 def IMUL64rri8 : RIi8<0x6B, MRMSrcReg,                      // GR64 = GR64*I8
606                       (outs GR64:$dst), (ins GR64:$src1, i64i8imm:$src2),
607                       "imul{q}\t{$src2, $src1, $dst|$dst, $src1, $src2}",
608                       [(set GR64:$dst, EFLAGS,
609                             (X86smul_flag GR64:$src1, i64immSExt8:$src2))]>;
610 def IMUL64rri32 : RIi32<0x69, MRMSrcReg,                    // GR64 = GR64*I32
611                         (outs GR64:$dst), (ins GR64:$src1, i64i32imm:$src2),
612                         "imul{q}\t{$src2, $src1, $dst|$dst, $src1, $src2}",
613                        [(set GR64:$dst, EFLAGS,
614                              (X86smul_flag GR64:$src1, i64immSExt32:$src2))]>;
615
616 // Memory-Integer Signed Integer Multiplication
617 def IMUL64rmi8 : RIi8<0x6B, MRMSrcMem,                      // GR64 = [mem64]*I8
618                       (outs GR64:$dst), (ins i64mem:$src1, i64i8imm: $src2),
619                       "imul{q}\t{$src2, $src1, $dst|$dst, $src1, $src2}",
620                       [(set GR64:$dst, EFLAGS,
621                             (X86smul_flag (load addr:$src1),
622                                           i64immSExt8:$src2))]>;
623 def IMUL64rmi32 : RIi32<0x69, MRMSrcMem,                   // GR64 = [mem64]*I32
624                         (outs GR64:$dst), (ins i64mem:$src1, i64i32imm:$src2),
625                         "imul{q}\t{$src2, $src1, $dst|$dst, $src1, $src2}",
626                         [(set GR64:$dst, EFLAGS,
627                               (X86smul_flag (load addr:$src1),
628                                             i64immSExt32:$src2))]>;
629 } // Defs = [EFLAGS]
630
631 // Unsigned division / remainder
632 let Defs = [RAX,RDX,EFLAGS], Uses = [RAX,RDX] in {
633 // RDX:RAX/r64 = RAX,RDX
634 def DIV64r : RI<0xF7, MRM6r, (outs), (ins GR64:$src),
635                 "div{q}\t$src", []>;
636 // Signed division / remainder
637 // RDX:RAX/r64 = RAX,RDX
638 def IDIV64r: RI<0xF7, MRM7r, (outs), (ins GR64:$src),
639                 "idiv{q}\t$src", []>;
640 let mayLoad = 1 in {
641 // RDX:RAX/[mem64] = RAX,RDX
642 def DIV64m : RI<0xF7, MRM6m, (outs), (ins i64mem:$src),
643                 "div{q}\t$src", []>;
644 // RDX:RAX/[mem64] = RAX,RDX
645 def IDIV64m: RI<0xF7, MRM7m, (outs), (ins i64mem:$src),
646                 "idiv{q}\t$src", []>;
647 }
648 }
649
650 // Unary instructions
651 let Defs = [EFLAGS], CodeSize = 2 in {
652 let Constraints = "$src = $dst" in
653 def NEG64r : RI<0xF7, MRM3r, (outs GR64:$dst), (ins GR64:$src), "neg{q}\t$dst",
654                 [(set GR64:$dst, (ineg GR64:$src)),
655                  (implicit EFLAGS)]>;
656 def NEG64m : RI<0xF7, MRM3m, (outs), (ins i64mem:$dst), "neg{q}\t$dst",
657                 [(store (ineg (loadi64 addr:$dst)), addr:$dst),
658                  (implicit EFLAGS)]>;
659
660 let Constraints = "$src = $dst", isConvertibleToThreeAddress = 1 in
661 def INC64r : RI<0xFF, MRM0r, (outs GR64:$dst), (ins GR64:$src), "inc{q}\t$dst",
662                 [(set GR64:$dst, EFLAGS, (X86inc_flag GR64:$src))]>;
663 def INC64m : RI<0xFF, MRM0m, (outs), (ins i64mem:$dst), "inc{q}\t$dst",
664                 [(store (add (loadi64 addr:$dst), 1), addr:$dst),
665                  (implicit EFLAGS)]>;
666
667 let Constraints = "$src = $dst", isConvertibleToThreeAddress = 1 in
668 def DEC64r : RI<0xFF, MRM1r, (outs GR64:$dst), (ins GR64:$src), "dec{q}\t$dst",
669                 [(set GR64:$dst, EFLAGS, (X86dec_flag GR64:$src))]>;
670 def DEC64m : RI<0xFF, MRM1m, (outs), (ins i64mem:$dst), "dec{q}\t$dst",
671                 [(store (add (loadi64 addr:$dst), -1), addr:$dst),
672                  (implicit EFLAGS)]>;
673
674 // In 64-bit mode, single byte INC and DEC cannot be encoded.
675 let Constraints = "$src = $dst", isConvertibleToThreeAddress = 1 in {
676 // Can transform into LEA.
677 def INC64_16r : I<0xFF, MRM0r, (outs GR16:$dst), (ins GR16:$src), 
678                   "inc{w}\t$dst",
679                   [(set GR16:$dst, EFLAGS, (X86inc_flag GR16:$src))]>,
680                 OpSize, Requires<[In64BitMode]>;
681 def INC64_32r : I<0xFF, MRM0r, (outs GR32:$dst), (ins GR32:$src), 
682                   "inc{l}\t$dst",
683                   [(set GR32:$dst, EFLAGS, (X86inc_flag GR32:$src))]>,
684                 Requires<[In64BitMode]>;
685 def DEC64_16r : I<0xFF, MRM1r, (outs GR16:$dst), (ins GR16:$src), 
686                   "dec{w}\t$dst",
687                   [(set GR16:$dst, EFLAGS, (X86dec_flag GR16:$src))]>,
688                 OpSize, Requires<[In64BitMode]>;
689 def DEC64_32r : I<0xFF, MRM1r, (outs GR32:$dst), (ins GR32:$src), 
690                   "dec{l}\t$dst",
691                   [(set GR32:$dst, EFLAGS, (X86dec_flag GR32:$src))]>,
692                 Requires<[In64BitMode]>;
693 } // Constraints = "$src = $dst", isConvertibleToThreeAddress
694
695 // These are duplicates of their 32-bit counterparts. Only needed so X86 knows
696 // how to unfold them.
697 def INC64_16m : I<0xFF, MRM0m, (outs), (ins i16mem:$dst), "inc{w}\t$dst",
698                   [(store (add (loadi16 addr:$dst), 1), addr:$dst),
699                     (implicit EFLAGS)]>,
700                 OpSize, Requires<[In64BitMode]>;
701 def INC64_32m : I<0xFF, MRM0m, (outs), (ins i32mem:$dst), "inc{l}\t$dst",
702                   [(store (add (loadi32 addr:$dst), 1), addr:$dst),
703                     (implicit EFLAGS)]>,
704                 Requires<[In64BitMode]>;
705 def DEC64_16m : I<0xFF, MRM1m, (outs), (ins i16mem:$dst), "dec{w}\t$dst",
706                   [(store (add (loadi16 addr:$dst), -1), addr:$dst),
707                     (implicit EFLAGS)]>,
708                 OpSize, Requires<[In64BitMode]>;
709 def DEC64_32m : I<0xFF, MRM1m, (outs), (ins i32mem:$dst), "dec{l}\t$dst",
710                   [(store (add (loadi32 addr:$dst), -1), addr:$dst),
711                     (implicit EFLAGS)]>,
712                 Requires<[In64BitMode]>;
713 } // Defs = [EFLAGS], CodeSize
714
715
716 let Defs = [EFLAGS] in {
717 // Shift instructions
718 let Constraints = "$src1 = $dst" in {
719 let Uses = [CL] in
720 def SHL64rCL : RI<0xD3, MRM4r, (outs GR64:$dst), (ins GR64:$src1),
721                   "shl{q}\t{%cl, $dst|$dst, %CL}",
722                   [(set GR64:$dst, (shl GR64:$src1, CL))]>;
723 let isConvertibleToThreeAddress = 1 in   // Can transform into LEA.
724 def SHL64ri  : RIi8<0xC1, MRM4r, (outs GR64:$dst), 
725                     (ins GR64:$src1, i8imm:$src2),
726                     "shl{q}\t{$src2, $dst|$dst, $src2}",
727                     [(set GR64:$dst, (shl GR64:$src1, (i8 imm:$src2)))]>;
728 // NOTE: We don't include patterns for shifts of a register by one, because
729 // 'add reg,reg' is cheaper.
730 def SHL64r1  : RI<0xD1, MRM4r, (outs GR64:$dst), (ins GR64:$src1),
731                  "shl{q}\t$dst", []>;
732 } // Constraints = "$src1 = $dst"
733
734 let Uses = [CL] in
735 def SHL64mCL : RI<0xD3, MRM4m, (outs), (ins i64mem:$dst),
736                   "shl{q}\t{%cl, $dst|$dst, %CL}",
737                   [(store (shl (loadi64 addr:$dst), CL), addr:$dst)]>;
738 def SHL64mi : RIi8<0xC1, MRM4m, (outs), (ins i64mem:$dst, i8imm:$src),
739                   "shl{q}\t{$src, $dst|$dst, $src}",
740                  [(store (shl (loadi64 addr:$dst), (i8 imm:$src)), addr:$dst)]>;
741 def SHL64m1 : RI<0xD1, MRM4m, (outs), (ins i64mem:$dst),
742                   "shl{q}\t$dst",
743                  [(store (shl (loadi64 addr:$dst), (i8 1)), addr:$dst)]>;
744
745 let Constraints = "$src1 = $dst" in {
746 let Uses = [CL] in
747 def SHR64rCL : RI<0xD3, MRM5r, (outs GR64:$dst), (ins GR64:$src1),
748                   "shr{q}\t{%cl, $dst|$dst, %CL}",
749                   [(set GR64:$dst, (srl GR64:$src1, CL))]>;
750 def SHR64ri : RIi8<0xC1, MRM5r, (outs GR64:$dst), (ins GR64:$src1, i8imm:$src2),
751                   "shr{q}\t{$src2, $dst|$dst, $src2}",
752                   [(set GR64:$dst, (srl GR64:$src1, (i8 imm:$src2)))]>;
753 def SHR64r1  : RI<0xD1, MRM5r, (outs GR64:$dst), (ins GR64:$src1),
754                  "shr{q}\t$dst",
755                  [(set GR64:$dst, (srl GR64:$src1, (i8 1)))]>;
756 } // Constraints = "$src1 = $dst"
757
758 let Uses = [CL] in
759 def SHR64mCL : RI<0xD3, MRM5m, (outs), (ins i64mem:$dst),
760                   "shr{q}\t{%cl, $dst|$dst, %CL}",
761                   [(store (srl (loadi64 addr:$dst), CL), addr:$dst)]>;
762 def SHR64mi : RIi8<0xC1, MRM5m, (outs), (ins i64mem:$dst, i8imm:$src),
763                   "shr{q}\t{$src, $dst|$dst, $src}",
764                  [(store (srl (loadi64 addr:$dst), (i8 imm:$src)), addr:$dst)]>;
765 def SHR64m1 : RI<0xD1, MRM5m, (outs), (ins i64mem:$dst),
766                   "shr{q}\t$dst",
767                  [(store (srl (loadi64 addr:$dst), (i8 1)), addr:$dst)]>;
768
769 let Constraints = "$src1 = $dst" in {
770 let Uses = [CL] in
771 def SAR64rCL : RI<0xD3, MRM7r, (outs GR64:$dst), (ins GR64:$src1),
772                  "sar{q}\t{%cl, $dst|$dst, %CL}",
773                  [(set GR64:$dst, (sra GR64:$src1, CL))]>;
774 def SAR64ri  : RIi8<0xC1, MRM7r, (outs GR64:$dst),
775                     (ins GR64:$src1, i8imm:$src2),
776                     "sar{q}\t{$src2, $dst|$dst, $src2}",
777                     [(set GR64:$dst, (sra GR64:$src1, (i8 imm:$src2)))]>;
778 def SAR64r1  : RI<0xD1, MRM7r, (outs GR64:$dst), (ins GR64:$src1),
779                  "sar{q}\t$dst",
780                  [(set GR64:$dst, (sra GR64:$src1, (i8 1)))]>;
781 } // Constraints = "$src = $dst"
782
783 let Uses = [CL] in
784 def SAR64mCL : RI<0xD3, MRM7m, (outs), (ins i64mem:$dst), 
785                  "sar{q}\t{%cl, $dst|$dst, %CL}",
786                  [(store (sra (loadi64 addr:$dst), CL), addr:$dst)]>;
787 def SAR64mi  : RIi8<0xC1, MRM7m, (outs), (ins i64mem:$dst, i8imm:$src),
788                     "sar{q}\t{$src, $dst|$dst, $src}",
789                  [(store (sra (loadi64 addr:$dst), (i8 imm:$src)), addr:$dst)]>;
790 def SAR64m1 : RI<0xD1, MRM7m, (outs), (ins i64mem:$dst),
791                   "sar{q}\t$dst",
792                  [(store (sra (loadi64 addr:$dst), (i8 1)), addr:$dst)]>;
793
794 // Rotate instructions
795
796 let Constraints = "$src = $dst" in {
797 def RCL64r1 : RI<0xD1, MRM2r, (outs GR64:$dst), (ins GR64:$src),
798                  "rcl{q}\t{1, $dst|$dst, 1}", []>;
799 def RCL64ri : RIi8<0xC1, MRM2r, (outs GR64:$dst), (ins GR64:$src, i8imm:$cnt),
800                    "rcl{q}\t{$cnt, $dst|$dst, $cnt}", []>;
801
802 def RCR64r1 : RI<0xD1, MRM3r, (outs GR64:$dst), (ins GR64:$src),
803                  "rcr{q}\t{1, $dst|$dst, 1}", []>;
804 def RCR64ri : RIi8<0xC1, MRM3r, (outs GR64:$dst), (ins GR64:$src, i8imm:$cnt),
805                    "rcr{q}\t{$cnt, $dst|$dst, $cnt}", []>;
806
807 let Uses = [CL] in {
808 def RCL64rCL : RI<0xD3, MRM2r, (outs GR64:$dst), (ins GR64:$src),
809                   "rcl{q}\t{%cl, $dst|$dst, CL}", []>;
810 def RCR64rCL : RI<0xD3, MRM3r, (outs GR64:$dst), (ins GR64:$src),
811                   "rcr{q}\t{%cl, $dst|$dst, CL}", []>;
812 }
813 } // Constraints = "$src = $dst"
814
815 def RCL64m1 : RI<0xD1, MRM2m, (outs), (ins i64mem:$dst),
816                  "rcl{q}\t{1, $dst|$dst, 1}", []>;
817 def RCL64mi : RIi8<0xC1, MRM2m, (outs), (ins i64mem:$dst, i8imm:$cnt),
818                    "rcl{q}\t{$cnt, $dst|$dst, $cnt}", []>;
819 def RCR64m1 : RI<0xD1, MRM3m, (outs), (ins i64mem:$dst),
820                  "rcr{q}\t{1, $dst|$dst, 1}", []>;
821 def RCR64mi : RIi8<0xC1, MRM3m, (outs), (ins i64mem:$dst, i8imm:$cnt),
822                    "rcr{q}\t{$cnt, $dst|$dst, $cnt}", []>;
823
824 let Uses = [CL] in {
825 def RCL64mCL : RI<0xD3, MRM2m, (outs), (ins i64mem:$dst),
826                   "rcl{q}\t{%cl, $dst|$dst, CL}", []>;
827 def RCR64mCL : RI<0xD3, MRM3m, (outs), (ins i64mem:$dst),
828                   "rcr{q}\t{%cl, $dst|$dst, CL}", []>;
829 }
830
831 let Constraints = "$src1 = $dst" in {
832 let Uses = [CL] in
833 def ROL64rCL : RI<0xD3, MRM0r, (outs GR64:$dst), (ins GR64:$src1),
834                   "rol{q}\t{%cl, $dst|$dst, %CL}",
835                   [(set GR64:$dst, (rotl GR64:$src1, CL))]>;
836 def ROL64ri  : RIi8<0xC1, MRM0r, (outs GR64:$dst), 
837                     (ins GR64:$src1, i8imm:$src2),
838                     "rol{q}\t{$src2, $dst|$dst, $src2}",
839                     [(set GR64:$dst, (rotl GR64:$src1, (i8 imm:$src2)))]>;
840 def ROL64r1  : RI<0xD1, MRM0r, (outs GR64:$dst), (ins GR64:$src1),
841                   "rol{q}\t$dst",
842                   [(set GR64:$dst, (rotl GR64:$src1, (i8 1)))]>;
843 } // Constraints = "$src1 = $dst"
844
845 let Uses = [CL] in
846 def ROL64mCL :  RI<0xD3, MRM0m, (outs), (ins i64mem:$dst),
847                    "rol{q}\t{%cl, $dst|$dst, %CL}",
848                    [(store (rotl (loadi64 addr:$dst), CL), addr:$dst)]>;
849 def ROL64mi  : RIi8<0xC1, MRM0m, (outs), (ins i64mem:$dst, i8imm:$src),
850                     "rol{q}\t{$src, $dst|$dst, $src}",
851                 [(store (rotl (loadi64 addr:$dst), (i8 imm:$src)), addr:$dst)]>;
852 def ROL64m1  : RI<0xD1, MRM0m, (outs), (ins i64mem:$dst),
853                  "rol{q}\t$dst",
854                [(store (rotl (loadi64 addr:$dst), (i8 1)), addr:$dst)]>;
855
856 let Constraints = "$src1 = $dst" in {
857 let Uses = [CL] in
858 def ROR64rCL : RI<0xD3, MRM1r, (outs GR64:$dst), (ins GR64:$src1),
859                   "ror{q}\t{%cl, $dst|$dst, %CL}",
860                   [(set GR64:$dst, (rotr GR64:$src1, CL))]>;
861 def ROR64ri  : RIi8<0xC1, MRM1r, (outs GR64:$dst), 
862                     (ins GR64:$src1, i8imm:$src2),
863                     "ror{q}\t{$src2, $dst|$dst, $src2}",
864                     [(set GR64:$dst, (rotr GR64:$src1, (i8 imm:$src2)))]>;
865 def ROR64r1  : RI<0xD1, MRM1r, (outs GR64:$dst), (ins GR64:$src1),
866                   "ror{q}\t$dst",
867                   [(set GR64:$dst, (rotr GR64:$src1, (i8 1)))]>;
868 } // Constraints = "$src1 = $dst"
869
870 let Uses = [CL] in
871 def ROR64mCL : RI<0xD3, MRM1m, (outs), (ins i64mem:$dst), 
872                   "ror{q}\t{%cl, $dst|$dst, %CL}",
873                   [(store (rotr (loadi64 addr:$dst), CL), addr:$dst)]>;
874 def ROR64mi  : RIi8<0xC1, MRM1m, (outs), (ins i64mem:$dst, i8imm:$src),
875                     "ror{q}\t{$src, $dst|$dst, $src}",
876                 [(store (rotr (loadi64 addr:$dst), (i8 imm:$src)), addr:$dst)]>;
877 def ROR64m1  : RI<0xD1, MRM1m, (outs), (ins i64mem:$dst),
878                  "ror{q}\t$dst",
879                [(store (rotr (loadi64 addr:$dst), (i8 1)), addr:$dst)]>;
880
881 // Double shift instructions (generalizations of rotate)
882 let Constraints = "$src1 = $dst" in {
883 let Uses = [CL] in {
884 def SHLD64rrCL : RI<0xA5, MRMDestReg, (outs GR64:$dst), 
885                     (ins GR64:$src1, GR64:$src2),
886                     "shld{q}\t{%cl, $src2, $dst|$dst, $src2, %CL}",
887                     [(set GR64:$dst, (X86shld GR64:$src1, GR64:$src2, CL))]>, 
888                     TB;
889 def SHRD64rrCL : RI<0xAD, MRMDestReg, (outs GR64:$dst), 
890                     (ins GR64:$src1, GR64:$src2),
891                     "shrd{q}\t{%cl, $src2, $dst|$dst, $src2, %CL}",
892                     [(set GR64:$dst, (X86shrd GR64:$src1, GR64:$src2, CL))]>, 
893                     TB;
894 }
895
896 let isCommutable = 1 in {  // FIXME: Update X86InstrInfo::commuteInstruction
897 def SHLD64rri8 : RIi8<0xA4, MRMDestReg,
898                       (outs GR64:$dst), 
899                       (ins GR64:$src1, GR64:$src2, i8imm:$src3),
900                       "shld{q}\t{$src3, $src2, $dst|$dst, $src2, $src3}",
901                       [(set GR64:$dst, (X86shld GR64:$src1, GR64:$src2,
902                                        (i8 imm:$src3)))]>,
903                  TB;
904 def SHRD64rri8 : RIi8<0xAC, MRMDestReg,
905                       (outs GR64:$dst), 
906                       (ins GR64:$src1, GR64:$src2, i8imm:$src3),
907                       "shrd{q}\t{$src3, $src2, $dst|$dst, $src2, $src3}",
908                       [(set GR64:$dst, (X86shrd GR64:$src1, GR64:$src2,
909                                        (i8 imm:$src3)))]>,
910                  TB;
911 } // isCommutable
912 } // Constraints = "$src1 = $dst"
913
914 let Uses = [CL] in {
915 def SHLD64mrCL : RI<0xA5, MRMDestMem, (outs), (ins i64mem:$dst, GR64:$src2),
916                     "shld{q}\t{%cl, $src2, $dst|$dst, $src2, %CL}",
917                     [(store (X86shld (loadi64 addr:$dst), GR64:$src2, CL),
918                       addr:$dst)]>, TB;
919 def SHRD64mrCL : RI<0xAD, MRMDestMem, (outs), (ins i64mem:$dst, GR64:$src2),
920                     "shrd{q}\t{%cl, $src2, $dst|$dst, $src2, %CL}",
921                     [(store (X86shrd (loadi64 addr:$dst), GR64:$src2, CL),
922                       addr:$dst)]>, TB;
923 }
924 def SHLD64mri8 : RIi8<0xA4, MRMDestMem,
925                       (outs), (ins i64mem:$dst, GR64:$src2, i8imm:$src3),
926                       "shld{q}\t{$src3, $src2, $dst|$dst, $src2, $src3}",
927                       [(store (X86shld (loadi64 addr:$dst), GR64:$src2,
928                                        (i8 imm:$src3)), addr:$dst)]>,
929                  TB;
930 def SHRD64mri8 : RIi8<0xAC, MRMDestMem, 
931                       (outs), (ins i64mem:$dst, GR64:$src2, i8imm:$src3),
932                       "shrd{q}\t{$src3, $src2, $dst|$dst, $src2, $src3}",
933                       [(store (X86shrd (loadi64 addr:$dst), GR64:$src2,
934                                        (i8 imm:$src3)), addr:$dst)]>,
935                  TB;
936 } // Defs = [EFLAGS]
937
938 //===----------------------------------------------------------------------===//
939 //  Logical Instructions...
940 //
941
942 let Constraints = "$src = $dst" , AddedComplexity = 15 in
943 def NOT64r : RI<0xF7, MRM2r, (outs GR64:$dst), (ins GR64:$src), "not{q}\t$dst",
944                 [(set GR64:$dst, (not GR64:$src))]>;
945 def NOT64m : RI<0xF7, MRM2m, (outs), (ins i64mem:$dst), "not{q}\t$dst",
946                 [(store (not (loadi64 addr:$dst)), addr:$dst)]>;
947
948 let Defs = [EFLAGS] in {
949 def AND64i32 : RIi32<0x25, RawFrm, (outs), (ins i64i32imm:$src),
950                      "and{q}\t{$src, %rax|%rax, $src}", []>;
951
952 let Constraints = "$src1 = $dst" in {
953 let isCommutable = 1 in
954 def AND64rr  : RI<0x21, MRMDestReg, 
955                   (outs GR64:$dst), (ins GR64:$src1, GR64:$src2),
956                   "and{q}\t{$src2, $dst|$dst, $src2}",
957                   [(set GR64:$dst, EFLAGS,
958                         (X86and_flag GR64:$src1, GR64:$src2))]>;
959 let isCodeGenOnly = 1 in {
960 def AND64rr_REV : RI<0x23, MRMSrcReg, (outs GR64:$dst), 
961                      (ins GR64:$src1, GR64:$src2),
962                      "and{q}\t{$src2, $dst|$dst, $src2}", []>;
963 }
964 def AND64rm  : RI<0x23, MRMSrcMem,
965                   (outs GR64:$dst), (ins GR64:$src1, i64mem:$src2),
966                   "and{q}\t{$src2, $dst|$dst, $src2}",
967                   [(set GR64:$dst, EFLAGS,
968                         (X86and_flag GR64:$src1, (load addr:$src2)))]>;
969 def AND64ri8 : RIi8<0x83, MRM4r, 
970                     (outs GR64:$dst), (ins GR64:$src1, i64i8imm:$src2),
971                     "and{q}\t{$src2, $dst|$dst, $src2}",
972                     [(set GR64:$dst, EFLAGS,
973                           (X86and_flag GR64:$src1, i64immSExt8:$src2))]>;
974 def AND64ri32  : RIi32<0x81, MRM4r, 
975                        (outs GR64:$dst), (ins GR64:$src1, i64i32imm:$src2),
976                        "and{q}\t{$src2, $dst|$dst, $src2}",
977                        [(set GR64:$dst, EFLAGS,
978                              (X86and_flag GR64:$src1, i64immSExt32:$src2))]>;
979 } // Constraints = "$src1 = $dst"
980
981 def AND64mr  : RI<0x21, MRMDestMem,
982                   (outs), (ins i64mem:$dst, GR64:$src),
983                   "and{q}\t{$src, $dst|$dst, $src}",
984                   [(store (and (load addr:$dst), GR64:$src), addr:$dst),
985                    (implicit EFLAGS)]>;
986 def AND64mi8 : RIi8<0x83, MRM4m,
987                     (outs), (ins i64mem:$dst, i64i8imm :$src),
988                     "and{q}\t{$src, $dst|$dst, $src}",
989                  [(store (and (load addr:$dst), i64immSExt8:$src), addr:$dst),
990                   (implicit EFLAGS)]>;
991 def AND64mi32  : RIi32<0x81, MRM4m,
992                        (outs), (ins i64mem:$dst, i64i32imm:$src),
993                        "and{q}\t{$src, $dst|$dst, $src}",
994              [(store (and (loadi64 addr:$dst), i64immSExt32:$src), addr:$dst),
995               (implicit EFLAGS)]>;
996
997 let Constraints = "$src1 = $dst" in {
998 let isCommutable = 1 in
999 def OR64rr   : RI<0x09, MRMDestReg, (outs GR64:$dst), 
1000                   (ins GR64:$src1, GR64:$src2),
1001                   "or{q}\t{$src2, $dst|$dst, $src2}",
1002                   [(set GR64:$dst, EFLAGS,
1003                         (X86or_flag GR64:$src1, GR64:$src2))]>;
1004 let isCodeGenOnly = 1 in {
1005 def OR64rr_REV : RI<0x0B, MRMSrcReg, (outs GR64:$dst), 
1006                     (ins GR64:$src1, GR64:$src2),
1007                     "or{q}\t{$src2, $dst|$dst, $src2}", []>;
1008 }
1009 def OR64rm   : RI<0x0B, MRMSrcMem , (outs GR64:$dst),
1010                   (ins GR64:$src1, i64mem:$src2),
1011                   "or{q}\t{$src2, $dst|$dst, $src2}",
1012                   [(set GR64:$dst, EFLAGS,
1013                         (X86or_flag GR64:$src1, (load addr:$src2)))]>;
1014 def OR64ri8  : RIi8<0x83, MRM1r, (outs GR64:$dst),
1015                     (ins GR64:$src1, i64i8imm:$src2),
1016                     "or{q}\t{$src2, $dst|$dst, $src2}",
1017                    [(set GR64:$dst, EFLAGS,
1018                          (X86or_flag GR64:$src1, i64immSExt8:$src2))]>;
1019 def OR64ri32 : RIi32<0x81, MRM1r, (outs GR64:$dst),
1020                      (ins GR64:$src1, i64i32imm:$src2),
1021                      "or{q}\t{$src2, $dst|$dst, $src2}",
1022                   [(set GR64:$dst, EFLAGS,
1023                         (X86or_flag GR64:$src1, i64immSExt32:$src2))]>;
1024 } // Constraints = "$src1 = $dst"
1025
1026 def OR64mr : RI<0x09, MRMDestMem, (outs), (ins i64mem:$dst, GR64:$src),
1027                 "or{q}\t{$src, $dst|$dst, $src}",
1028                 [(store (or (load addr:$dst), GR64:$src), addr:$dst),
1029                  (implicit EFLAGS)]>;
1030 def OR64mi8  : RIi8<0x83, MRM1m, (outs), (ins i64mem:$dst, i64i8imm:$src),
1031                     "or{q}\t{$src, $dst|$dst, $src}",
1032                   [(store (or (load addr:$dst), i64immSExt8:$src), addr:$dst),
1033                    (implicit EFLAGS)]>;
1034 def OR64mi32 : RIi32<0x81, MRM1m, (outs), (ins i64mem:$dst, i64i32imm:$src),
1035                      "or{q}\t{$src, $dst|$dst, $src}",
1036               [(store (or (loadi64 addr:$dst), i64immSExt32:$src), addr:$dst),
1037                (implicit EFLAGS)]>;
1038
1039 def OR64i32 : RIi32<0x0D, RawFrm, (outs), (ins i64i32imm:$src),
1040                     "or{q}\t{$src, %rax|%rax, $src}", []>;
1041
1042 let Constraints = "$src1 = $dst" in {
1043 let isCommutable = 1 in
1044 def XOR64rr  : RI<0x31, MRMDestReg,  (outs GR64:$dst), 
1045                   (ins GR64:$src1, GR64:$src2), 
1046                   "xor{q}\t{$src2, $dst|$dst, $src2}",
1047                   [(set GR64:$dst, EFLAGS,
1048                         (X86xor_flag GR64:$src1, GR64:$src2))]>;
1049 let isCodeGenOnly = 1 in {
1050 def XOR64rr_REV : RI<0x33, MRMSrcReg, (outs GR64:$dst), 
1051                      (ins GR64:$src1, GR64:$src2),
1052                     "xor{q}\t{$src2, $dst|$dst, $src2}", []>;
1053 }
1054 def XOR64rm  : RI<0x33, MRMSrcMem, (outs GR64:$dst), 
1055                   (ins GR64:$src1, i64mem:$src2), 
1056                   "xor{q}\t{$src2, $dst|$dst, $src2}",
1057                   [(set GR64:$dst, EFLAGS,
1058                         (X86xor_flag GR64:$src1, (load addr:$src2)))]>;
1059 def XOR64ri8 : RIi8<0x83, MRM6r,  (outs GR64:$dst), 
1060                     (ins GR64:$src1, i64i8imm:$src2),
1061                     "xor{q}\t{$src2, $dst|$dst, $src2}",
1062                     [(set GR64:$dst, EFLAGS,
1063                           (X86xor_flag GR64:$src1, i64immSExt8:$src2))]>;
1064 def XOR64ri32 : RIi32<0x81, MRM6r, 
1065                       (outs GR64:$dst), (ins GR64:$src1, i64i32imm:$src2), 
1066                       "xor{q}\t{$src2, $dst|$dst, $src2}",
1067                       [(set GR64:$dst, EFLAGS,
1068                             (X86xor_flag GR64:$src1, i64immSExt32:$src2))]>;
1069 } // Constraints = "$src1 = $dst"
1070
1071 def XOR64mr  : RI<0x31, MRMDestMem, (outs), (ins i64mem:$dst, GR64:$src),
1072                   "xor{q}\t{$src, $dst|$dst, $src}",
1073                   [(store (xor (load addr:$dst), GR64:$src), addr:$dst),
1074                    (implicit EFLAGS)]>;
1075 def XOR64mi8 : RIi8<0x83, MRM6m, (outs), (ins i64mem:$dst, i64i8imm :$src),
1076                     "xor{q}\t{$src, $dst|$dst, $src}",
1077                  [(store (xor (load addr:$dst), i64immSExt8:$src), addr:$dst),
1078                   (implicit EFLAGS)]>;
1079 def XOR64mi32 : RIi32<0x81, MRM6m, (outs), (ins i64mem:$dst, i64i32imm:$src),
1080                       "xor{q}\t{$src, $dst|$dst, $src}",
1081              [(store (xor (loadi64 addr:$dst), i64immSExt32:$src), addr:$dst),
1082               (implicit EFLAGS)]>;
1083               
1084 def XOR64i32 : RIi32<0x35, RawFrm, (outs), (ins i64i32imm:$src),
1085                      "xor{q}\t{$src, %rax|%rax, $src}", []>;
1086
1087 } // Defs = [EFLAGS]
1088
1089 //===----------------------------------------------------------------------===//
1090 //  Comparison Instructions...
1091 //
1092
1093 // Integer comparison
1094 let Defs = [EFLAGS] in {
1095 def TEST64i32 : RIi32<0xa9, RawFrm, (outs), (ins i64i32imm:$src),
1096                       "test{q}\t{$src, %rax|%rax, $src}", []>;
1097 let isCommutable = 1 in
1098 def TEST64rr : RI<0x85, MRMSrcReg, (outs), (ins GR64:$src1, GR64:$src2),
1099                   "test{q}\t{$src2, $src1|$src1, $src2}",
1100                   [(set EFLAGS, (X86cmp (and GR64:$src1, GR64:$src2), 0))]>;
1101 def TEST64rm : RI<0x85, MRMSrcMem, (outs), (ins GR64:$src1, i64mem:$src2),
1102                   "test{q}\t{$src2, $src1|$src1, $src2}",
1103                   [(set EFLAGS, (X86cmp (and GR64:$src1, (loadi64 addr:$src2)),
1104                     0))]>;
1105 def TEST64ri32 : RIi32<0xF7, MRM0r, (outs),
1106                                         (ins GR64:$src1, i64i32imm:$src2),
1107                        "test{q}\t{$src2, $src1|$src1, $src2}",
1108                      [(set EFLAGS, (X86cmp (and GR64:$src1, i64immSExt32:$src2),
1109                       0))]>;
1110 def TEST64mi32 : RIi32<0xF7, MRM0m, (outs),
1111                                         (ins i64mem:$src1, i64i32imm:$src2),
1112                        "test{q}\t{$src2, $src1|$src1, $src2}",
1113                 [(set EFLAGS, (X86cmp (and (loadi64 addr:$src1),
1114                                            i64immSExt32:$src2), 0))]>;
1115
1116
1117 def CMP64i32 : RIi32<0x3D, RawFrm, (outs), (ins i64i32imm:$src),
1118                      "cmp{q}\t{$src, %rax|%rax, $src}", []>;
1119 def CMP64rr : RI<0x39, MRMDestReg, (outs), (ins GR64:$src1, GR64:$src2),
1120                  "cmp{q}\t{$src2, $src1|$src1, $src2}",
1121                  [(set EFLAGS, (X86cmp GR64:$src1, GR64:$src2))]>;
1122
1123 // These are alternate spellings for use by the disassembler, we mark them as
1124 // code gen only to ensure they aren't matched by the assembler.
1125 let isCodeGenOnly = 1 in {
1126   def CMP64mrmrr : RI<0x3B, MRMSrcReg, (outs), (ins GR64:$src1, GR64:$src2),
1127                       "cmp{q}\t{$src2, $src1|$src1, $src2}", []>;
1128 }
1129
1130 def CMP64mr : RI<0x39, MRMDestMem, (outs), (ins i64mem:$src1, GR64:$src2),
1131                  "cmp{q}\t{$src2, $src1|$src1, $src2}",
1132                  [(set EFLAGS, (X86cmp (loadi64 addr:$src1), GR64:$src2))]>;
1133 def CMP64rm : RI<0x3B, MRMSrcMem, (outs), (ins GR64:$src1, i64mem:$src2),
1134                  "cmp{q}\t{$src2, $src1|$src1, $src2}",
1135                  [(set EFLAGS, (X86cmp GR64:$src1, (loadi64 addr:$src2)))]>;
1136 def CMP64ri8 : RIi8<0x83, MRM7r, (outs), (ins GR64:$src1, i64i8imm:$src2),
1137                     "cmp{q}\t{$src2, $src1|$src1, $src2}",
1138                     [(set EFLAGS, (X86cmp GR64:$src1, i64immSExt8:$src2))]>;
1139 def CMP64ri32 : RIi32<0x81, MRM7r, (outs), (ins GR64:$src1, i64i32imm:$src2),
1140                       "cmp{q}\t{$src2, $src1|$src1, $src2}",
1141                       [(set EFLAGS, (X86cmp GR64:$src1, i64immSExt32:$src2))]>;
1142 def CMP64mi8 : RIi8<0x83, MRM7m, (outs), (ins i64mem:$src1, i64i8imm:$src2),
1143                     "cmp{q}\t{$src2, $src1|$src1, $src2}",
1144                     [(set EFLAGS, (X86cmp (loadi64 addr:$src1),
1145                                           i64immSExt8:$src2))]>;
1146 def CMP64mi32 : RIi32<0x81, MRM7m, (outs),
1147                                        (ins i64mem:$src1, i64i32imm:$src2),
1148                       "cmp{q}\t{$src2, $src1|$src1, $src2}",
1149                       [(set EFLAGS, (X86cmp (loadi64 addr:$src1),
1150                                             i64immSExt32:$src2))]>;
1151 } // Defs = [EFLAGS]
1152
1153 // Bit tests.
1154 // TODO: BTC, BTR, and BTS
1155 let Defs = [EFLAGS] in {
1156 def BT64rr : RI<0xA3, MRMDestReg, (outs), (ins GR64:$src1, GR64:$src2),
1157                "bt{q}\t{$src2, $src1|$src1, $src2}",
1158                [(set EFLAGS, (X86bt GR64:$src1, GR64:$src2))]>, TB;
1159
1160 // Unlike with the register+register form, the memory+register form of the
1161 // bt instruction does not ignore the high bits of the index. From ISel's
1162 // perspective, this is pretty bizarre. Disable these instructions for now.
1163 def BT64mr : RI<0xA3, MRMDestMem, (outs), (ins i64mem:$src1, GR64:$src2),
1164                "bt{q}\t{$src2, $src1|$src1, $src2}",
1165 //               [(X86bt (loadi64 addr:$src1), GR64:$src2),
1166 //                (implicit EFLAGS)]
1167                 []
1168                 >, TB;
1169
1170 def BT64ri8 : RIi8<0xBA, MRM4r, (outs), (ins GR64:$src1, i64i8imm:$src2),
1171                 "bt{q}\t{$src2, $src1|$src1, $src2}",
1172                 [(set EFLAGS, (X86bt GR64:$src1, i64immSExt8:$src2))]>, TB;
1173 // Note that these instructions don't need FastBTMem because that
1174 // only applies when the other operand is in a register. When it's
1175 // an immediate, bt is still fast.
1176 def BT64mi8 : RIi8<0xBA, MRM4m, (outs), (ins i64mem:$src1, i64i8imm:$src2),
1177                 "bt{q}\t{$src2, $src1|$src1, $src2}",
1178                 [(set EFLAGS, (X86bt (loadi64 addr:$src1),
1179                                      i64immSExt8:$src2))]>, TB;
1180
1181 def BTC64rr : RI<0xBB, MRMDestReg, (outs), (ins GR64:$src1, GR64:$src2),
1182                  "btc{q}\t{$src2, $src1|$src1, $src2}", []>, TB;
1183 def BTC64mr : RI<0xBB, MRMDestMem, (outs), (ins i64mem:$src1, GR64:$src2),
1184                  "btc{q}\t{$src2, $src1|$src1, $src2}", []>, TB;
1185 def BTC64ri8 : RIi8<0xBA, MRM7r, (outs), (ins GR64:$src1, i64i8imm:$src2),
1186                     "btc{q}\t{$src2, $src1|$src1, $src2}", []>, TB;
1187 def BTC64mi8 : RIi8<0xBA, MRM7m, (outs), (ins i64mem:$src1, i64i8imm:$src2),
1188                     "btc{q}\t{$src2, $src1|$src1, $src2}", []>, TB;
1189
1190 def BTR64rr : RI<0xB3, MRMDestReg, (outs), (ins GR64:$src1, GR64:$src2),
1191                  "btr{q}\t{$src2, $src1|$src1, $src2}", []>, TB;
1192 def BTR64mr : RI<0xB3, MRMDestMem, (outs), (ins i64mem:$src1, GR64:$src2),
1193                  "btr{q}\t{$src2, $src1|$src1, $src2}", []>, TB;
1194 def BTR64ri8 : RIi8<0xBA, MRM6r, (outs), (ins GR64:$src1, i64i8imm:$src2),
1195                     "btr{q}\t{$src2, $src1|$src1, $src2}", []>, TB;
1196 def BTR64mi8 : RIi8<0xBA, MRM6m, (outs), (ins i64mem:$src1, i64i8imm:$src2),
1197                     "btr{q}\t{$src2, $src1|$src1, $src2}", []>, TB;
1198
1199 def BTS64rr : RI<0xAB, MRMDestReg, (outs), (ins GR64:$src1, GR64:$src2),
1200                  "bts{q}\t{$src2, $src1|$src1, $src2}", []>, TB;
1201 def BTS64mr : RI<0xAB, MRMDestMem, (outs), (ins i64mem:$src1, GR64:$src2),
1202                  "bts{q}\t{$src2, $src1|$src1, $src2}", []>, TB;
1203 def BTS64ri8 : RIi8<0xBA, MRM5r, (outs), (ins GR64:$src1, i64i8imm:$src2),
1204                     "bts{q}\t{$src2, $src1|$src1, $src2}", []>, TB;
1205 def BTS64mi8 : RIi8<0xBA, MRM5m, (outs), (ins i64mem:$src1, i64i8imm:$src2),
1206                     "bts{q}\t{$src2, $src1|$src1, $src2}", []>, TB;
1207 } // Defs = [EFLAGS]
1208
1209 // Conditional moves
1210 let Uses = [EFLAGS], Constraints = "$src1 = $dst" in {
1211 let isCommutable = 1 in {
1212 def CMOVB64rr : RI<0x42, MRMSrcReg,       // if <u, GR64 = GR64
1213                    (outs GR64:$dst), (ins GR64:$src1, GR64:$src2),
1214                    "cmovb{q}\t{$src2, $dst|$dst, $src2}",
1215                    [(set GR64:$dst, (X86cmov GR64:$src1, GR64:$src2,
1216                                      X86_COND_B, EFLAGS))]>, TB;
1217 def CMOVAE64rr: RI<0x43, MRMSrcReg,       // if >=u, GR64 = GR64
1218                    (outs GR64:$dst), (ins GR64:$src1, GR64:$src2),
1219                    "cmovae{q}\t{$src2, $dst|$dst, $src2}",
1220                    [(set GR64:$dst, (X86cmov GR64:$src1, GR64:$src2,
1221                                      X86_COND_AE, EFLAGS))]>, TB;
1222 def CMOVE64rr : RI<0x44, MRMSrcReg,       // if ==, GR64 = GR64
1223                    (outs GR64:$dst), (ins GR64:$src1, GR64:$src2),
1224                    "cmove{q}\t{$src2, $dst|$dst, $src2}",
1225                    [(set GR64:$dst, (X86cmov GR64:$src1, GR64:$src2,
1226                                      X86_COND_E, EFLAGS))]>, TB;
1227 def CMOVNE64rr: RI<0x45, MRMSrcReg,       // if !=, GR64 = GR64
1228                    (outs GR64:$dst), (ins GR64:$src1, GR64:$src2),
1229                    "cmovne{q}\t{$src2, $dst|$dst, $src2}",
1230                    [(set GR64:$dst, (X86cmov GR64:$src1, GR64:$src2,
1231                                     X86_COND_NE, EFLAGS))]>, TB;
1232 def CMOVBE64rr: RI<0x46, MRMSrcReg,       // if <=u, GR64 = GR64
1233                    (outs GR64:$dst), (ins GR64:$src1, GR64:$src2),
1234                    "cmovbe{q}\t{$src2, $dst|$dst, $src2}",
1235                    [(set GR64:$dst, (X86cmov GR64:$src1, GR64:$src2,
1236                                     X86_COND_BE, EFLAGS))]>, TB;
1237 def CMOVA64rr : RI<0x47, MRMSrcReg,       // if >u, GR64 = GR64
1238                    (outs GR64:$dst), (ins GR64:$src1, GR64:$src2),
1239                    "cmova{q}\t{$src2, $dst|$dst, $src2}",
1240                    [(set GR64:$dst, (X86cmov GR64:$src1, GR64:$src2,
1241                                     X86_COND_A, EFLAGS))]>, TB;
1242 def CMOVL64rr : RI<0x4C, MRMSrcReg,       // if <s, GR64 = GR64
1243                    (outs GR64:$dst), (ins GR64:$src1, GR64:$src2),
1244                    "cmovl{q}\t{$src2, $dst|$dst, $src2}",
1245                    [(set GR64:$dst, (X86cmov GR64:$src1, GR64:$src2,
1246                                     X86_COND_L, EFLAGS))]>, TB;
1247 def CMOVGE64rr: RI<0x4D, MRMSrcReg,       // if >=s, GR64 = GR64
1248                    (outs GR64:$dst), (ins GR64:$src1, GR64:$src2),
1249                    "cmovge{q}\t{$src2, $dst|$dst, $src2}",
1250                    [(set GR64:$dst, (X86cmov GR64:$src1, GR64:$src2,
1251                                     X86_COND_GE, EFLAGS))]>, TB;
1252 def CMOVLE64rr: RI<0x4E, MRMSrcReg,       // if <=s, GR64 = GR64
1253                    (outs GR64:$dst), (ins GR64:$src1, GR64:$src2),
1254                    "cmovle{q}\t{$src2, $dst|$dst, $src2}",
1255                    [(set GR64:$dst, (X86cmov GR64:$src1, GR64:$src2,
1256                                     X86_COND_LE, EFLAGS))]>, TB;
1257 def CMOVG64rr : RI<0x4F, MRMSrcReg,       // if >s, GR64 = GR64
1258                    (outs GR64:$dst), (ins GR64:$src1, GR64:$src2),
1259                    "cmovg{q}\t{$src2, $dst|$dst, $src2}",
1260                    [(set GR64:$dst, (X86cmov GR64:$src1, GR64:$src2,
1261                                     X86_COND_G, EFLAGS))]>, TB;
1262 def CMOVS64rr : RI<0x48, MRMSrcReg,       // if signed, GR64 = GR64
1263                    (outs GR64:$dst), (ins GR64:$src1, GR64:$src2),
1264                    "cmovs{q}\t{$src2, $dst|$dst, $src2}",
1265                    [(set GR64:$dst, (X86cmov GR64:$src1, GR64:$src2,
1266                                     X86_COND_S, EFLAGS))]>, TB;
1267 def CMOVNS64rr: RI<0x49, MRMSrcReg,       // if !signed, GR64 = GR64
1268                    (outs GR64:$dst), (ins GR64:$src1, GR64:$src2),
1269                    "cmovns{q}\t{$src2, $dst|$dst, $src2}",
1270                    [(set GR64:$dst, (X86cmov GR64:$src1, GR64:$src2,
1271                                     X86_COND_NS, EFLAGS))]>, TB;
1272 def CMOVP64rr : RI<0x4A, MRMSrcReg,       // if parity, GR64 = GR64
1273                    (outs GR64:$dst), (ins GR64:$src1, GR64:$src2),
1274                    "cmovp{q}\t{$src2, $dst|$dst, $src2}",
1275                    [(set GR64:$dst, (X86cmov GR64:$src1, GR64:$src2,
1276                                     X86_COND_P, EFLAGS))]>, TB;
1277 def CMOVNP64rr : RI<0x4B, MRMSrcReg,       // if !parity, GR64 = GR64
1278                    (outs GR64:$dst), (ins GR64:$src1, GR64:$src2),
1279                    "cmovnp{q}\t{$src2, $dst|$dst, $src2}",
1280                     [(set GR64:$dst, (X86cmov GR64:$src1, GR64:$src2,
1281                                      X86_COND_NP, EFLAGS))]>, TB;
1282 def CMOVO64rr : RI<0x40, MRMSrcReg,       // if overflow, GR64 = GR64
1283                    (outs GR64:$dst), (ins GR64:$src1, GR64:$src2),
1284                    "cmovo{q}\t{$src2, $dst|$dst, $src2}",
1285                    [(set GR64:$dst, (X86cmov GR64:$src1, GR64:$src2,
1286                                     X86_COND_O, EFLAGS))]>, TB;
1287 def CMOVNO64rr : RI<0x41, MRMSrcReg,       // if !overflow, GR64 = GR64
1288                    (outs GR64:$dst), (ins GR64:$src1, GR64:$src2),
1289                    "cmovno{q}\t{$src2, $dst|$dst, $src2}",
1290                     [(set GR64:$dst, (X86cmov GR64:$src1, GR64:$src2,
1291                                      X86_COND_NO, EFLAGS))]>, TB;
1292 } // isCommutable = 1
1293
1294 def CMOVB64rm : RI<0x42, MRMSrcMem,       // if <u, GR64 = [mem64]
1295                    (outs GR64:$dst), (ins GR64:$src1, i64mem:$src2),
1296                    "cmovb{q}\t{$src2, $dst|$dst, $src2}",
1297                    [(set GR64:$dst, (X86cmov GR64:$src1, (loadi64 addr:$src2),
1298                                      X86_COND_B, EFLAGS))]>, TB;
1299 def CMOVAE64rm: RI<0x43, MRMSrcMem,       // if >=u, GR64 = [mem64]
1300                    (outs GR64:$dst), (ins GR64:$src1, i64mem:$src2),
1301                    "cmovae{q}\t{$src2, $dst|$dst, $src2}",
1302                    [(set GR64:$dst, (X86cmov GR64:$src1, (loadi64 addr:$src2),
1303                                      X86_COND_AE, EFLAGS))]>, TB;
1304 def CMOVE64rm : RI<0x44, MRMSrcMem,       // if ==, GR64 = [mem64]
1305                    (outs GR64:$dst), (ins GR64:$src1, i64mem:$src2),
1306                    "cmove{q}\t{$src2, $dst|$dst, $src2}",
1307                    [(set GR64:$dst, (X86cmov GR64:$src1, (loadi64 addr:$src2),
1308                                      X86_COND_E, EFLAGS))]>, TB;
1309 def CMOVNE64rm: RI<0x45, MRMSrcMem,       // if !=, GR64 = [mem64]
1310                    (outs GR64:$dst), (ins GR64:$src1, i64mem:$src2),
1311                    "cmovne{q}\t{$src2, $dst|$dst, $src2}",
1312                    [(set GR64:$dst, (X86cmov GR64:$src1, (loadi64 addr:$src2),
1313                                     X86_COND_NE, EFLAGS))]>, TB;
1314 def CMOVBE64rm: RI<0x46, MRMSrcMem,       // if <=u, GR64 = [mem64]
1315                    (outs GR64:$dst), (ins GR64:$src1, i64mem:$src2),
1316                    "cmovbe{q}\t{$src2, $dst|$dst, $src2}",
1317                    [(set GR64:$dst, (X86cmov GR64:$src1, (loadi64 addr:$src2),
1318                                     X86_COND_BE, EFLAGS))]>, TB;
1319 def CMOVA64rm : RI<0x47, MRMSrcMem,       // if >u, GR64 = [mem64]
1320                    (outs GR64:$dst), (ins GR64:$src1, i64mem:$src2),
1321                    "cmova{q}\t{$src2, $dst|$dst, $src2}",
1322                    [(set GR64:$dst, (X86cmov GR64:$src1, (loadi64 addr:$src2),
1323                                     X86_COND_A, EFLAGS))]>, TB;
1324 def CMOVL64rm : RI<0x4C, MRMSrcMem,       // if <s, GR64 = [mem64]
1325                    (outs GR64:$dst), (ins GR64:$src1, i64mem:$src2),
1326                    "cmovl{q}\t{$src2, $dst|$dst, $src2}",
1327                    [(set GR64:$dst, (X86cmov GR64:$src1, (loadi64 addr:$src2),
1328                                     X86_COND_L, EFLAGS))]>, TB;
1329 def CMOVGE64rm: RI<0x4D, MRMSrcMem,       // if >=s, GR64 = [mem64]
1330                    (outs GR64:$dst), (ins GR64:$src1, i64mem:$src2),
1331                    "cmovge{q}\t{$src2, $dst|$dst, $src2}",
1332                    [(set GR64:$dst, (X86cmov GR64:$src1, (loadi64 addr:$src2),
1333                                     X86_COND_GE, EFLAGS))]>, TB;
1334 def CMOVLE64rm: RI<0x4E, MRMSrcMem,       // if <=s, GR64 = [mem64]
1335                    (outs GR64:$dst), (ins GR64:$src1, i64mem:$src2),
1336                    "cmovle{q}\t{$src2, $dst|$dst, $src2}",
1337                    [(set GR64:$dst, (X86cmov GR64:$src1, (loadi64 addr:$src2),
1338                                     X86_COND_LE, EFLAGS))]>, TB;
1339 def CMOVG64rm : RI<0x4F, MRMSrcMem,       // if >s, GR64 = [mem64]
1340                    (outs GR64:$dst), (ins GR64:$src1, i64mem:$src2),
1341                    "cmovg{q}\t{$src2, $dst|$dst, $src2}",
1342                    [(set GR64:$dst, (X86cmov GR64:$src1, (loadi64 addr:$src2),
1343                                     X86_COND_G, EFLAGS))]>, TB;
1344 def CMOVS64rm : RI<0x48, MRMSrcMem,       // if signed, GR64 = [mem64]
1345                    (outs GR64:$dst), (ins GR64:$src1, i64mem:$src2),
1346                    "cmovs{q}\t{$src2, $dst|$dst, $src2}",
1347                    [(set GR64:$dst, (X86cmov GR64:$src1, (loadi64 addr:$src2),
1348                                     X86_COND_S, EFLAGS))]>, TB;
1349 def CMOVNS64rm: RI<0x49, MRMSrcMem,       // if !signed, GR64 = [mem64]
1350                    (outs GR64:$dst), (ins GR64:$src1, i64mem:$src2),
1351                    "cmovns{q}\t{$src2, $dst|$dst, $src2}",
1352                    [(set GR64:$dst, (X86cmov GR64:$src1, (loadi64 addr:$src2),
1353                                     X86_COND_NS, EFLAGS))]>, TB;
1354 def CMOVP64rm : RI<0x4A, MRMSrcMem,       // if parity, GR64 = [mem64]
1355                    (outs GR64:$dst), (ins GR64:$src1, i64mem:$src2),
1356                    "cmovp{q}\t{$src2, $dst|$dst, $src2}",
1357                    [(set GR64:$dst, (X86cmov GR64:$src1, (loadi64 addr:$src2),
1358                                     X86_COND_P, EFLAGS))]>, TB;
1359 def CMOVNP64rm : RI<0x4B, MRMSrcMem,       // if !parity, GR64 = [mem64]
1360                    (outs GR64:$dst), (ins GR64:$src1, i64mem:$src2),
1361                    "cmovnp{q}\t{$src2, $dst|$dst, $src2}",
1362                     [(set GR64:$dst, (X86cmov GR64:$src1, (loadi64 addr:$src2),
1363                                      X86_COND_NP, EFLAGS))]>, TB;
1364 def CMOVO64rm : RI<0x40, MRMSrcMem,       // if overflow, GR64 = [mem64]
1365                    (outs GR64:$dst), (ins GR64:$src1, i64mem:$src2),
1366                    "cmovo{q}\t{$src2, $dst|$dst, $src2}",
1367                    [(set GR64:$dst, (X86cmov GR64:$src1, (loadi64 addr:$src2),
1368                                     X86_COND_O, EFLAGS))]>, TB;
1369 def CMOVNO64rm : RI<0x41, MRMSrcMem,       // if !overflow, GR64 = [mem64]
1370                    (outs GR64:$dst), (ins GR64:$src1, i64mem:$src2),
1371                    "cmovno{q}\t{$src2, $dst|$dst, $src2}",
1372                     [(set GR64:$dst, (X86cmov GR64:$src1, (loadi64 addr:$src2),
1373                                      X86_COND_NO, EFLAGS))]>, TB;
1374 } // Constraints = "$src1 = $dst"
1375
1376 // Use sbb to materialize carry flag into a GPR.
1377 // FIXME: This are pseudo ops that should be replaced with Pat<> patterns.
1378 // However, Pat<> can't replicate the destination reg into the inputs of the
1379 // result.
1380 // FIXME: Change this to have encoding Pseudo when X86MCCodeEmitter replaces
1381 // X86CodeEmitter.
1382 let Defs = [EFLAGS], Uses = [EFLAGS], isCodeGenOnly = 1 in
1383 def SETB_C64r : RI<0x19, MRMInitReg, (outs GR64:$dst), (ins), "",
1384                  [(set GR64:$dst, (X86setcc_c X86_COND_B, EFLAGS))]>;
1385
1386 def : Pat<(i64 (anyext (i8 (X86setcc_c X86_COND_B, EFLAGS)))),
1387           (SETB_C64r)>;
1388
1389 //===----------------------------------------------------------------------===//
1390 // Descriptor-table support instructions
1391
1392 // LLDT is not interpreted specially in 64-bit mode because there is no sign
1393 //   extension.
1394 def SLDT64r : RI<0x00, MRM0r, (outs GR64:$dst), (ins),
1395                  "sldt{q}\t$dst", []>, TB;
1396 def SLDT64m : RI<0x00, MRM0m, (outs i16mem:$dst), (ins),
1397                  "sldt{q}\t$dst", []>, TB;
1398
1399 //===----------------------------------------------------------------------===//
1400 // Alias Instructions
1401 //===----------------------------------------------------------------------===//
1402
1403 // We want to rewrite MOV64r0 in terms of MOV32r0, because it's sometimes a
1404 // smaller encoding, but doing so at isel time interferes with rematerialization
1405 // in the current register allocator. For now, this is rewritten when the
1406 // instruction is lowered to an MCInst.
1407 // FIXME: AddedComplexity gives this a higher priority than MOV64ri32. Remove
1408 // when we have a better way to specify isel priority.
1409 let Defs = [EFLAGS],
1410     AddedComplexity = 1, isReMaterializable = 1, isAsCheapAsAMove = 1 in
1411 def MOV64r0   : I<0x31, MRMInitReg, (outs GR64:$dst), (ins), "",
1412                  [(set GR64:$dst, 0)]>;
1413
1414 // Materialize i64 constant where top 32-bits are zero. This could theoretically
1415 // use MOV32ri with a SUBREG_TO_REG to represent the zero-extension, however
1416 // that would make it more difficult to rematerialize.
1417 let AddedComplexity = 1, isReMaterializable = 1, isAsCheapAsAMove = 1 in
1418 def MOV64ri64i32 : Ii32<0xB8, AddRegFrm, (outs GR64:$dst), (ins i64i32imm:$src),
1419                         "", [(set GR64:$dst, i64immZExt32:$src)]>;
1420
1421 //===----------------------------------------------------------------------===//
1422 // Atomic Instructions
1423 //===----------------------------------------------------------------------===//
1424
1425 // TODO: Get this to fold the constant into the instruction.           
1426 let hasSideEffects = 1, Defs = [ESP] in
1427 def Int_MemBarrierNoSSE64  : RI<0x09, MRM1r, (outs), (ins GR64:$zero),
1428                            "lock\n\t"
1429                            "or{q}\t{$zero, (%rsp)|(%rsp), $zero}",
1430                            [(X86MemBarrierNoSSE GR64:$zero)]>,
1431                            Requires<[In64BitMode]>, LOCK;
1432
1433 let Defs = [RAX, EFLAGS], Uses = [RAX] in {
1434 def LCMPXCHG64 : RI<0xB1, MRMDestMem, (outs), (ins i64mem:$ptr, GR64:$swap),
1435                "lock\n\t"
1436                "cmpxchgq\t$swap,$ptr",
1437                [(X86cas addr:$ptr, GR64:$swap, 8)]>, TB, LOCK;
1438 }
1439
1440 let Constraints = "$val = $dst" in {
1441 let Defs = [EFLAGS] in
1442 def LXADD64 : RI<0xC1, MRMSrcMem, (outs GR64:$dst), (ins GR64:$val,i64mem:$ptr),
1443                "lock\n\t"
1444                "xadd\t$val, $ptr",
1445                [(set GR64:$dst, (atomic_load_add_64 addr:$ptr, GR64:$val))]>,
1446                 TB, LOCK;
1447
1448 def XCHG64rm : RI<0x87, MRMSrcMem, (outs GR64:$dst), 
1449                   (ins GR64:$val,i64mem:$ptr),
1450                   "xchg{q}\t{$val, $ptr|$ptr, $val}", 
1451                   [(set GR64:$dst, (atomic_swap_64 addr:$ptr, GR64:$val))]>;
1452
1453 def XCHG64rr : RI<0x87, MRMSrcReg, (outs GR64:$dst), (ins GR64:$val,GR64:$src),
1454                   "xchg{q}\t{$val, $src|$src, $val}", []>;
1455 }
1456
1457 def XADD64rr  : RI<0xC1, MRMDestReg, (outs GR64:$dst), (ins GR64:$src),
1458                    "xadd{q}\t{$src, $dst|$dst, $src}", []>, TB;
1459 let mayLoad = 1, mayStore = 1 in
1460 def XADD64rm  : RI<0xC1, MRMDestMem, (outs), (ins i64mem:$dst, GR64:$src),
1461                    "xadd{q}\t{$src, $dst|$dst, $src}", []>, TB;
1462                    
1463 def CMPXCHG64rr  : RI<0xB1, MRMDestReg, (outs GR64:$dst), (ins GR64:$src),
1464                       "cmpxchg{q}\t{$src, $dst|$dst, $src}", []>, TB;
1465 let mayLoad = 1, mayStore = 1 in
1466 def CMPXCHG64rm  : RI<0xB1, MRMDestMem, (outs), (ins i64mem:$dst, GR64:$src),
1467                       "cmpxchg{q}\t{$src, $dst|$dst, $src}", []>, TB;
1468                       
1469 let Defs = [RAX, RDX, EFLAGS], Uses = [RAX, RBX, RCX, RDX] in
1470 def CMPXCHG16B : RI<0xC7, MRM1m, (outs), (ins i128mem:$dst),
1471                     "cmpxchg16b\t$dst", []>, TB;
1472
1473 def XCHG64ar : RI<0x90, AddRegFrm, (outs), (ins GR64:$src),
1474                   "xchg{q}\t{$src, %rax|%rax, $src}", []>;
1475
1476 // Optimized codegen when the non-memory output is not used.
1477 let Defs = [EFLAGS], mayLoad = 1, mayStore = 1 in {
1478 // FIXME: Use normal add / sub instructions and add lock prefix dynamically.
1479 def LOCK_ADD64mr : RI<0x01, MRMDestMem, (outs), (ins i64mem:$dst, GR64:$src2),
1480                       "lock\n\t"
1481                       "add{q}\t{$src2, $dst|$dst, $src2}", []>, LOCK;
1482 def LOCK_ADD64mi8 : RIi8<0x83, MRM0m, (outs),
1483                                       (ins i64mem:$dst, i64i8imm :$src2),
1484                     "lock\n\t"
1485                     "add{q}\t{$src2, $dst|$dst, $src2}", []>, LOCK;
1486 def LOCK_ADD64mi32 : RIi32<0x81, MRM0m, (outs),
1487                                         (ins i64mem:$dst, i64i32imm :$src2),
1488                       "lock\n\t"
1489                       "add{q}\t{$src2, $dst|$dst, $src2}", []>, LOCK;
1490 def LOCK_SUB64mr : RI<0x29, MRMDestMem, (outs), (ins i64mem:$dst, GR64:$src2), 
1491                       "lock\n\t"
1492                       "sub{q}\t{$src2, $dst|$dst, $src2}", []>, LOCK;
1493 def LOCK_SUB64mi8 : RIi8<0x83, MRM5m, (outs),
1494                                       (ins i64mem:$dst, i64i8imm :$src2), 
1495                       "lock\n\t"
1496                       "sub{q}\t{$src2, $dst|$dst, $src2}", []>, LOCK;
1497 def LOCK_SUB64mi32 : RIi32<0x81, MRM5m, (outs),
1498                                         (ins i64mem:$dst, i64i32imm:$src2),
1499                       "lock\n\t"
1500                       "sub{q}\t{$src2, $dst|$dst, $src2}", []>, LOCK;
1501 def LOCK_INC64m : RI<0xFF, MRM0m, (outs), (ins i64mem:$dst),
1502                      "lock\n\t"
1503                      "inc{q}\t$dst", []>, LOCK;
1504 def LOCK_DEC64m : RI<0xFF, MRM1m, (outs), (ins i64mem:$dst),
1505                       "lock\n\t"
1506                       "dec{q}\t$dst", []>, LOCK;
1507 }
1508 // Atomic exchange, and, or, xor
1509 let Constraints = "$val = $dst", Defs = [EFLAGS],
1510                   usesCustomInserter = 1 in {
1511 def ATOMAND64 : I<0, Pseudo, (outs GR64:$dst),(ins i64mem:$ptr, GR64:$val),
1512                "#ATOMAND64 PSEUDO!", 
1513                [(set GR64:$dst, (atomic_load_and_64 addr:$ptr, GR64:$val))]>;
1514 def ATOMOR64 : I<0, Pseudo, (outs GR64:$dst),(ins i64mem:$ptr, GR64:$val),
1515                "#ATOMOR64 PSEUDO!", 
1516                [(set GR64:$dst, (atomic_load_or_64 addr:$ptr, GR64:$val))]>;
1517 def ATOMXOR64 : I<0, Pseudo,(outs GR64:$dst),(ins i64mem:$ptr, GR64:$val),
1518                "#ATOMXOR64 PSEUDO!", 
1519                [(set GR64:$dst, (atomic_load_xor_64 addr:$ptr, GR64:$val))]>;
1520 def ATOMNAND64 : I<0, Pseudo,(outs GR64:$dst),(ins i64mem:$ptr, GR64:$val),
1521                "#ATOMNAND64 PSEUDO!", 
1522                [(set GR64:$dst, (atomic_load_nand_64 addr:$ptr, GR64:$val))]>;
1523 def ATOMMIN64: I<0, Pseudo, (outs GR64:$dst), (ins i64mem:$ptr, GR64:$val),
1524                "#ATOMMIN64 PSEUDO!", 
1525                [(set GR64:$dst, (atomic_load_min_64 addr:$ptr, GR64:$val))]>;
1526 def ATOMMAX64: I<0, Pseudo, (outs GR64:$dst),(ins i64mem:$ptr, GR64:$val),
1527                "#ATOMMAX64 PSEUDO!", 
1528                [(set GR64:$dst, (atomic_load_max_64 addr:$ptr, GR64:$val))]>;
1529 def ATOMUMIN64: I<0, Pseudo, (outs GR64:$dst),(ins i64mem:$ptr, GR64:$val),
1530                "#ATOMUMIN64 PSEUDO!", 
1531                [(set GR64:$dst, (atomic_load_umin_64 addr:$ptr, GR64:$val))]>;
1532 def ATOMUMAX64: I<0, Pseudo, (outs GR64:$dst),(ins i64mem:$ptr, GR64:$val),
1533                "#ATOMUMAX64 PSEUDO!", 
1534                [(set GR64:$dst, (atomic_load_umax_64 addr:$ptr, GR64:$val))]>;
1535 }
1536
1537
1538 // String manipulation instructions
1539
1540 def LODSQ : RI<0xAD, RawFrm, (outs), (ins), "lodsq", []>;
1541
1542
1543 //===----------------------------------------------------------------------===//
1544 // X86-64 SSE Instructions
1545 //===----------------------------------------------------------------------===//
1546
1547 // Move instructions...
1548
1549 def MOV64toPQIrr : RPDI<0x6E, MRMSrcReg, (outs VR128:$dst), (ins GR64:$src),
1550                         "mov{d|q}\t{$src, $dst|$dst, $src}",
1551                         [(set VR128:$dst,
1552                           (v2i64 (scalar_to_vector GR64:$src)))]>;
1553 def MOVPQIto64rr  : RPDI<0x7E, MRMDestReg, (outs GR64:$dst), (ins VR128:$src),
1554                          "mov{d|q}\t{$src, $dst|$dst, $src}",
1555                          [(set GR64:$dst, (vector_extract (v2i64 VR128:$src),
1556                                            (iPTR 0)))]>;
1557
1558 def MOV64toSDrr : RPDI<0x6E, MRMSrcReg, (outs FR64:$dst), (ins GR64:$src),
1559                        "mov{d|q}\t{$src, $dst|$dst, $src}",
1560                        [(set FR64:$dst, (bitconvert GR64:$src))]>;
1561 def MOV64toSDrm : S3SI<0x7E, MRMSrcMem, (outs FR64:$dst), (ins i64mem:$src),
1562                        "movq\t{$src, $dst|$dst, $src}",
1563                        [(set FR64:$dst, (bitconvert (loadi64 addr:$src)))]>;
1564
1565 def MOVSDto64rr  : RPDI<0x7E, MRMDestReg, (outs GR64:$dst), (ins FR64:$src),
1566                         "mov{d|q}\t{$src, $dst|$dst, $src}",
1567                         [(set GR64:$dst, (bitconvert FR64:$src))]>;
1568 def MOVSDto64mr  : RPDI<0x7E, MRMDestMem, (outs), (ins i64mem:$dst, FR64:$src),
1569                         "movq\t{$src, $dst|$dst, $src}",
1570                         [(store (i64 (bitconvert FR64:$src)), addr:$dst)]>;
1571