Home | History | Annotate | Download | only in X86
      1 //===-- X86InstrArithmetic.td - Integer Arithmetic Instrs --*- 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 integer arithmetic instructions in the X86
     11 // architecture.
     12 //
     13 //===----------------------------------------------------------------------===//
     14 
     15 //===----------------------------------------------------------------------===//
     16 // LEA - Load Effective Address
     17 let SchedRW = [WriteLEA] in {
     18 let neverHasSideEffects = 1 in
     19 def LEA16r   : I<0x8D, MRMSrcMem,
     20                  (outs GR16:$dst), (ins i32mem:$src),
     21                  "lea{w}\t{$src|$dst}, {$dst|$src}", [], IIC_LEA_16>, OpSize16;
     22 let isReMaterializable = 1 in
     23 def LEA32r   : I<0x8D, MRMSrcMem,
     24                  (outs GR32:$dst), (ins i32mem:$src),
     25                  "lea{l}\t{$src|$dst}, {$dst|$src}",
     26                  [(set GR32:$dst, lea32addr:$src)], IIC_LEA>,
     27                  OpSize32, Requires<[Not64BitMode]>;
     28 
     29 def LEA64_32r : I<0x8D, MRMSrcMem,
     30                   (outs GR32:$dst), (ins lea64_32mem:$src),
     31                   "lea{l}\t{$src|$dst}, {$dst|$src}",
     32                   [(set GR32:$dst, lea64_32addr:$src)], IIC_LEA>,
     33                   OpSize32, Requires<[In64BitMode]>;
     34 
     35 let isReMaterializable = 1 in
     36 def LEA64r   : RI<0x8D, MRMSrcMem, (outs GR64:$dst), (ins lea64mem:$src),
     37                   "lea{q}\t{$src|$dst}, {$dst|$src}",
     38                   [(set GR64:$dst, lea64addr:$src)], IIC_LEA>;
     39 } // SchedRW
     40 
     41 //===----------------------------------------------------------------------===//
     42 //  Fixed-Register Multiplication and Division Instructions.
     43 //
     44 
     45 // SchedModel info for instruction that loads one value and gets the second
     46 // (and possibly third) value from a register.
     47 // This is used for instructions that put the memory operands before other
     48 // uses.
     49 class SchedLoadReg<SchedWrite SW> : Sched<[SW,
     50   // Memory operand.
     51   ReadDefault, ReadDefault, ReadDefault, ReadDefault, ReadDefault,
     52   // Register reads (implicit or explicit).
     53   ReadAfterLd, ReadAfterLd]>;
     54 
     55 // Extra precision multiplication
     56 
     57 // AL is really implied by AX, but the registers in Defs must match the
     58 // SDNode results (i8, i32).
     59 // AL,AH = AL*GR8
     60 let Defs = [AL,EFLAGS,AX], Uses = [AL] in
     61 def MUL8r  : I<0xF6, MRM4r, (outs),  (ins GR8:$src), "mul{b}\t$src",
     62                // FIXME: Used for 8-bit mul, ignore result upper 8 bits.
     63                // This probably ought to be moved to a def : Pat<> if the
     64                // syntax can be accepted.
     65                [(set AL, (mul AL, GR8:$src)),
     66                 (implicit EFLAGS)], IIC_MUL8>, Sched<[WriteIMul]>;
     67 // AX,DX = AX*GR16
     68 let Defs = [AX,DX,EFLAGS], Uses = [AX], neverHasSideEffects = 1 in
     69 def MUL16r : I<0xF7, MRM4r, (outs),  (ins GR16:$src),
     70                "mul{w}\t$src",
     71                [], IIC_MUL16_REG>, OpSize16, Sched<[WriteIMul]>;
     72 // EAX,EDX = EAX*GR32
     73 let Defs = [EAX,EDX,EFLAGS], Uses = [EAX], neverHasSideEffects = 1 in
     74 def MUL32r : I<0xF7, MRM4r, (outs),  (ins GR32:$src),
     75                "mul{l}\t$src",
     76                [/*(set EAX, EDX, EFLAGS, (X86umul_flag EAX, GR32:$src))*/],
     77                IIC_MUL32_REG>, OpSize32, Sched<[WriteIMul]>;
     78 // RAX,RDX = RAX*GR64
     79 let Defs = [RAX,RDX,EFLAGS], Uses = [RAX], neverHasSideEffects = 1 in
     80 def MUL64r : RI<0xF7, MRM4r, (outs), (ins GR64:$src),
     81                 "mul{q}\t$src",
     82                 [/*(set RAX, RDX, EFLAGS, (X86umul_flag RAX, GR64:$src))*/],
     83                 IIC_MUL64>, Sched<[WriteIMul]>;
     84 // AL,AH = AL*[mem8]
     85 let Defs = [AL,EFLAGS,AX], Uses = [AL] in
     86 def MUL8m  : I<0xF6, MRM4m, (outs), (ins i8mem :$src),
     87                "mul{b}\t$src",
     88                // FIXME: Used for 8-bit mul, ignore result upper 8 bits.
     89                // This probably ought to be moved to a def : Pat<> if the
     90                // syntax can be accepted.
     91                [(set AL, (mul AL, (loadi8 addr:$src))),
     92                 (implicit EFLAGS)], IIC_MUL8>, SchedLoadReg<WriteIMulLd>;
     93 // AX,DX = AX*[mem16]
     94 let mayLoad = 1, neverHasSideEffects = 1 in {
     95 let Defs = [AX,DX,EFLAGS], Uses = [AX] in
     96 def MUL16m : I<0xF7, MRM4m, (outs), (ins i16mem:$src),
     97                "mul{w}\t$src",
     98                [], IIC_MUL16_MEM>, OpSize16, SchedLoadReg<WriteIMulLd>;
     99 // EAX,EDX = EAX*[mem32]
    100 let Defs = [EAX,EDX,EFLAGS], Uses = [EAX] in
    101 def MUL32m : I<0xF7, MRM4m, (outs), (ins i32mem:$src),
    102               "mul{l}\t$src",
    103               [], IIC_MUL32_MEM>, OpSize32, SchedLoadReg<WriteIMulLd>;
    104 // RAX,RDX = RAX*[mem64]
    105 let Defs = [RAX,RDX,EFLAGS], Uses = [RAX] in
    106 def MUL64m : RI<0xF7, MRM4m, (outs), (ins i64mem:$src),
    107                 "mul{q}\t$src", [], IIC_MUL64>, SchedLoadReg<WriteIMulLd>;
    108 }
    109 
    110 let neverHasSideEffects = 1 in {
    111 // AL,AH = AL*GR8
    112 let Defs = [AL,EFLAGS,AX], Uses = [AL] in
    113 def IMUL8r  : I<0xF6, MRM5r, (outs),  (ins GR8:$src), "imul{b}\t$src", [],
    114               IIC_IMUL8>, Sched<[WriteIMul]>;
    115 // AX,DX = AX*GR16
    116 let Defs = [AX,DX,EFLAGS], Uses = [AX] in
    117 def IMUL16r : I<0xF7, MRM5r, (outs),  (ins GR16:$src), "imul{w}\t$src", [],
    118               IIC_IMUL16_RR>, OpSize16, Sched<[WriteIMul]>;
    119 // EAX,EDX = EAX*GR32
    120 let Defs = [EAX,EDX,EFLAGS], Uses = [EAX] in
    121 def IMUL32r : I<0xF7, MRM5r, (outs),  (ins GR32:$src), "imul{l}\t$src", [],
    122               IIC_IMUL32_RR>, OpSize32, Sched<[WriteIMul]>;
    123 // RAX,RDX = RAX*GR64
    124 let Defs = [RAX,RDX,EFLAGS], Uses = [RAX] in
    125 def IMUL64r : RI<0xF7, MRM5r, (outs), (ins GR64:$src), "imul{q}\t$src", [],
    126               IIC_IMUL64_RR>, Sched<[WriteIMul]>;
    127 
    128 let mayLoad = 1 in {
    129 // AL,AH = AL*[mem8]
    130 let Defs = [AL,EFLAGS,AX], Uses = [AL] in
    131 def IMUL8m  : I<0xF6, MRM5m, (outs), (ins i8mem :$src),
    132                 "imul{b}\t$src", [], IIC_IMUL8>, SchedLoadReg<WriteIMulLd>;
    133 // AX,DX = AX*[mem16]
    134 let Defs = [AX,DX,EFLAGS], Uses = [AX] in
    135 def IMUL16m : I<0xF7, MRM5m, (outs), (ins i16mem:$src),
    136                 "imul{w}\t$src", [], IIC_IMUL16_MEM>, OpSize16,
    137               SchedLoadReg<WriteIMulLd>;
    138 // EAX,EDX = EAX*[mem32]
    139 let Defs = [EAX,EDX,EFLAGS], Uses = [EAX] in
    140 def IMUL32m : I<0xF7, MRM5m, (outs), (ins i32mem:$src),
    141                 "imul{l}\t$src", [], IIC_IMUL32_MEM>, OpSize32,
    142               SchedLoadReg<WriteIMulLd>;
    143 // RAX,RDX = RAX*[mem64]
    144 let Defs = [RAX,RDX,EFLAGS], Uses = [RAX] in
    145 def IMUL64m : RI<0xF7, MRM5m, (outs), (ins i64mem:$src),
    146                  "imul{q}\t$src", [], IIC_IMUL64>, SchedLoadReg<WriteIMulLd>;
    147 }
    148 } // neverHasSideEffects
    149 
    150 
    151 let Defs = [EFLAGS] in {
    152 let Constraints = "$src1 = $dst" in {
    153 
    154 let isCommutable = 1, SchedRW = [WriteIMul] in {
    155 // X = IMUL Y, Z --> X = IMUL Z, Y
    156 // Register-Register Signed Integer Multiply
    157 def IMUL16rr : I<0xAF, MRMSrcReg, (outs GR16:$dst), (ins GR16:$src1,GR16:$src2),
    158                  "imul{w}\t{$src2, $dst|$dst, $src2}",
    159                  [(set GR16:$dst, EFLAGS,
    160                        (X86smul_flag GR16:$src1, GR16:$src2))], IIC_IMUL16_RR>,
    161                        TB, OpSize16;
    162 def IMUL32rr : I<0xAF, MRMSrcReg, (outs GR32:$dst), (ins GR32:$src1,GR32:$src2),
    163                  "imul{l}\t{$src2, $dst|$dst, $src2}",
    164                  [(set GR32:$dst, EFLAGS,
    165                        (X86smul_flag GR32:$src1, GR32:$src2))], IIC_IMUL32_RR>,
    166                  TB, OpSize32;
    167 def IMUL64rr : RI<0xAF, MRMSrcReg, (outs GR64:$dst),
    168                                    (ins GR64:$src1, GR64:$src2),
    169                   "imul{q}\t{$src2, $dst|$dst, $src2}",
    170                   [(set GR64:$dst, EFLAGS,
    171                         (X86smul_flag GR64:$src1, GR64:$src2))], IIC_IMUL64_RR>,
    172                  TB;
    173 } // isCommutable, SchedRW
    174 
    175 // Register-Memory Signed Integer Multiply
    176 let SchedRW = [WriteIMulLd, ReadAfterLd] in {
    177 def IMUL16rm : I<0xAF, MRMSrcMem, (outs GR16:$dst),
    178                                   (ins GR16:$src1, i16mem:$src2),
    179                  "imul{w}\t{$src2, $dst|$dst, $src2}",
    180                  [(set GR16:$dst, EFLAGS,
    181                        (X86smul_flag GR16:$src1, (load addr:$src2)))],
    182                        IIC_IMUL16_RM>,
    183                TB, OpSize16;
    184 def IMUL32rm : I<0xAF, MRMSrcMem, (outs GR32:$dst),
    185                  (ins GR32:$src1, i32mem:$src2),
    186                  "imul{l}\t{$src2, $dst|$dst, $src2}",
    187                  [(set GR32:$dst, EFLAGS,
    188                        (X86smul_flag GR32:$src1, (load addr:$src2)))],
    189                        IIC_IMUL32_RM>,
    190                TB, OpSize32;
    191 def IMUL64rm : RI<0xAF, MRMSrcMem, (outs GR64:$dst),
    192                                    (ins GR64:$src1, i64mem:$src2),
    193                   "imul{q}\t{$src2, $dst|$dst, $src2}",
    194                   [(set GR64:$dst, EFLAGS,
    195                         (X86smul_flag GR64:$src1, (load addr:$src2)))],
    196                         IIC_IMUL64_RM>,
    197                TB;
    198 } // SchedRW
    199 } // Constraints = "$src1 = $dst"
    200 
    201 } // Defs = [EFLAGS]
    202 
    203 // Surprisingly enough, these are not two address instructions!
    204 let Defs = [EFLAGS] in {
    205 let SchedRW = [WriteIMul] in {
    206 // Register-Integer Signed Integer Multiply
    207 def IMUL16rri  : Ii16<0x69, MRMSrcReg,                      // GR16 = GR16*I16
    208                       (outs GR16:$dst), (ins GR16:$src1, i16imm:$src2),
    209                       "imul{w}\t{$src2, $src1, $dst|$dst, $src1, $src2}",
    210                       [(set GR16:$dst, EFLAGS,
    211                             (X86smul_flag GR16:$src1, imm:$src2))],
    212                             IIC_IMUL16_RRI>, OpSize16;
    213 def IMUL16rri8 : Ii8<0x6B, MRMSrcReg,                       // GR16 = GR16*I8
    214                      (outs GR16:$dst), (ins GR16:$src1, i16i8imm:$src2),
    215                      "imul{w}\t{$src2, $src1, $dst|$dst, $src1, $src2}",
    216                      [(set GR16:$dst, EFLAGS,
    217                            (X86smul_flag GR16:$src1, i16immSExt8:$src2))],
    218                            IIC_IMUL16_RRI>, OpSize16;
    219 def IMUL32rri  : Ii32<0x69, MRMSrcReg,                      // GR32 = GR32*I32
    220                       (outs GR32:$dst), (ins GR32:$src1, i32imm:$src2),
    221                       "imul{l}\t{$src2, $src1, $dst|$dst, $src1, $src2}",
    222                       [(set GR32:$dst, EFLAGS,
    223                             (X86smul_flag GR32:$src1, imm:$src2))],
    224                             IIC_IMUL32_RRI>, OpSize32;
    225 def IMUL32rri8 : Ii8<0x6B, MRMSrcReg,                       // GR32 = GR32*I8
    226                      (outs GR32:$dst), (ins GR32:$src1, i32i8imm:$src2),
    227                      "imul{l}\t{$src2, $src1, $dst|$dst, $src1, $src2}",
    228                      [(set GR32:$dst, EFLAGS,
    229                            (X86smul_flag GR32:$src1, i32immSExt8:$src2))],
    230                            IIC_IMUL32_RRI>, OpSize32;
    231 def IMUL64rri32 : RIi32S<0x69, MRMSrcReg,                    // GR64 = GR64*I32
    232                          (outs GR64:$dst), (ins GR64:$src1, i64i32imm:$src2),
    233                          "imul{q}\t{$src2, $src1, $dst|$dst, $src1, $src2}",
    234                          [(set GR64:$dst, EFLAGS,
    235                              (X86smul_flag GR64:$src1, i64immSExt32:$src2))],
    236                              IIC_IMUL64_RRI>;
    237 def IMUL64rri8 : RIi8<0x6B, MRMSrcReg,                      // GR64 = GR64*I8
    238                       (outs GR64:$dst), (ins GR64:$src1, i64i8imm:$src2),
    239                       "imul{q}\t{$src2, $src1, $dst|$dst, $src1, $src2}",
    240                       [(set GR64:$dst, EFLAGS,
    241                             (X86smul_flag GR64:$src1, i64immSExt8:$src2))],
    242                             IIC_IMUL64_RRI>;
    243 } // SchedRW
    244 
    245 // Memory-Integer Signed Integer Multiply
    246 let SchedRW = [WriteIMulLd] in {
    247 def IMUL16rmi  : Ii16<0x69, MRMSrcMem,                     // GR16 = [mem16]*I16
    248                       (outs GR16:$dst), (ins i16mem:$src1, i16imm:$src2),
    249                       "imul{w}\t{$src2, $src1, $dst|$dst, $src1, $src2}",
    250                       [(set GR16:$dst, EFLAGS,
    251                             (X86smul_flag (load addr:$src1), imm:$src2))],
    252                             IIC_IMUL16_RMI>,
    253                  OpSize16;
    254 def IMUL16rmi8 : Ii8<0x6B, MRMSrcMem,                       // GR16 = [mem16]*I8
    255                      (outs GR16:$dst), (ins i16mem:$src1, i16i8imm :$src2),
    256                      "imul{w}\t{$src2, $src1, $dst|$dst, $src1, $src2}",
    257                      [(set GR16:$dst, EFLAGS,
    258                            (X86smul_flag (load addr:$src1),
    259                                          i16immSExt8:$src2))], IIC_IMUL16_RMI>,
    260                                          OpSize16;
    261 def IMUL32rmi  : Ii32<0x69, MRMSrcMem,                     // GR32 = [mem32]*I32
    262                       (outs GR32:$dst), (ins i32mem:$src1, i32imm:$src2),
    263                       "imul{l}\t{$src2, $src1, $dst|$dst, $src1, $src2}",
    264                       [(set GR32:$dst, EFLAGS,
    265                             (X86smul_flag (load addr:$src1), imm:$src2))],
    266                             IIC_IMUL32_RMI>, OpSize32;
    267 def IMUL32rmi8 : Ii8<0x6B, MRMSrcMem,                       // GR32 = [mem32]*I8
    268                      (outs GR32:$dst), (ins i32mem:$src1, i32i8imm: $src2),
    269                      "imul{l}\t{$src2, $src1, $dst|$dst, $src1, $src2}",
    270                      [(set GR32:$dst, EFLAGS,
    271                            (X86smul_flag (load addr:$src1),
    272                                          i32immSExt8:$src2))],
    273                                          IIC_IMUL32_RMI>, OpSize32;
    274 def IMUL64rmi32 : RIi32S<0x69, MRMSrcMem,                   // GR64 = [mem64]*I32
    275                          (outs GR64:$dst), (ins i64mem:$src1, i64i32imm:$src2),
    276                          "imul{q}\t{$src2, $src1, $dst|$dst, $src1, $src2}",
    277                          [(set GR64:$dst, EFLAGS,
    278                               (X86smul_flag (load addr:$src1),
    279                                             i64immSExt32:$src2))],
    280                                             IIC_IMUL64_RMI>;
    281 def IMUL64rmi8 : RIi8<0x6B, MRMSrcMem,                      // GR64 = [mem64]*I8
    282                       (outs GR64:$dst), (ins i64mem:$src1, i64i8imm: $src2),
    283                       "imul{q}\t{$src2, $src1, $dst|$dst, $src1, $src2}",
    284                       [(set GR64:$dst, EFLAGS,
    285                             (X86smul_flag (load addr:$src1),
    286                                           i64immSExt8:$src2))],
    287                                           IIC_IMUL64_RMI>;
    288 } // SchedRW
    289 } // Defs = [EFLAGS]
    290 
    291 
    292 
    293 
    294 // unsigned division/remainder
    295 let hasSideEffects = 1 in { // so that we don't speculatively execute
    296 let SchedRW = [WriteIDiv] in {
    297 let Defs = [AL,AH,EFLAGS], Uses = [AX] in
    298 def DIV8r  : I<0xF6, MRM6r, (outs),  (ins GR8:$src),    // AX/r8 = AL,AH
    299                "div{b}\t$src", [], IIC_DIV8_REG>;
    300 let Defs = [AX,DX,EFLAGS], Uses = [AX,DX] in
    301 def DIV16r : I<0xF7, MRM6r, (outs),  (ins GR16:$src),   // DX:AX/r16 = AX,DX
    302                "div{w}\t$src", [], IIC_DIV16>, OpSize16;
    303 let Defs = [EAX,EDX,EFLAGS], Uses = [EAX,EDX] in
    304 def DIV32r : I<0xF7, MRM6r, (outs),  (ins GR32:$src),   // EDX:EAX/r32 = EAX,EDX
    305                "div{l}\t$src", [], IIC_DIV32>, OpSize32;
    306 // RDX:RAX/r64 = RAX,RDX
    307 let Defs = [RAX,RDX,EFLAGS], Uses = [RAX,RDX] in
    308 def DIV64r : RI<0xF7, MRM6r, (outs), (ins GR64:$src),
    309                 "div{q}\t$src", [], IIC_DIV64>;
    310 } // SchedRW
    311 
    312 let mayLoad = 1 in {
    313 let Defs = [AL,AH,EFLAGS], Uses = [AX] in
    314 def DIV8m  : I<0xF6, MRM6m, (outs), (ins i8mem:$src),   // AX/[mem8] = AL,AH
    315                "div{b}\t$src", [], IIC_DIV8_MEM>,
    316              SchedLoadReg<WriteIDivLd>;
    317 let Defs = [AX,DX,EFLAGS], Uses = [AX,DX] in
    318 def DIV16m : I<0xF7, MRM6m, (outs), (ins i16mem:$src),  // DX:AX/[mem16] = AX,DX
    319                "div{w}\t$src", [], IIC_DIV16>, OpSize16,
    320              SchedLoadReg<WriteIDivLd>;
    321 let Defs = [EAX,EDX,EFLAGS], Uses = [EAX,EDX] in    // EDX:EAX/[mem32] = EAX,EDX
    322 def DIV32m : I<0xF7, MRM6m, (outs), (ins i32mem:$src),
    323                "div{l}\t$src", [], IIC_DIV32>,
    324              SchedLoadReg<WriteIDivLd>, OpSize32;
    325 // RDX:RAX/[mem64] = RAX,RDX
    326 let Defs = [RAX,RDX,EFLAGS], Uses = [RAX,RDX] in
    327 def DIV64m : RI<0xF7, MRM6m, (outs), (ins i64mem:$src),
    328                 "div{q}\t$src", [], IIC_DIV64>,
    329              SchedLoadReg<WriteIDivLd>;
    330 }
    331 
    332 // Signed division/remainder.
    333 let SchedRW = [WriteIDiv] in {
    334 let Defs = [AL,AH,EFLAGS], Uses = [AX] in
    335 def IDIV8r : I<0xF6, MRM7r, (outs),  (ins GR8:$src),    // AX/r8 = AL,AH
    336                "idiv{b}\t$src", [], IIC_IDIV8>;
    337 let Defs = [AX,DX,EFLAGS], Uses = [AX,DX] in
    338 def IDIV16r: I<0xF7, MRM7r, (outs),  (ins GR16:$src),   // DX:AX/r16 = AX,DX
    339                "idiv{w}\t$src", [], IIC_IDIV16>, OpSize16;
    340 let Defs = [EAX,EDX,EFLAGS], Uses = [EAX,EDX] in
    341 def IDIV32r: I<0xF7, MRM7r, (outs),  (ins GR32:$src),   // EDX:EAX/r32 = EAX,EDX
    342                "idiv{l}\t$src", [], IIC_IDIV32>, OpSize32;
    343 // RDX:RAX/r64 = RAX,RDX
    344 let Defs = [RAX,RDX,EFLAGS], Uses = [RAX,RDX] in
    345 def IDIV64r: RI<0xF7, MRM7r, (outs), (ins GR64:$src),
    346                 "idiv{q}\t$src", [], IIC_IDIV64>;
    347 } // SchedRW
    348 
    349 let mayLoad = 1 in {
    350 let Defs = [AL,AH,EFLAGS], Uses = [AX] in
    351 def IDIV8m : I<0xF6, MRM7m, (outs), (ins i8mem:$src),   // AX/[mem8] = AL,AH
    352                "idiv{b}\t$src", [], IIC_IDIV8>,
    353              SchedLoadReg<WriteIDivLd>;
    354 let Defs = [AX,DX,EFLAGS], Uses = [AX,DX] in
    355 def IDIV16m: I<0xF7, MRM7m, (outs), (ins i16mem:$src),  // DX:AX/[mem16] = AX,DX
    356                "idiv{w}\t$src", [], IIC_IDIV16>, OpSize16,
    357              SchedLoadReg<WriteIDivLd>;
    358 let Defs = [EAX,EDX,EFLAGS], Uses = [EAX,EDX] in    // EDX:EAX/[mem32] = EAX,EDX
    359 def IDIV32m: I<0xF7, MRM7m, (outs), (ins i32mem:$src),
    360                "idiv{l}\t$src", [], IIC_IDIV32>, OpSize32,
    361              SchedLoadReg<WriteIDivLd>;
    362 let Defs = [RAX,RDX,EFLAGS], Uses = [RAX,RDX] in // RDX:RAX/[mem64] = RAX,RDX
    363 def IDIV64m: RI<0xF7, MRM7m, (outs), (ins i64mem:$src),
    364                 "idiv{q}\t$src", [], IIC_IDIV64>,
    365              SchedLoadReg<WriteIDivLd>;
    366 }
    367 } // hasSideEffects = 0
    368 
    369 //===----------------------------------------------------------------------===//
    370 //  Two address Instructions.
    371 //
    372 
    373 // unary instructions
    374 let CodeSize = 2 in {
    375 let Defs = [EFLAGS] in {
    376 let Constraints = "$src1 = $dst", SchedRW = [WriteALU] in {
    377 def NEG8r  : I<0xF6, MRM3r, (outs GR8 :$dst), (ins GR8 :$src1),
    378                "neg{b}\t$dst",
    379                [(set GR8:$dst, (ineg GR8:$src1)),
    380                 (implicit EFLAGS)], IIC_UNARY_REG>;
    381 def NEG16r : I<0xF7, MRM3r, (outs GR16:$dst), (ins GR16:$src1),
    382                "neg{w}\t$dst",
    383                [(set GR16:$dst, (ineg GR16:$src1)),
    384                 (implicit EFLAGS)], IIC_UNARY_REG>, OpSize16;
    385 def NEG32r : I<0xF7, MRM3r, (outs GR32:$dst), (ins GR32:$src1),
    386                "neg{l}\t$dst",
    387                [(set GR32:$dst, (ineg GR32:$src1)),
    388                 (implicit EFLAGS)], IIC_UNARY_REG>, OpSize32;
    389 def NEG64r : RI<0xF7, MRM3r, (outs GR64:$dst), (ins GR64:$src1), "neg{q}\t$dst",
    390                 [(set GR64:$dst, (ineg GR64:$src1)),
    391                  (implicit EFLAGS)], IIC_UNARY_REG>;
    392 } // Constraints = "$src1 = $dst", SchedRW
    393 
    394 // Read-modify-write negate.
    395 let SchedRW = [WriteALULd, WriteRMW] in {
    396 def NEG8m  : I<0xF6, MRM3m, (outs), (ins i8mem :$dst),
    397                "neg{b}\t$dst",
    398                [(store (ineg (loadi8 addr:$dst)), addr:$dst),
    399                 (implicit EFLAGS)], IIC_UNARY_MEM>;
    400 def NEG16m : I<0xF7, MRM3m, (outs), (ins i16mem:$dst),
    401                "neg{w}\t$dst",
    402                [(store (ineg (loadi16 addr:$dst)), addr:$dst),
    403                 (implicit EFLAGS)], IIC_UNARY_MEM>, OpSize16;
    404 def NEG32m : I<0xF7, MRM3m, (outs), (ins i32mem:$dst),
    405                "neg{l}\t$dst",
    406                [(store (ineg (loadi32 addr:$dst)), addr:$dst),
    407                 (implicit EFLAGS)], IIC_UNARY_MEM>, OpSize32;
    408 def NEG64m : RI<0xF7, MRM3m, (outs), (ins i64mem:$dst), "neg{q}\t$dst",
    409                 [(store (ineg (loadi64 addr:$dst)), addr:$dst),
    410                  (implicit EFLAGS)], IIC_UNARY_MEM>;
    411 } // SchedRW
    412 } // Defs = [EFLAGS]
    413 
    414 
    415 // Note: NOT does not set EFLAGS!
    416 
    417 let Constraints = "$src1 = $dst", SchedRW = [WriteALU] in {
    418 // Match xor -1 to not. Favors these over a move imm + xor to save code size.
    419 let AddedComplexity = 15 in {
    420 def NOT8r  : I<0xF6, MRM2r, (outs GR8 :$dst), (ins GR8 :$src1),
    421                "not{b}\t$dst",
    422                [(set GR8:$dst, (not GR8:$src1))], IIC_UNARY_REG>;
    423 def NOT16r : I<0xF7, MRM2r, (outs GR16:$dst), (ins GR16:$src1),
    424                "not{w}\t$dst",
    425                [(set GR16:$dst, (not GR16:$src1))], IIC_UNARY_REG>, OpSize16;
    426 def NOT32r : I<0xF7, MRM2r, (outs GR32:$dst), (ins GR32:$src1),
    427                "not{l}\t$dst",
    428                [(set GR32:$dst, (not GR32:$src1))], IIC_UNARY_REG>, OpSize32;
    429 def NOT64r : RI<0xF7, MRM2r, (outs GR64:$dst), (ins GR64:$src1), "not{q}\t$dst",
    430                 [(set GR64:$dst, (not GR64:$src1))], IIC_UNARY_REG>;
    431 }
    432 } // Constraints = "$src1 = $dst", SchedRW
    433 
    434 let SchedRW = [WriteALULd, WriteRMW] in {
    435 def NOT8m  : I<0xF6, MRM2m, (outs), (ins i8mem :$dst),
    436                "not{b}\t$dst",
    437                [(store (not (loadi8 addr:$dst)), addr:$dst)], IIC_UNARY_MEM>;
    438 def NOT16m : I<0xF7, MRM2m, (outs), (ins i16mem:$dst),
    439                "not{w}\t$dst",
    440                [(store (not (loadi16 addr:$dst)), addr:$dst)], IIC_UNARY_MEM>,
    441                OpSize16;
    442 def NOT32m : I<0xF7, MRM2m, (outs), (ins i32mem:$dst),
    443                "not{l}\t$dst",
    444                [(store (not (loadi32 addr:$dst)), addr:$dst)], IIC_UNARY_MEM>,
    445                OpSize32;
    446 def NOT64m : RI<0xF7, MRM2m, (outs), (ins i64mem:$dst), "not{q}\t$dst",
    447                 [(store (not (loadi64 addr:$dst)), addr:$dst)], IIC_UNARY_MEM>;
    448 } // SchedRW
    449 } // CodeSize
    450 
    451 // TODO: inc/dec is slow for P4, but fast for Pentium-M.
    452 let Defs = [EFLAGS] in {
    453 let Constraints = "$src1 = $dst", SchedRW = [WriteALU] in {
    454 let CodeSize = 2 in
    455 def INC8r  : I<0xFE, MRM0r, (outs GR8 :$dst), (ins GR8 :$src1),
    456                "inc{b}\t$dst",
    457                [(set GR8:$dst, EFLAGS, (X86inc_flag GR8:$src1))],
    458                IIC_UNARY_REG>;
    459 
    460 let isConvertibleToThreeAddress = 1, CodeSize = 1 in {  // Can xform into LEA.
    461 def INC16r : I<0x40, AddRegFrm, (outs GR16:$dst), (ins GR16:$src1),
    462                "inc{w}\t$dst",
    463                [(set GR16:$dst, EFLAGS, (X86inc_flag GR16:$src1))], IIC_UNARY_REG>,
    464              OpSize16, Requires<[Not64BitMode]>;
    465 def INC32r : I<0x40, AddRegFrm, (outs GR32:$dst), (ins GR32:$src1),
    466                "inc{l}\t$dst",
    467                [(set GR32:$dst, EFLAGS, (X86inc_flag GR32:$src1))],
    468                IIC_UNARY_REG>,
    469              OpSize32, Requires<[Not64BitMode]>;
    470 def INC64r : RI<0xFF, MRM0r, (outs GR64:$dst), (ins GR64:$src1), "inc{q}\t$dst",
    471                 [(set GR64:$dst, EFLAGS, (X86inc_flag GR64:$src1))],
    472                 IIC_UNARY_REG>;
    473 } // isConvertibleToThreeAddress = 1, CodeSize = 1
    474 
    475 
    476 // In 64-bit mode, single byte INC and DEC cannot be encoded.
    477 let isConvertibleToThreeAddress = 1, CodeSize = 2 in {
    478 // Can transform into LEA.
    479 def INC64_16r : I<0xFF, MRM0r, (outs GR16:$dst), (ins GR16:$src1),
    480                   "inc{w}\t$dst",
    481                   [(set GR16:$dst, EFLAGS, (X86inc_flag GR16:$src1))],
    482                   IIC_UNARY_REG>,
    483                 OpSize16, Requires<[In64BitMode]>;
    484 def INC64_32r : I<0xFF, MRM0r, (outs GR32:$dst), (ins GR32:$src1),
    485                   "inc{l}\t$dst",
    486                   [(set GR32:$dst, EFLAGS, (X86inc_flag GR32:$src1))],
    487                   IIC_UNARY_REG>,
    488                 OpSize32, Requires<[In64BitMode]>;
    489 def DEC64_16r : I<0xFF, MRM1r, (outs GR16:$dst), (ins GR16:$src1),
    490                   "dec{w}\t$dst",
    491                   [(set GR16:$dst, EFLAGS, (X86dec_flag GR16:$src1))],
    492                   IIC_UNARY_REG>,
    493                 OpSize16, Requires<[In64BitMode]>;
    494 def DEC64_32r : I<0xFF, MRM1r, (outs GR32:$dst), (ins GR32:$src1),
    495                   "dec{l}\t$dst",
    496                   [(set GR32:$dst, EFLAGS, (X86dec_flag GR32:$src1))],
    497                   IIC_UNARY_REG>,
    498                 OpSize32, Requires<[In64BitMode]>;
    499 } // isConvertibleToThreeAddress = 1, CodeSize = 2
    500 
    501 let isCodeGenOnly = 1, ForceDisassemble = 1, hasSideEffects = 0,
    502     CodeSize = 2 in {
    503 def INC32_16r : I<0xFF, MRM0r, (outs GR16:$dst), (ins GR16:$src1),
    504                   "inc{w}\t$dst", [], IIC_UNARY_REG>,
    505                 OpSize16, Requires<[Not64BitMode]>;
    506 def INC32_32r : I<0xFF, MRM0r, (outs GR32:$dst), (ins GR32:$src1),
    507                   "inc{l}\t$dst", [], IIC_UNARY_REG>,
    508                 OpSize32, Requires<[Not64BitMode]>;
    509 def DEC32_16r : I<0xFF, MRM1r, (outs GR16:$dst), (ins GR16:$src1),
    510                   "dec{w}\t$dst", [], IIC_UNARY_REG>,
    511                 OpSize16, Requires<[Not64BitMode]>;
    512 def DEC32_32r : I<0xFF, MRM1r, (outs GR32:$dst), (ins GR32:$src1),
    513                   "dec{l}\t$dst", [], IIC_UNARY_REG>,
    514                 OpSize32, Requires<[Not64BitMode]>;
    515 } // isCodeGenOnly = 1, ForceDisassemble = 1, HasSideEffects = 0, CodeSize = 2
    516 
    517 } // Constraints = "$src1 = $dst", SchedRW
    518 
    519 let CodeSize = 2, SchedRW = [WriteALULd, WriteRMW] in {
    520   def INC8m  : I<0xFE, MRM0m, (outs), (ins i8mem :$dst), "inc{b}\t$dst",
    521                [(store (add (loadi8 addr:$dst), 1), addr:$dst),
    522                 (implicit EFLAGS)], IIC_UNARY_MEM>;
    523   def INC16m : I<0xFF, MRM0m, (outs), (ins i16mem:$dst), "inc{w}\t$dst",
    524                [(store (add (loadi16 addr:$dst), 1), addr:$dst),
    525                 (implicit EFLAGS)], IIC_UNARY_MEM>,
    526                OpSize16, Requires<[Not64BitMode]>;
    527   def INC32m : I<0xFF, MRM0m, (outs), (ins i32mem:$dst), "inc{l}\t$dst",
    528                [(store (add (loadi32 addr:$dst), 1), addr:$dst),
    529                 (implicit EFLAGS)], IIC_UNARY_MEM>,
    530                OpSize32, Requires<[Not64BitMode]>;
    531   def INC64m : RI<0xFF, MRM0m, (outs), (ins i64mem:$dst), "inc{q}\t$dst",
    532                   [(store (add (loadi64 addr:$dst), 1), addr:$dst),
    533                    (implicit EFLAGS)], IIC_UNARY_MEM>;
    534 
    535 // These are duplicates of their 32-bit counterparts. Only needed so X86 knows
    536 // how to unfold them.
    537 // FIXME: What is this for??
    538 def INC64_16m : I<0xFF, MRM0m, (outs), (ins i16mem:$dst), "inc{w}\t$dst",
    539                   [(store (add (loadi16 addr:$dst), 1), addr:$dst),
    540                     (implicit EFLAGS)], IIC_UNARY_MEM>,
    541                 OpSize16, Requires<[In64BitMode]>;
    542 def INC64_32m : I<0xFF, MRM0m, (outs), (ins i32mem:$dst), "inc{l}\t$dst",
    543                   [(store (add (loadi32 addr:$dst), 1), addr:$dst),
    544                     (implicit EFLAGS)], IIC_UNARY_MEM>,
    545                 OpSize32, Requires<[In64BitMode]>;
    546 def DEC64_16m : I<0xFF, MRM1m, (outs), (ins i16mem:$dst), "dec{w}\t$dst",
    547                   [(store (add (loadi16 addr:$dst), -1), addr:$dst),
    548                     (implicit EFLAGS)], IIC_UNARY_MEM>,
    549                 OpSize16, Requires<[In64BitMode]>;
    550 def DEC64_32m : I<0xFF, MRM1m, (outs), (ins i32mem:$dst), "dec{l}\t$dst",
    551                   [(store (add (loadi32 addr:$dst), -1), addr:$dst),
    552                     (implicit EFLAGS)], IIC_UNARY_MEM>,
    553                 OpSize32, Requires<[In64BitMode]>;
    554 } // CodeSize = 2, SchedRW
    555 
    556 let Constraints = "$src1 = $dst", SchedRW = [WriteALU] in {
    557 let CodeSize = 2 in
    558 def DEC8r  : I<0xFE, MRM1r, (outs GR8 :$dst), (ins GR8 :$src1),
    559                "dec{b}\t$dst",
    560                [(set GR8:$dst, EFLAGS, (X86dec_flag GR8:$src1))],
    561                IIC_UNARY_REG>;
    562 let isConvertibleToThreeAddress = 1, CodeSize = 1 in {   // Can xform into LEA.
    563 def DEC16r : I<0x48, AddRegFrm, (outs GR16:$dst), (ins GR16:$src1),
    564                "dec{w}\t$dst",
    565                [(set GR16:$dst, EFLAGS, (X86dec_flag GR16:$src1))],
    566                IIC_UNARY_REG>,
    567              OpSize16, Requires<[Not64BitMode]>;
    568 def DEC32r : I<0x48, AddRegFrm, (outs GR32:$dst), (ins GR32:$src1),
    569                "dec{l}\t$dst",
    570                [(set GR32:$dst, EFLAGS, (X86dec_flag GR32:$src1))],
    571                IIC_UNARY_REG>,
    572              OpSize32, Requires<[Not64BitMode]>;
    573 def DEC64r : RI<0xFF, MRM1r, (outs GR64:$dst), (ins GR64:$src1), "dec{q}\t$dst",
    574                 [(set GR64:$dst, EFLAGS, (X86dec_flag GR64:$src1))],
    575                 IIC_UNARY_REG>;
    576 } // CodeSize = 2
    577 } // Constraints = "$src1 = $dst", SchedRW
    578 
    579 
    580 let CodeSize = 2, SchedRW = [WriteALULd, WriteRMW] in {
    581   def DEC8m  : I<0xFE, MRM1m, (outs), (ins i8mem :$dst), "dec{b}\t$dst",
    582                [(store (add (loadi8 addr:$dst), -1), addr:$dst),
    583                 (implicit EFLAGS)], IIC_UNARY_MEM>;
    584   def DEC16m : I<0xFF, MRM1m, (outs), (ins i16mem:$dst), "dec{w}\t$dst",
    585                [(store (add (loadi16 addr:$dst), -1), addr:$dst),
    586                 (implicit EFLAGS)], IIC_UNARY_MEM>,
    587                OpSize16, Requires<[Not64BitMode]>;
    588   def DEC32m : I<0xFF, MRM1m, (outs), (ins i32mem:$dst), "dec{l}\t$dst",
    589                [(store (add (loadi32 addr:$dst), -1), addr:$dst),
    590                 (implicit EFLAGS)], IIC_UNARY_MEM>,
    591                OpSize32, Requires<[Not64BitMode]>;
    592   def DEC64m : RI<0xFF, MRM1m, (outs), (ins i64mem:$dst), "dec{q}\t$dst",
    593                   [(store (add (loadi64 addr:$dst), -1), addr:$dst),
    594                    (implicit EFLAGS)], IIC_UNARY_MEM>;
    595 } // CodeSize = 2, SchedRW
    596 } // Defs = [EFLAGS]
    597 
    598 /// X86TypeInfo - This is a bunch of information that describes relevant X86
    599 /// information about value types.  For example, it can tell you what the
    600 /// register class and preferred load to use.
    601 class X86TypeInfo<ValueType vt, string instrsuffix, RegisterClass regclass,
    602                   PatFrag loadnode, X86MemOperand memoperand, ImmType immkind,
    603                   Operand immoperand, SDPatternOperator immoperator,
    604                   Operand imm8operand, SDPatternOperator imm8operator,
    605                   bit hasOddOpcode, OperandSize opSize,
    606                   bit hasREX_WPrefix> {
    607   /// VT - This is the value type itself.
    608   ValueType VT = vt;
    609 
    610   /// InstrSuffix - This is the suffix used on instructions with this type.  For
    611   /// example, i8 -> "b", i16 -> "w", i32 -> "l", i64 -> "q".
    612   string InstrSuffix = instrsuffix;
    613 
    614   /// RegClass - This is the register class associated with this type.  For
    615   /// example, i8 -> GR8, i16 -> GR16, i32 -> GR32, i64 -> GR64.
    616   RegisterClass RegClass = regclass;
    617 
    618   /// LoadNode - This is the load node associated with this type.  For
    619   /// example, i8 -> loadi8, i16 -> loadi16, i32 -> loadi32, i64 -> loadi64.
    620   PatFrag LoadNode = loadnode;
    621 
    622   /// MemOperand - This is the memory operand associated with this type.  For
    623   /// example, i8 -> i8mem, i16 -> i16mem, i32 -> i32mem, i64 -> i64mem.
    624   X86MemOperand MemOperand = memoperand;
    625 
    626   /// ImmEncoding - This is the encoding of an immediate of this type.  For
    627   /// example, i8 -> Imm8, i16 -> Imm16, i32 -> Imm32.  Note that i64 -> Imm32
    628   /// since the immediate fields of i64 instructions is a 32-bit sign extended
    629   /// value.
    630   ImmType ImmEncoding = immkind;
    631 
    632   /// ImmOperand - This is the operand kind of an immediate of this type.  For
    633   /// example, i8 -> i8imm, i16 -> i16imm, i32 -> i32imm.  Note that i64 ->
    634   /// i64i32imm since the immediate fields of i64 instructions is a 32-bit sign
    635   /// extended value.
    636   Operand ImmOperand = immoperand;
    637 
    638   /// ImmOperator - This is the operator that should be used to match an
    639   /// immediate of this kind in a pattern (e.g. imm, or i64immSExt32).
    640   SDPatternOperator ImmOperator = immoperator;
    641 
    642   /// Imm8Operand - This is the operand kind to use for an imm8 of this type.
    643   /// For example, i8 -> <invalid>, i16 -> i16i8imm, i32 -> i32i8imm.  This is
    644   /// only used for instructions that have a sign-extended imm8 field form.
    645   Operand Imm8Operand = imm8operand;
    646 
    647   /// Imm8Operator - This is the operator that should be used to match an 8-bit
    648   /// sign extended immediate of this kind in a pattern (e.g. imm16immSExt8).
    649   SDPatternOperator Imm8Operator = imm8operator;
    650 
    651   /// HasOddOpcode - This bit is true if the instruction should have an odd (as
    652   /// opposed to even) opcode.  Operations on i8 are usually even, operations on
    653   /// other datatypes are odd.
    654   bit HasOddOpcode = hasOddOpcode;
    655 
    656   /// OpSize - Selects whether the instruction needs a 0x66 prefix based on
    657   /// 16-bit vs 32-bit mode. i8/i64 set this to OpSizeFixed. i16 sets this
    658   /// to Opsize16. i32 sets this to OpSize32.
    659   OperandSize OpSize = opSize;
    660 
    661   /// HasREX_WPrefix - This bit is set to true if the instruction should have
    662   /// the 0x40 REX prefix.  This is set for i64 types.
    663   bit HasREX_WPrefix = hasREX_WPrefix;
    664 }
    665 
    666 def invalid_node : SDNode<"<<invalid_node>>", SDTIntLeaf,[],"<<invalid_node>>">;
    667 
    668 
    669 def Xi8  : X86TypeInfo<i8 , "b", GR8 , loadi8 , i8mem ,
    670                        Imm8 , i8imm ,    imm,          i8imm   , invalid_node,
    671                        0, OpSizeFixed, 0>;
    672 def Xi16 : X86TypeInfo<i16, "w", GR16, loadi16, i16mem,
    673                        Imm16, i16imm,    imm,          i16i8imm, i16immSExt8,
    674                        1, OpSize16, 0>;
    675 def Xi32 : X86TypeInfo<i32, "l", GR32, loadi32, i32mem,
    676                        Imm32, i32imm,    imm,          i32i8imm, i32immSExt8,
    677                        1, OpSize32, 0>;
    678 def Xi64 : X86TypeInfo<i64, "q", GR64, loadi64, i64mem,
    679                        Imm32S, i64i32imm, i64immSExt32, i64i8imm, i64immSExt8,
    680                        1, OpSizeFixed, 1>;
    681 
    682 /// ITy - This instruction base class takes the type info for the instruction.
    683 /// Using this, it:
    684 /// 1. Concatenates together the instruction mnemonic with the appropriate
    685 ///    suffix letter, a tab, and the arguments.
    686 /// 2. Infers whether the instruction should have a 0x66 prefix byte.
    687 /// 3. Infers whether the instruction should have a 0x40 REX_W prefix.
    688 /// 4. Infers whether the low bit of the opcode should be 0 (for i8 operations)
    689 ///    or 1 (for i16,i32,i64 operations).
    690 class ITy<bits<8> opcode, Format f, X86TypeInfo typeinfo, dag outs, dag ins,
    691           string mnemonic, string args, list<dag> pattern,
    692           InstrItinClass itin = IIC_BIN_NONMEM>
    693   : I<{opcode{7}, opcode{6}, opcode{5}, opcode{4},
    694        opcode{3}, opcode{2}, opcode{1}, typeinfo.HasOddOpcode },
    695       f, outs, ins,
    696       !strconcat(mnemonic, "{", typeinfo.InstrSuffix, "}\t", args), pattern,
    697       itin> {
    698 
    699   // Infer instruction prefixes from type info.
    700   let OpSize = typeinfo.OpSize;
    701   let hasREX_WPrefix  = typeinfo.HasREX_WPrefix;
    702 }
    703 
    704 // BinOpRR - Instructions like "add reg, reg, reg".
    705 class BinOpRR<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    706               dag outlist, list<dag> pattern, InstrItinClass itin,
    707               Format f = MRMDestReg>
    708   : ITy<opcode, f, typeinfo, outlist,
    709         (ins typeinfo.RegClass:$src1, typeinfo.RegClass:$src2),
    710         mnemonic, "{$src2, $src1|$src1, $src2}", pattern, itin>,
    711     Sched<[WriteALU]>;
    712 
    713 // BinOpRR_R - Instructions like "add reg, reg, reg", where the pattern has
    714 // just a regclass (no eflags) as a result.
    715 class BinOpRR_R<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    716                 SDNode opnode>
    717   : BinOpRR<opcode, mnemonic, typeinfo, (outs typeinfo.RegClass:$dst),
    718             [(set typeinfo.RegClass:$dst,
    719                   (opnode typeinfo.RegClass:$src1, typeinfo.RegClass:$src2))],
    720                   IIC_BIN_NONMEM>;
    721 
    722 // BinOpRR_F - Instructions like "cmp reg, Reg", where the pattern has
    723 // just a EFLAGS as a result.
    724 class BinOpRR_F<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    725                 SDPatternOperator opnode, Format f = MRMDestReg>
    726   : BinOpRR<opcode, mnemonic, typeinfo, (outs),
    727             [(set EFLAGS,
    728                   (opnode typeinfo.RegClass:$src1, typeinfo.RegClass:$src2))],
    729             IIC_BIN_NONMEM, f>;
    730 
    731 // BinOpRR_RF - Instructions like "add reg, reg, reg", where the pattern has
    732 // both a regclass and EFLAGS as a result.
    733 class BinOpRR_RF<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    734                  SDNode opnode>
    735   : BinOpRR<opcode, mnemonic, typeinfo, (outs typeinfo.RegClass:$dst),
    736             [(set typeinfo.RegClass:$dst, EFLAGS,
    737                   (opnode typeinfo.RegClass:$src1, typeinfo.RegClass:$src2))],
    738                   IIC_BIN_NONMEM>;
    739 
    740 // BinOpRR_RFF - Instructions like "adc reg, reg, reg", where the pattern has
    741 // both a regclass and EFLAGS as a result, and has EFLAGS as input.
    742 class BinOpRR_RFF<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    743                   SDNode opnode>
    744   : BinOpRR<opcode, mnemonic, typeinfo, (outs typeinfo.RegClass:$dst),
    745             [(set typeinfo.RegClass:$dst, EFLAGS,
    746                   (opnode typeinfo.RegClass:$src1, typeinfo.RegClass:$src2,
    747                           EFLAGS))], IIC_BIN_CARRY_NONMEM>;
    748 
    749 // BinOpRR_Rev - Instructions like "add reg, reg, reg" (reversed encoding).
    750 class BinOpRR_Rev<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    751                  InstrItinClass itin = IIC_BIN_NONMEM>
    752   : ITy<opcode, MRMSrcReg, typeinfo,
    753         (outs typeinfo.RegClass:$dst),
    754         (ins typeinfo.RegClass:$src1, typeinfo.RegClass:$src2),
    755         mnemonic, "{$src2, $dst|$dst, $src2}", [], itin>,
    756     Sched<[WriteALU]> {
    757   // The disassembler should know about this, but not the asmparser.
    758   let isCodeGenOnly = 1;
    759   let ForceDisassemble = 1;
    760   let hasSideEffects = 0;
    761 }
    762 
    763 // BinOpRR_RDD_Rev - Instructions like "adc reg, reg, reg" (reversed encoding).
    764 class BinOpRR_RFF_Rev<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo>
    765   : BinOpRR_Rev<opcode, mnemonic, typeinfo, IIC_BIN_CARRY_NONMEM>;
    766 
    767 // BinOpRR_F_Rev - Instructions like "cmp reg, reg" (reversed encoding).
    768 class BinOpRR_F_Rev<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo>
    769   : ITy<opcode, MRMSrcReg, typeinfo, (outs),
    770         (ins typeinfo.RegClass:$src1, typeinfo.RegClass:$src2),
    771         mnemonic, "{$src2, $src1|$src1, $src2}", [], IIC_BIN_NONMEM>,
    772     Sched<[WriteALU]> {
    773   // The disassembler should know about this, but not the asmparser.
    774   let isCodeGenOnly = 1;
    775   let ForceDisassemble = 1;
    776   let hasSideEffects = 0;
    777 }
    778 
    779 // BinOpRM - Instructions like "add reg, reg, [mem]".
    780 class BinOpRM<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    781               dag outlist, list<dag> pattern,
    782               InstrItinClass itin = IIC_BIN_MEM>
    783   : ITy<opcode, MRMSrcMem, typeinfo, outlist,
    784         (ins typeinfo.RegClass:$src1, typeinfo.MemOperand:$src2),
    785         mnemonic, "{$src2, $src1|$src1, $src2}", pattern, itin>,
    786     Sched<[WriteALULd, ReadAfterLd]>;
    787 
    788 // BinOpRM_R - Instructions like "add reg, reg, [mem]".
    789 class BinOpRM_R<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    790               SDNode opnode>
    791   : BinOpRM<opcode, mnemonic, typeinfo, (outs typeinfo.RegClass:$dst),
    792             [(set typeinfo.RegClass:$dst,
    793             (opnode typeinfo.RegClass:$src1, (typeinfo.LoadNode addr:$src2)))]>;
    794 
    795 // BinOpRM_F - Instructions like "cmp reg, [mem]".
    796 class BinOpRM_F<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    797               SDPatternOperator opnode>
    798   : BinOpRM<opcode, mnemonic, typeinfo, (outs),
    799             [(set EFLAGS,
    800             (opnode typeinfo.RegClass:$src1, (typeinfo.LoadNode addr:$src2)))]>;
    801 
    802 // BinOpRM_RF - Instructions like "add reg, reg, [mem]".
    803 class BinOpRM_RF<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    804                  SDNode opnode>
    805   : BinOpRM<opcode, mnemonic, typeinfo, (outs typeinfo.RegClass:$dst),
    806             [(set typeinfo.RegClass:$dst, EFLAGS,
    807             (opnode typeinfo.RegClass:$src1, (typeinfo.LoadNode addr:$src2)))]>;
    808 
    809 // BinOpRM_RFF - Instructions like "adc reg, reg, [mem]".
    810 class BinOpRM_RFF<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    811                  SDNode opnode>
    812   : BinOpRM<opcode, mnemonic, typeinfo, (outs typeinfo.RegClass:$dst),
    813             [(set typeinfo.RegClass:$dst, EFLAGS,
    814             (opnode typeinfo.RegClass:$src1, (typeinfo.LoadNode addr:$src2),
    815                     EFLAGS))], IIC_BIN_CARRY_MEM>;
    816 
    817 // BinOpRI - Instructions like "add reg, reg, imm".
    818 class BinOpRI<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    819               Format f, dag outlist, list<dag> pattern,
    820               InstrItinClass itin = IIC_BIN_NONMEM>
    821   : ITy<opcode, f, typeinfo, outlist,
    822         (ins typeinfo.RegClass:$src1, typeinfo.ImmOperand:$src2),
    823         mnemonic, "{$src2, $src1|$src1, $src2}", pattern, itin>,
    824     Sched<[WriteALU]> {
    825   let ImmT = typeinfo.ImmEncoding;
    826 }
    827 
    828 // BinOpRI_R - Instructions like "add reg, reg, imm".
    829 class BinOpRI_R<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    830                 SDNode opnode, Format f>
    831   : BinOpRI<opcode, mnemonic, typeinfo, f, (outs typeinfo.RegClass:$dst),
    832             [(set typeinfo.RegClass:$dst,
    833                 (opnode typeinfo.RegClass:$src1, typeinfo.ImmOperator:$src2))]>;
    834 
    835 // BinOpRI_F - Instructions like "cmp reg, imm".
    836 class BinOpRI_F<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    837                 SDPatternOperator opnode, Format f>
    838   : BinOpRI<opcode, mnemonic, typeinfo, f, (outs),
    839             [(set EFLAGS,
    840                 (opnode typeinfo.RegClass:$src1, typeinfo.ImmOperator:$src2))]>;
    841 
    842 // BinOpRI_RF - Instructions like "add reg, reg, imm".
    843 class BinOpRI_RF<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    844                  SDNode opnode, Format f>
    845   : BinOpRI<opcode, mnemonic, typeinfo, f, (outs typeinfo.RegClass:$dst),
    846             [(set typeinfo.RegClass:$dst, EFLAGS,
    847                 (opnode typeinfo.RegClass:$src1, typeinfo.ImmOperator:$src2))]>;
    848 // BinOpRI_RFF - Instructions like "adc reg, reg, imm".
    849 class BinOpRI_RFF<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    850                  SDNode opnode, Format f>
    851   : BinOpRI<opcode, mnemonic, typeinfo, f, (outs typeinfo.RegClass:$dst),
    852             [(set typeinfo.RegClass:$dst, EFLAGS,
    853                 (opnode typeinfo.RegClass:$src1, typeinfo.ImmOperator:$src2,
    854                         EFLAGS))], IIC_BIN_CARRY_NONMEM>;
    855 
    856 // BinOpRI8 - Instructions like "add reg, reg, imm8".
    857 class BinOpRI8<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    858                Format f, dag outlist, list<dag> pattern,
    859                InstrItinClass itin = IIC_BIN_NONMEM>
    860   : ITy<opcode, f, typeinfo, outlist,
    861         (ins typeinfo.RegClass:$src1, typeinfo.Imm8Operand:$src2),
    862         mnemonic, "{$src2, $src1|$src1, $src2}", pattern, itin>,
    863     Sched<[WriteALU]> {
    864   let ImmT = Imm8; // Always 8-bit immediate.
    865 }
    866 
    867 // BinOpRI8_R - Instructions like "add reg, reg, imm8".
    868 class BinOpRI8_R<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    869                   SDNode opnode, Format f>
    870   : BinOpRI8<opcode, mnemonic, typeinfo, f, (outs typeinfo.RegClass:$dst),
    871              [(set typeinfo.RegClass:$dst,
    872                (opnode typeinfo.RegClass:$src1, typeinfo.Imm8Operator:$src2))]>;
    873 
    874 // BinOpRI8_F - Instructions like "cmp reg, imm8".
    875 class BinOpRI8_F<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    876                   SDNode opnode, Format f>
    877   : BinOpRI8<opcode, mnemonic, typeinfo, f, (outs),
    878              [(set EFLAGS,
    879                (opnode typeinfo.RegClass:$src1, typeinfo.Imm8Operator:$src2))]>;
    880 
    881 // BinOpRI8_RF - Instructions like "add reg, reg, imm8".
    882 class BinOpRI8_RF<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    883                   SDNode opnode, Format f>
    884   : BinOpRI8<opcode, mnemonic, typeinfo, f, (outs typeinfo.RegClass:$dst),
    885              [(set typeinfo.RegClass:$dst, EFLAGS,
    886                (opnode typeinfo.RegClass:$src1, typeinfo.Imm8Operator:$src2))]>;
    887 
    888 // BinOpRI8_RFF - Instructions like "adc reg, reg, imm8".
    889 class BinOpRI8_RFF<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    890                    SDNode opnode, Format f>
    891   : BinOpRI8<opcode, mnemonic, typeinfo, f, (outs typeinfo.RegClass:$dst),
    892              [(set typeinfo.RegClass:$dst, EFLAGS,
    893                (opnode typeinfo.RegClass:$src1, typeinfo.Imm8Operator:$src2,
    894                        EFLAGS))], IIC_BIN_CARRY_NONMEM>;
    895 
    896 // BinOpMR - Instructions like "add [mem], reg".
    897 class BinOpMR<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    898               list<dag> pattern, InstrItinClass itin = IIC_BIN_MEM>
    899   : ITy<opcode, MRMDestMem, typeinfo,
    900         (outs), (ins typeinfo.MemOperand:$dst, typeinfo.RegClass:$src),
    901         mnemonic, "{$src, $dst|$dst, $src}", pattern, itin>,
    902     Sched<[WriteALULd, WriteRMW]>;
    903 
    904 // BinOpMR_RMW - Instructions like "add [mem], reg".
    905 class BinOpMR_RMW<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    906                   SDNode opnode>
    907   : BinOpMR<opcode, mnemonic, typeinfo,
    908           [(store (opnode (load addr:$dst), typeinfo.RegClass:$src), addr:$dst),
    909            (implicit EFLAGS)]>;
    910 
    911 // BinOpMR_RMW_FF - Instructions like "adc [mem], reg".
    912 class BinOpMR_RMW_FF<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    913                     SDNode opnode>
    914   : BinOpMR<opcode, mnemonic, typeinfo,
    915           [(store (opnode (load addr:$dst), typeinfo.RegClass:$src, EFLAGS),
    916                   addr:$dst),
    917            (implicit EFLAGS)], IIC_BIN_CARRY_MEM>;
    918 
    919 // BinOpMR_F - Instructions like "cmp [mem], reg".
    920 class BinOpMR_F<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    921                   SDNode opnode>
    922   : BinOpMR<opcode, mnemonic, typeinfo,
    923             [(set EFLAGS, (opnode (load addr:$dst), typeinfo.RegClass:$src))]>;
    924 
    925 // BinOpMI - Instructions like "add [mem], imm".
    926 class BinOpMI<string mnemonic, X86TypeInfo typeinfo,
    927               Format f, list<dag> pattern, bits<8> opcode = 0x80,
    928               InstrItinClass itin = IIC_BIN_MEM>
    929   : ITy<opcode, f, typeinfo,
    930         (outs), (ins typeinfo.MemOperand:$dst, typeinfo.ImmOperand:$src),
    931         mnemonic, "{$src, $dst|$dst, $src}", pattern, itin>,
    932     Sched<[WriteALULd, WriteRMW]> {
    933   let ImmT = typeinfo.ImmEncoding;
    934 }
    935 
    936 // BinOpMI_RMW - Instructions like "add [mem], imm".
    937 class BinOpMI_RMW<string mnemonic, X86TypeInfo typeinfo,
    938                   SDNode opnode, Format f>
    939   : BinOpMI<mnemonic, typeinfo, f,
    940             [(store (opnode (typeinfo.VT (load addr:$dst)),
    941                             typeinfo.ImmOperator:$src), addr:$dst),
    942              (implicit EFLAGS)]>;
    943 // BinOpMI_RMW_FF - Instructions like "adc [mem], imm".
    944 class BinOpMI_RMW_FF<string mnemonic, X86TypeInfo typeinfo,
    945                   SDNode opnode, Format f>
    946   : BinOpMI<mnemonic, typeinfo, f,
    947             [(store (opnode (typeinfo.VT (load addr:$dst)),
    948                             typeinfo.ImmOperator:$src, EFLAGS), addr:$dst),
    949              (implicit EFLAGS)], 0x80, IIC_BIN_CARRY_MEM>;
    950 
    951 // BinOpMI_F - Instructions like "cmp [mem], imm".
    952 class BinOpMI_F<string mnemonic, X86TypeInfo typeinfo,
    953                 SDPatternOperator opnode, Format f, bits<8> opcode = 0x80>
    954   : BinOpMI<mnemonic, typeinfo, f,
    955             [(set EFLAGS, (opnode (typeinfo.VT (load addr:$dst)),
    956                                                typeinfo.ImmOperator:$src))],
    957             opcode>;
    958 
    959 // BinOpMI8 - Instructions like "add [mem], imm8".
    960 class BinOpMI8<string mnemonic, X86TypeInfo typeinfo,
    961                Format f, list<dag> pattern,
    962                InstrItinClass itin = IIC_BIN_MEM>
    963   : ITy<0x82, f, typeinfo,
    964         (outs), (ins typeinfo.MemOperand:$dst, typeinfo.Imm8Operand:$src),
    965         mnemonic, "{$src, $dst|$dst, $src}", pattern, itin>,
    966     Sched<[WriteALULd, WriteRMW]> {
    967   let ImmT = Imm8; // Always 8-bit immediate.
    968 }
    969 
    970 // BinOpMI8_RMW - Instructions like "add [mem], imm8".
    971 class BinOpMI8_RMW<string mnemonic, X86TypeInfo typeinfo,
    972                    SDNode opnode, Format f>
    973   : BinOpMI8<mnemonic, typeinfo, f,
    974              [(store (opnode (load addr:$dst),
    975                              typeinfo.Imm8Operator:$src), addr:$dst),
    976               (implicit EFLAGS)]>;
    977 
    978 // BinOpMI8_RMW_FF - Instructions like "adc [mem], imm8".
    979 class BinOpMI8_RMW_FF<string mnemonic, X86TypeInfo typeinfo,
    980                    SDNode opnode, Format f>
    981   : BinOpMI8<mnemonic, typeinfo, f,
    982              [(store (opnode (load addr:$dst),
    983                              typeinfo.Imm8Operator:$src, EFLAGS), addr:$dst),
    984               (implicit EFLAGS)], IIC_BIN_CARRY_MEM>;
    985 
    986 // BinOpMI8_F - Instructions like "cmp [mem], imm8".
    987 class BinOpMI8_F<string mnemonic, X86TypeInfo typeinfo,
    988                  SDNode opnode, Format f>
    989   : BinOpMI8<mnemonic, typeinfo, f,
    990              [(set EFLAGS, (opnode (load addr:$dst),
    991                                    typeinfo.Imm8Operator:$src))]>;
    992 
    993 // BinOpAI - Instructions like "add %eax, %eax, imm", that imp-def EFLAGS.
    994 class BinOpAI<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
    995               Register areg, string operands,
    996               InstrItinClass itin = IIC_BIN_NONMEM>
    997   : ITy<opcode, RawFrm, typeinfo,
    998         (outs), (ins typeinfo.ImmOperand:$src),
    999         mnemonic, operands, [], itin>, Sched<[WriteALU]> {
   1000   let ImmT = typeinfo.ImmEncoding;
   1001   let Uses = [areg];
   1002   let Defs = [areg, EFLAGS];
   1003   let hasSideEffects = 0;
   1004 }
   1005 
   1006 // BinOpAI_FF - Instructions like "adc %eax, %eax, imm", that implicitly define
   1007 // and use EFLAGS.
   1008 class BinOpAI_FF<bits<8> opcode, string mnemonic, X86TypeInfo typeinfo,
   1009                 Register areg, string operands>
   1010   : BinOpAI<opcode, mnemonic, typeinfo, areg, operands,
   1011             IIC_BIN_CARRY_NONMEM> {
   1012   let Uses = [areg, EFLAGS];
   1013 }
   1014 
   1015 /// ArithBinOp_RF - This is an arithmetic binary operator where the pattern is
   1016 /// defined with "(set GPR:$dst, EFLAGS, (...".
   1017 ///
   1018 /// It would be nice to get rid of the second and third argument here, but
   1019 /// tblgen can't handle dependent type references aggressively enough: PR8330
   1020 multiclass ArithBinOp_RF<bits<8> BaseOpc, bits<8> BaseOpc2, bits<8> BaseOpc4,
   1021                          string mnemonic, Format RegMRM, Format MemMRM,
   1022                          SDNode opnodeflag, SDNode opnode,
   1023                          bit CommutableRR, bit ConvertibleToThreeAddress> {
   1024   let Defs = [EFLAGS] in {
   1025     let Constraints = "$src1 = $dst" in {
   1026       let isCommutable = CommutableRR,
   1027           isConvertibleToThreeAddress = ConvertibleToThreeAddress in {
   1028         def NAME#8rr  : BinOpRR_RF<BaseOpc, mnemonic, Xi8 , opnodeflag>;
   1029         def NAME#16rr : BinOpRR_RF<BaseOpc, mnemonic, Xi16, opnodeflag>;
   1030         def NAME#32rr : BinOpRR_RF<BaseOpc, mnemonic, Xi32, opnodeflag>;
   1031         def NAME#64rr : BinOpRR_RF<BaseOpc, mnemonic, Xi64, opnodeflag>;
   1032       } // isCommutable
   1033 
   1034       def NAME#8rr_REV  : BinOpRR_Rev<BaseOpc2, mnemonic, Xi8>;
   1035       def NAME#16rr_REV : BinOpRR_Rev<BaseOpc2, mnemonic, Xi16>;
   1036       def NAME#32rr_REV : BinOpRR_Rev<BaseOpc2, mnemonic, Xi32>;
   1037       def NAME#64rr_REV : BinOpRR_Rev<BaseOpc2, mnemonic, Xi64>;
   1038 
   1039       def NAME#8rm   : BinOpRM_RF<BaseOpc2, mnemonic, Xi8 , opnodeflag>;
   1040       def NAME#16rm  : BinOpRM_RF<BaseOpc2, mnemonic, Xi16, opnodeflag>;
   1041       def NAME#32rm  : BinOpRM_RF<BaseOpc2, mnemonic, Xi32, opnodeflag>;
   1042       def NAME#64rm  : BinOpRM_RF<BaseOpc2, mnemonic, Xi64, opnodeflag>;
   1043 
   1044       let isConvertibleToThreeAddress = ConvertibleToThreeAddress in {
   1045         // NOTE: These are order specific, we want the ri8 forms to be listed
   1046         // first so that they are slightly preferred to the ri forms.
   1047         def NAME#16ri8 : BinOpRI8_RF<0x82, mnemonic, Xi16, opnodeflag, RegMRM>;
   1048         def NAME#32ri8 : BinOpRI8_RF<0x82, mnemonic, Xi32, opnodeflag, RegMRM>;
   1049         def NAME#64ri8 : BinOpRI8_RF<0x82, mnemonic, Xi64, opnodeflag, RegMRM>;
   1050 
   1051         def NAME#8ri   : BinOpRI_RF<0x80, mnemonic, Xi8 , opnodeflag, RegMRM>;
   1052         def NAME#16ri  : BinOpRI_RF<0x80, mnemonic, Xi16, opnodeflag, RegMRM>;
   1053         def NAME#32ri  : BinOpRI_RF<0x80, mnemonic, Xi32, opnodeflag, RegMRM>;
   1054         def NAME#64ri32: BinOpRI_RF<0x80, mnemonic, Xi64, opnodeflag, RegMRM>;
   1055       }
   1056     } // Constraints = "$src1 = $dst"
   1057 
   1058     def NAME#8mr    : BinOpMR_RMW<BaseOpc, mnemonic, Xi8 , opnode>;
   1059     def NAME#16mr   : BinOpMR_RMW<BaseOpc, mnemonic, Xi16, opnode>;
   1060     def NAME#32mr   : BinOpMR_RMW<BaseOpc, mnemonic, Xi32, opnode>;
   1061     def NAME#64mr   : BinOpMR_RMW<BaseOpc, mnemonic, Xi64, opnode>;
   1062 
   1063     // NOTE: These are order specific, we want the mi8 forms to be listed
   1064     // first so that they are slightly preferred to the mi forms.
   1065     def NAME#16mi8  : BinOpMI8_RMW<mnemonic, Xi16, opnode, MemMRM>;
   1066     def NAME#32mi8  : BinOpMI8_RMW<mnemonic, Xi32, opnode, MemMRM>;
   1067     def NAME#64mi8  : BinOpMI8_RMW<mnemonic, Xi64, opnode, MemMRM>;
   1068 
   1069     def NAME#8mi    : BinOpMI_RMW<mnemonic, Xi8 , opnode, MemMRM>;
   1070     def NAME#16mi   : BinOpMI_RMW<mnemonic, Xi16, opnode, MemMRM>;
   1071     def NAME#32mi   : BinOpMI_RMW<mnemonic, Xi32, opnode, MemMRM>;
   1072     def NAME#64mi32 : BinOpMI_RMW<mnemonic, Xi64, opnode, MemMRM>;
   1073   } // Defs = [EFLAGS]
   1074 
   1075   def NAME#8i8   : BinOpAI<BaseOpc4, mnemonic, Xi8 , AL,
   1076                            "{$src, %al|al, $src}">;
   1077   def NAME#16i16 : BinOpAI<BaseOpc4, mnemonic, Xi16, AX,
   1078                            "{$src, %ax|ax, $src}">;
   1079   def NAME#32i32 : BinOpAI<BaseOpc4, mnemonic, Xi32, EAX,
   1080                            "{$src, %eax|eax, $src}">;
   1081   def NAME#64i32 : BinOpAI<BaseOpc4, mnemonic, Xi64, RAX,
   1082                            "{$src, %rax|rax, $src}">;
   1083 }
   1084 
   1085 /// ArithBinOp_RFF - This is an arithmetic binary operator where the pattern is
   1086 /// defined with "(set GPR:$dst, EFLAGS, (node LHS, RHS, EFLAGS))" like ADC and
   1087 /// SBB.
   1088 ///
   1089 /// It would be nice to get rid of the second and third argument here, but
   1090 /// tblgen can't handle dependent type references aggressively enough: PR8330
   1091 multiclass ArithBinOp_RFF<bits<8> BaseOpc, bits<8> BaseOpc2, bits<8> BaseOpc4,
   1092                           string mnemonic, Format RegMRM, Format MemMRM,
   1093                           SDNode opnode, bit CommutableRR,
   1094                            bit ConvertibleToThreeAddress> {
   1095   let Uses = [EFLAGS], Defs = [EFLAGS] in {
   1096     let Constraints = "$src1 = $dst" in {
   1097       let isCommutable = CommutableRR,
   1098           isConvertibleToThreeAddress = ConvertibleToThreeAddress in {
   1099         def NAME#8rr  : BinOpRR_RFF<BaseOpc, mnemonic, Xi8 , opnode>;
   1100         def NAME#16rr : BinOpRR_RFF<BaseOpc, mnemonic, Xi16, opnode>;
   1101         def NAME#32rr : BinOpRR_RFF<BaseOpc, mnemonic, Xi32, opnode>;
   1102         def NAME#64rr : BinOpRR_RFF<BaseOpc, mnemonic, Xi64, opnode>;
   1103       } // isCommutable
   1104 
   1105       def NAME#8rr_REV  : BinOpRR_RFF_Rev<BaseOpc2, mnemonic, Xi8>;
   1106       def NAME#16rr_REV : BinOpRR_RFF_Rev<BaseOpc2, mnemonic, Xi16>;
   1107       def NAME#32rr_REV : BinOpRR_RFF_Rev<BaseOpc2, mnemonic, Xi32>;
   1108       def NAME#64rr_REV : BinOpRR_RFF_Rev<BaseOpc2, mnemonic, Xi64>;
   1109 
   1110       def NAME#8rm   : BinOpRM_RFF<BaseOpc2, mnemonic, Xi8 , opnode>;
   1111       def NAME#16rm  : BinOpRM_RFF<BaseOpc2, mnemonic, Xi16, opnode>;
   1112       def NAME#32rm  : BinOpRM_RFF<BaseOpc2, mnemonic, Xi32, opnode>;
   1113       def NAME#64rm  : BinOpRM_RFF<BaseOpc2, mnemonic, Xi64, opnode>;
   1114 
   1115       let isConvertibleToThreeAddress = ConvertibleToThreeAddress in {
   1116         // NOTE: These are order specific, we want the ri8 forms to be listed
   1117         // first so that they are slightly preferred to the ri forms.
   1118         def NAME#16ri8 : BinOpRI8_RFF<0x82, mnemonic, Xi16, opnode, RegMRM>;
   1119         def NAME#32ri8 : BinOpRI8_RFF<0x82, mnemonic, Xi32, opnode, RegMRM>;
   1120         def NAME#64ri8 : BinOpRI8_RFF<0x82, mnemonic, Xi64, opnode, RegMRM>;
   1121 
   1122         def NAME#8ri   : BinOpRI_RFF<0x80, mnemonic, Xi8 , opnode, RegMRM>;
   1123         def NAME#16ri  : BinOpRI_RFF<0x80, mnemonic, Xi16, opnode, RegMRM>;
   1124         def NAME#32ri  : BinOpRI_RFF<0x80, mnemonic, Xi32, opnode, RegMRM>;
   1125         def NAME#64ri32: BinOpRI_RFF<0x80, mnemonic, Xi64, opnode, RegMRM>;
   1126       }
   1127     } // Constraints = "$src1 = $dst"
   1128 
   1129     def NAME#8mr    : BinOpMR_RMW_FF<BaseOpc, mnemonic, Xi8 , opnode>;
   1130     def NAME#16mr   : BinOpMR_RMW_FF<BaseOpc, mnemonic, Xi16, opnode>;
   1131     def NAME#32mr   : BinOpMR_RMW_FF<BaseOpc, mnemonic, Xi32, opnode>;
   1132     def NAME#64mr   : BinOpMR_RMW_FF<BaseOpc, mnemonic, Xi64, opnode>;
   1133 
   1134     // NOTE: These are order specific, we want the mi8 forms to be listed
   1135     // first so that they are slightly preferred to the mi forms.
   1136     def NAME#16mi8  : BinOpMI8_RMW_FF<mnemonic, Xi16, opnode, MemMRM>;
   1137     def NAME#32mi8  : BinOpMI8_RMW_FF<mnemonic, Xi32, opnode, MemMRM>;
   1138     def NAME#64mi8  : BinOpMI8_RMW_FF<mnemonic, Xi64, opnode, MemMRM>;
   1139 
   1140     def NAME#8mi    : BinOpMI_RMW_FF<mnemonic, Xi8 , opnode, MemMRM>;
   1141     def NAME#16mi   : BinOpMI_RMW_FF<mnemonic, Xi16, opnode, MemMRM>;
   1142     def NAME#32mi   : BinOpMI_RMW_FF<mnemonic, Xi32, opnode, MemMRM>;
   1143     def NAME#64mi32 : BinOpMI_RMW_FF<mnemonic, Xi64, opnode, MemMRM>;
   1144   } // Uses = [EFLAGS], Defs = [EFLAGS]
   1145 
   1146   def NAME#8i8   : BinOpAI_FF<BaseOpc4, mnemonic, Xi8 , AL,
   1147                               "{$src, %al|al, $src}">;
   1148   def NAME#16i16 : BinOpAI_FF<BaseOpc4, mnemonic, Xi16, AX,
   1149                               "{$src, %ax|ax, $src}">;
   1150   def NAME#32i32 : BinOpAI_FF<BaseOpc4, mnemonic, Xi32, EAX,
   1151                               "{$src, %eax|eax, $src}">;
   1152   def NAME#64i32 : BinOpAI_FF<BaseOpc4, mnemonic, Xi64, RAX,
   1153                               "{$src, %rax|rax, $src}">;
   1154 }
   1155 
   1156 /// ArithBinOp_F - This is an arithmetic binary operator where the pattern is
   1157 /// defined with "(set EFLAGS, (...".  It would be really nice to find a way
   1158 /// to factor this with the other ArithBinOp_*.
   1159 ///
   1160 multiclass ArithBinOp_F<bits<8> BaseOpc, bits<8> BaseOpc2, bits<8> BaseOpc4,
   1161                         string mnemonic, Format RegMRM, Format MemMRM,
   1162                         SDNode opnode,
   1163                         bit CommutableRR, bit ConvertibleToThreeAddress> {
   1164   let Defs = [EFLAGS] in {
   1165     let isCommutable = CommutableRR,
   1166         isConvertibleToThreeAddress = ConvertibleToThreeAddress in {
   1167       def NAME#8rr  : BinOpRR_F<BaseOpc, mnemonic, Xi8 , opnode>;
   1168       def NAME#16rr : BinOpRR_F<BaseOpc, mnemonic, Xi16, opnode>;
   1169       def NAME#32rr : BinOpRR_F<BaseOpc, mnemonic, Xi32, opnode>;
   1170       def NAME#64rr : BinOpRR_F<BaseOpc, mnemonic, Xi64, opnode>;
   1171     } // isCommutable
   1172 
   1173     def NAME#8rr_REV  : BinOpRR_F_Rev<BaseOpc2, mnemonic, Xi8>;
   1174     def NAME#16rr_REV : BinOpRR_F_Rev<BaseOpc2, mnemonic, Xi16>;
   1175     def NAME#32rr_REV : BinOpRR_F_Rev<BaseOpc2, mnemonic, Xi32>;
   1176     def NAME#64rr_REV : BinOpRR_F_Rev<BaseOpc2, mnemonic, Xi64>;
   1177 
   1178     def NAME#8rm   : BinOpRM_F<BaseOpc2, mnemonic, Xi8 , opnode>;
   1179     def NAME#16rm  : BinOpRM_F<BaseOpc2, mnemonic, Xi16, opnode>;
   1180     def NAME#32rm  : BinOpRM_F<BaseOpc2, mnemonic, Xi32, opnode>;
   1181     def NAME#64rm  : BinOpRM_F<BaseOpc2, mnemonic, Xi64, opnode>;
   1182 
   1183     let isConvertibleToThreeAddress = ConvertibleToThreeAddress in {
   1184       // NOTE: These are order specific, we want the ri8 forms to be listed
   1185       // first so that they are slightly preferred to the ri forms.
   1186       def NAME#16ri8 : BinOpRI8_F<0x82, mnemonic, Xi16, opnode, RegMRM>;
   1187       def NAME#32ri8 : BinOpRI8_F<0x82, mnemonic, Xi32, opnode, RegMRM>;
   1188       def NAME#64ri8 : BinOpRI8_F<0x82, mnemonic, Xi64, opnode, RegMRM>;
   1189 
   1190       def NAME#8ri   : BinOpRI_F<0x80, mnemonic, Xi8 , opnode, RegMRM>;
   1191       def NAME#16ri  : BinOpRI_F<0x80, mnemonic, Xi16, opnode, RegMRM>;
   1192       def NAME#32ri  : BinOpRI_F<0x80, mnemonic, Xi32, opnode, RegMRM>;
   1193       def NAME#64ri32: BinOpRI_F<0x80, mnemonic, Xi64, opnode, RegMRM>;
   1194     }
   1195 
   1196     def NAME#8mr    : BinOpMR_F<BaseOpc, mnemonic, Xi8 , opnode>;
   1197     def NAME#16mr   : BinOpMR_F<BaseOpc, mnemonic, Xi16, opnode>;
   1198     def NAME#32mr   : BinOpMR_F<BaseOpc, mnemonic, Xi32, opnode>;
   1199     def NAME#64mr   : BinOpMR_F<BaseOpc, mnemonic, Xi64, opnode>;
   1200 
   1201     // NOTE: These are order specific, we want the mi8 forms to be listed
   1202     // first so that they are slightly preferred to the mi forms.
   1203     def NAME#16mi8  : BinOpMI8_F<mnemonic, Xi16, opnode, MemMRM>;
   1204     def NAME#32mi8  : BinOpMI8_F<mnemonic, Xi32, opnode, MemMRM>;
   1205     def NAME#64mi8  : BinOpMI8_F<mnemonic, Xi64, opnode, MemMRM>;
   1206 
   1207     def NAME#8mi    : BinOpMI_F<mnemonic, Xi8 , opnode, MemMRM>;
   1208     def NAME#16mi   : BinOpMI_F<mnemonic, Xi16, opnode, MemMRM>;
   1209     def NAME#32mi   : BinOpMI_F<mnemonic, Xi32, opnode, MemMRM>;
   1210     def NAME#64mi32 : BinOpMI_F<mnemonic, Xi64, opnode, MemMRM>;
   1211   } // Defs = [EFLAGS]
   1212 
   1213   def NAME#8i8   : BinOpAI<BaseOpc4, mnemonic, Xi8 , AL,
   1214                            "{$src, %al|al, $src}">;
   1215   def NAME#16i16 : BinOpAI<BaseOpc4, mnemonic, Xi16, AX,
   1216                            "{$src, %ax|ax, $src}">;
   1217   def NAME#32i32 : BinOpAI<BaseOpc4, mnemonic, Xi32, EAX,
   1218                            "{$src, %eax|eax, $src}">;
   1219   def NAME#64i32 : BinOpAI<BaseOpc4, mnemonic, Xi64, RAX,
   1220                            "{$src, %rax|rax, $src}">;
   1221 }
   1222 
   1223 
   1224 defm AND : ArithBinOp_RF<0x20, 0x22, 0x24, "and", MRM4r, MRM4m,
   1225                          X86and_flag, and, 1, 0>;
   1226 defm OR  : ArithBinOp_RF<0x08, 0x0A, 0x0C, "or", MRM1r, MRM1m,
   1227                          X86or_flag, or, 1, 0>;
   1228 defm XOR : ArithBinOp_RF<0x30, 0x32, 0x34, "xor", MRM6r, MRM6m,
   1229                          X86xor_flag, xor, 1, 0>;
   1230 defm ADD : ArithBinOp_RF<0x00, 0x02, 0x04, "add", MRM0r, MRM0m,
   1231                          X86add_flag, add, 1, 1>;
   1232 let isCompare = 1 in {
   1233 defm SUB : ArithBinOp_RF<0x28, 0x2A, 0x2C, "sub", MRM5r, MRM5m,
   1234                          X86sub_flag, sub, 0, 0>;
   1235 }
   1236 
   1237 // Arithmetic.
   1238 defm ADC : ArithBinOp_RFF<0x10, 0x12, 0x14, "adc", MRM2r, MRM2m, X86adc_flag,
   1239                           1, 0>;
   1240 defm SBB : ArithBinOp_RFF<0x18, 0x1A, 0x1C, "sbb", MRM3r, MRM3m, X86sbb_flag,
   1241                           0, 0>;
   1242 
   1243 let isCompare = 1 in {
   1244 defm CMP : ArithBinOp_F<0x38, 0x3A, 0x3C, "cmp", MRM7r, MRM7m, X86cmp, 0, 0>;
   1245 }
   1246 
   1247 
   1248 //===----------------------------------------------------------------------===//
   1249 // Semantically, test instructions are similar like AND, except they don't
   1250 // generate a result.  From an encoding perspective, they are very different:
   1251 // they don't have all the usual imm8 and REV forms, and are encoded into a
   1252 // different space.
   1253 def X86testpat : PatFrag<(ops node:$lhs, node:$rhs),
   1254                          (X86cmp (and_su node:$lhs, node:$rhs), 0)>;
   1255 
   1256 let isCompare = 1 in {
   1257   let Defs = [EFLAGS] in {
   1258     let isCommutable = 1 in {
   1259       def TEST8rr  : BinOpRR_F<0x84, "test", Xi8 , X86testpat, MRMSrcReg>;
   1260       def TEST16rr : BinOpRR_F<0x84, "test", Xi16, X86testpat, MRMSrcReg>;
   1261       def TEST32rr : BinOpRR_F<0x84, "test", Xi32, X86testpat, MRMSrcReg>;
   1262       def TEST64rr : BinOpRR_F<0x84, "test", Xi64, X86testpat, MRMSrcReg>;
   1263     } // isCommutable
   1264 
   1265     def TEST8rm    : BinOpRM_F<0x84, "test", Xi8 , X86testpat>;
   1266     def TEST16rm   : BinOpRM_F<0x84, "test", Xi16, X86testpat>;
   1267     def TEST32rm   : BinOpRM_F<0x84, "test", Xi32, X86testpat>;
   1268     def TEST64rm   : BinOpRM_F<0x84, "test", Xi64, X86testpat>;
   1269 
   1270     def TEST8ri    : BinOpRI_F<0xF6, "test", Xi8 , X86testpat, MRM0r>;
   1271     def TEST16ri   : BinOpRI_F<0xF6, "test", Xi16, X86testpat, MRM0r>;
   1272     def TEST32ri   : BinOpRI_F<0xF6, "test", Xi32, X86testpat, MRM0r>;
   1273     def TEST64ri32 : BinOpRI_F<0xF6, "test", Xi64, X86testpat, MRM0r>;
   1274 
   1275     def TEST8mi    : BinOpMI_F<"test", Xi8 , X86testpat, MRM0m, 0xF6>;
   1276     def TEST16mi   : BinOpMI_F<"test", Xi16, X86testpat, MRM0m, 0xF6>;
   1277     def TEST32mi   : BinOpMI_F<"test", Xi32, X86testpat, MRM0m, 0xF6>;
   1278     def TEST64mi32 : BinOpMI_F<"test", Xi64, X86testpat, MRM0m, 0xF6>;
   1279 
   1280     // When testing the result of EXTRACT_SUBREG sub_8bit_hi, make sure the
   1281     // register class is constrained to GR8_NOREX. This pseudo is explicitly
   1282     // marked side-effect free, since it doesn't have an isel pattern like
   1283     // other test instructions. 
   1284     let isPseudo = 1, hasSideEffects = 0 in
   1285     def TEST8ri_NOREX : I<0, Pseudo, (outs), (ins GR8_NOREX:$src, i8imm:$mask),
   1286                           "", [], IIC_BIN_NONMEM>, Sched<[WriteALU]>;
   1287   } // Defs = [EFLAGS]
   1288 
   1289   def TEST8i8    : BinOpAI<0xA8, "test", Xi8 , AL,
   1290                            "{$src, %al|al, $src}">;
   1291   def TEST16i16  : BinOpAI<0xA8, "test", Xi16, AX,
   1292                            "{$src, %ax|ax, $src}">;
   1293   def TEST32i32  : BinOpAI<0xA8, "test", Xi32, EAX,
   1294                            "{$src, %eax|eax, $src}">;
   1295   def TEST64i32  : BinOpAI<0xA8, "test", Xi64, RAX,
   1296                            "{$src, %rax|rax, $src}">;
   1297 } // isCompare
   1298 
   1299 //===----------------------------------------------------------------------===//
   1300 // ANDN Instruction
   1301 //
   1302 multiclass bmi_andn<string mnemonic, RegisterClass RC, X86MemOperand x86memop,
   1303                     PatFrag ld_frag> {
   1304   def rr : I<0xF2, MRMSrcReg, (outs RC:$dst), (ins RC:$src1, RC:$src2),
   1305             !strconcat(mnemonic, "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
   1306             [(set RC:$dst, EFLAGS, (X86and_flag (not RC:$src1), RC:$src2))],
   1307             IIC_BIN_NONMEM>, Sched<[WriteALU]>;
   1308   def rm : I<0xF2, MRMSrcMem, (outs RC:$dst), (ins RC:$src1, x86memop:$src2),
   1309             !strconcat(mnemonic, "\t{$src2, $src1, $dst|$dst, $src1, $src2}"),
   1310             [(set RC:$dst, EFLAGS,
   1311              (X86and_flag (not RC:$src1), (ld_frag addr:$src2)))], IIC_BIN_MEM>,
   1312            Sched<[WriteALULd, ReadAfterLd]>;
   1313 }
   1314 
   1315 let Predicates = [HasBMI], Defs = [EFLAGS] in {
   1316   defm ANDN32 : bmi_andn<"andn{l}", GR32, i32mem, loadi32>, T8PS, VEX_4V;
   1317   defm ANDN64 : bmi_andn<"andn{q}", GR64, i64mem, loadi64>, T8PS, VEX_4V, VEX_W;
   1318 }
   1319 
   1320 let Predicates = [HasBMI] in {
   1321   def : Pat<(and (not GR32:$src1), GR32:$src2),
   1322             (ANDN32rr GR32:$src1, GR32:$src2)>;
   1323   def : Pat<(and (not GR64:$src1), GR64:$src2),
   1324             (ANDN64rr GR64:$src1, GR64:$src2)>;
   1325   def : Pat<(and (not GR32:$src1), (loadi32 addr:$src2)),
   1326             (ANDN32rm GR32:$src1, addr:$src2)>;
   1327   def : Pat<(and (not GR64:$src1), (loadi64 addr:$src2)),
   1328             (ANDN64rm GR64:$src1, addr:$src2)>;
   1329 }
   1330 
   1331 //===----------------------------------------------------------------------===//
   1332 // MULX Instruction
   1333 //
   1334 multiclass bmi_mulx<string mnemonic, RegisterClass RC, X86MemOperand x86memop> {
   1335 let neverHasSideEffects = 1 in {
   1336   let isCommutable = 1 in
   1337   def rr : I<0xF6, MRMSrcReg, (outs RC:$dst1, RC:$dst2), (ins RC:$src),
   1338              !strconcat(mnemonic, "\t{$src, $dst2, $dst1|$dst1, $dst2, $src}"),
   1339              [], IIC_MUL8>, T8XD, VEX_4V, Sched<[WriteIMul, WriteIMulH]>;
   1340 
   1341   let mayLoad = 1 in
   1342   def rm : I<0xF6, MRMSrcMem, (outs RC:$dst1, RC:$dst2), (ins x86memop:$src),
   1343              !strconcat(mnemonic, "\t{$src, $dst2, $dst1|$dst1, $dst2, $src}"),
   1344              [], IIC_MUL8>, T8XD, VEX_4V, Sched<[WriteIMulLd, WriteIMulH]>;
   1345 }
   1346 }
   1347 
   1348 let Predicates = [HasBMI2] in {
   1349   let Uses = [EDX] in
   1350     defm MULX32 : bmi_mulx<"mulx{l}", GR32, i32mem>;
   1351   let Uses = [RDX] in
   1352     defm MULX64 : bmi_mulx<"mulx{q}", GR64, i64mem>, VEX_W;
   1353 }
   1354 
   1355 //===----------------------------------------------------------------------===//
   1356 // ADCX Instruction
   1357 //
   1358 let hasSideEffects = 0, Predicates = [HasADX], Defs = [EFLAGS] in {
   1359   let SchedRW = [WriteALU] in {
   1360   def ADCX32rr : I<0xF6, MRMSrcReg, (outs GR32:$dst), (ins GR32:$src),
   1361              "adcx{l}\t{$src, $dst|$dst, $src}",
   1362              [], IIC_BIN_NONMEM>, T8PD;
   1363 
   1364   def ADCX64rr : RI<0xF6, MRMSrcReg, (outs GR64:$dst), (ins GR64:$src),
   1365              "adcx{q}\t{$src, $dst|$dst, $src}",
   1366              [], IIC_BIN_NONMEM>, T8PD, Requires<[In64BitMode]>;
   1367   } // SchedRW
   1368 
   1369   let mayLoad = 1, SchedRW = [WriteALULd] in {
   1370   def ADCX32rm : I<0xF6, MRMSrcMem, (outs GR32:$dst), (ins i32mem:$src),
   1371              "adcx{l}\t{$src, $dst|$dst, $src}",
   1372              [], IIC_BIN_MEM>, T8PD;
   1373 
   1374   def ADCX64rm : RI<0xF6, MRMSrcMem, (outs GR64:$dst), (ins i64mem:$src),
   1375              "adcx{q}\t{$src, $dst|$dst, $src}",
   1376              [], IIC_BIN_MEM>, T8PD, Requires<[In64BitMode]>;
   1377   }
   1378 }
   1379 
   1380 //===----------------------------------------------------------------------===//
   1381 // ADOX Instruction
   1382 //
   1383 let hasSideEffects = 0, Predicates = [HasADX], Defs = [EFLAGS] in {
   1384   let SchedRW = [WriteALU] in {
   1385   def ADOX32rr : I<0xF6, MRMSrcReg, (outs GR32:$dst), (ins GR32:$src),
   1386              "adox{l}\t{$src, $dst|$dst, $src}",
   1387              [], IIC_BIN_NONMEM>, T8XS;
   1388 
   1389   def ADOX64rr : RI<0xF6, MRMSrcReg, (outs GR64:$dst), (ins GR64:$src),
   1390              "adox{q}\t{$src, $dst|$dst, $src}",
   1391              [], IIC_BIN_NONMEM>, T8XS, Requires<[In64BitMode]>;
   1392   } // SchedRW
   1393 
   1394   let mayLoad = 1, SchedRW = [WriteALULd] in {
   1395   def ADOX32rm : I<0xF6, MRMSrcMem, (outs GR32:$dst), (ins i32mem:$src),
   1396              "adox{l}\t{$src, $dst|$dst, $src}",
   1397              [], IIC_BIN_MEM>, T8XS;
   1398 
   1399   def ADOX64rm : RI<0xF6, MRMSrcMem, (outs GR64:$dst), (ins i64mem:$src),
   1400              "adox{q}\t{$src, $dst|$dst, $src}",
   1401              [], IIC_BIN_MEM>, T8XS, Requires<[In64BitMode]>;
   1402   }
   1403 }
   1404