Home | History | Annotate | Download | only in Mips
      1 //===- MipsInstrInfo.td - Target Description for Mips Target -*- 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 contains the Mips implementation of the TargetInstrInfo class.
     11 //
     12 //===----------------------------------------------------------------------===//
     13 
     14 //===----------------------------------------------------------------------===//
     15 // Instruction format superclass
     16 //===----------------------------------------------------------------------===//
     17 
     18 include "MipsInstrFormats.td"
     19 
     20 //===----------------------------------------------------------------------===//
     21 // Mips profiles and nodes
     22 //===----------------------------------------------------------------------===//
     23 
     24 def SDT_MipsRet          : SDTypeProfile<0, 1, [SDTCisInt<0>]>;
     25 def SDT_MipsJmpLink      : SDTypeProfile<0, 1, [SDTCisVT<0, iPTR>]>;
     26 def SDT_MipsCMov         : SDTypeProfile<1, 4, [SDTCisSameAs<0, 1>,
     27                                                 SDTCisSameAs<1, 2>,
     28                                                 SDTCisSameAs<3, 4>,
     29                                                 SDTCisInt<4>]>;
     30 def SDT_MipsCallSeqStart : SDCallSeqStart<[SDTCisVT<0, i32>]>;
     31 def SDT_MipsCallSeqEnd   : SDCallSeqEnd<[SDTCisVT<0, i32>, SDTCisVT<1, i32>]>;
     32 def SDT_MipsMAddMSub     : SDTypeProfile<0, 4,
     33                                          [SDTCisVT<0, i32>, SDTCisSameAs<0, 1>,
     34                                           SDTCisSameAs<1, 2>,
     35                                           SDTCisSameAs<2, 3>]>;
     36 def SDT_MipsDivRem       : SDTypeProfile<0, 2,
     37                                          [SDTCisInt<0>,
     38                                           SDTCisSameAs<0, 1>]>;
     39 
     40 def SDT_MipsThreadPointer : SDTypeProfile<1, 0, [SDTCisPtrTy<0>]>;
     41 
     42 def SDT_MipsDynAlloc    : SDTypeProfile<1, 1, [SDTCisVT<0, i32>,
     43                                                SDTCisVT<1, iPTR>]>;
     44 def SDT_Sync             : SDTypeProfile<0, 1, [SDTCisVT<0, i32>]>;
     45 
     46 def SDT_Ext : SDTypeProfile<1, 3, [SDTCisInt<0>, SDTCisSameAs<0, 1>,
     47                                    SDTCisVT<2, i32>, SDTCisSameAs<2, 3>]>;
     48 def SDT_Ins : SDTypeProfile<1, 4, [SDTCisInt<0>, SDTCisSameAs<0, 1>,
     49                                    SDTCisVT<2, i32>, SDTCisSameAs<2, 3>,
     50                                    SDTCisSameAs<0, 4>]>;
     51 
     52 // Call
     53 def MipsJmpLink : SDNode<"MipsISD::JmpLink",SDT_MipsJmpLink,
     54                          [SDNPHasChain, SDNPOutGlue, SDNPOptInGlue,
     55                           SDNPVariadic]>;
     56 
     57 // Hi and Lo nodes are used to handle global addresses. Used on
     58 // MipsISelLowering to lower stuff like GlobalAddress, ExternalSymbol
     59 // static model. (nothing to do with Mips Registers Hi and Lo)
     60 def MipsHi    : SDNode<"MipsISD::Hi", SDTIntUnaryOp>;
     61 def MipsLo    : SDNode<"MipsISD::Lo", SDTIntUnaryOp>;
     62 def MipsGPRel : SDNode<"MipsISD::GPRel", SDTIntUnaryOp>;
     63 
     64 // TlsGd node is used to handle General Dynamic TLS
     65 def MipsTlsGd : SDNode<"MipsISD::TlsGd", SDTIntUnaryOp>;
     66 
     67 // TprelHi and TprelLo nodes are used to handle Local Exec TLS
     68 def MipsTprelHi    : SDNode<"MipsISD::TprelHi", SDTIntUnaryOp>;
     69 def MipsTprelLo    : SDNode<"MipsISD::TprelLo", SDTIntUnaryOp>;
     70 
     71 // Thread pointer
     72 def MipsThreadPointer: SDNode<"MipsISD::ThreadPointer", SDT_MipsThreadPointer>;
     73 
     74 // Return
     75 def MipsRet : SDNode<"MipsISD::Ret", SDT_MipsRet, [SDNPHasChain,
     76                      SDNPOptInGlue]>;
     77 
     78 // These are target-independent nodes, but have target-specific formats.
     79 def callseq_start : SDNode<"ISD::CALLSEQ_START", SDT_MipsCallSeqStart,
     80                            [SDNPHasChain, SDNPOutGlue]>;
     81 def callseq_end   : SDNode<"ISD::CALLSEQ_END", SDT_MipsCallSeqEnd,
     82                            [SDNPHasChain, SDNPOptInGlue, SDNPOutGlue]>;
     83 
     84 // MAdd*/MSub* nodes
     85 def MipsMAdd      : SDNode<"MipsISD::MAdd", SDT_MipsMAddMSub,
     86                            [SDNPOptInGlue, SDNPOutGlue]>;
     87 def MipsMAddu     : SDNode<"MipsISD::MAddu", SDT_MipsMAddMSub,
     88                            [SDNPOptInGlue, SDNPOutGlue]>;
     89 def MipsMSub      : SDNode<"MipsISD::MSub", SDT_MipsMAddMSub,
     90                            [SDNPOptInGlue, SDNPOutGlue]>;
     91 def MipsMSubu     : SDNode<"MipsISD::MSubu", SDT_MipsMAddMSub,
     92                            [SDNPOptInGlue, SDNPOutGlue]>;
     93 
     94 // DivRem(u) nodes
     95 def MipsDivRem    : SDNode<"MipsISD::DivRem", SDT_MipsDivRem,
     96                            [SDNPOutGlue]>;
     97 def MipsDivRemU   : SDNode<"MipsISD::DivRemU", SDT_MipsDivRem,
     98                            [SDNPOutGlue]>;
     99 
    100 // Target constant nodes that are not part of any isel patterns and remain
    101 // unchanged can cause instructions with illegal operands to be emitted.
    102 // Wrapper node patterns give the instruction selector a chance to replace
    103 // target constant nodes that would otherwise remain unchanged with ADDiu
    104 // nodes. Without these wrapper node patterns, the following conditional move
    105 // instrucion is emitted when function cmov2 in test/CodeGen/Mips/cmov.ll is
    106 // compiled: 
    107 //  movn  %got(d)($gp), %got(c)($gp), $4
    108 // This instruction is illegal since movn can take only register operands.
    109 
    110 def MipsWrapperPIC    : SDNode<"MipsISD::WrapperPIC",  SDTIntUnaryOp>;
    111 
    112 // Pointer to dynamically allocated stack area.
    113 def MipsDynAlloc  : SDNode<"MipsISD::DynAlloc", SDT_MipsDynAlloc,
    114                            [SDNPHasChain, SDNPInGlue]>;
    115 
    116 def MipsSync : SDNode<"MipsISD::Sync", SDT_Sync, [SDNPHasChain]>;
    117 
    118 def MipsExt :  SDNode<"MipsISD::Ext", SDT_Ext>;
    119 def MipsIns :  SDNode<"MipsISD::Ins", SDT_Ins>;
    120 
    121 //===----------------------------------------------------------------------===//
    122 // Mips Instruction Predicate Definitions.
    123 //===----------------------------------------------------------------------===//
    124 def HasSEInReg  : Predicate<"Subtarget.hasSEInReg()">;
    125 def HasBitCount : Predicate<"Subtarget.hasBitCount()">;
    126 def HasSwap     : Predicate<"Subtarget.hasSwap()">;
    127 def HasCondMov  : Predicate<"Subtarget.hasCondMov()">;
    128 def HasMips32    : Predicate<"Subtarget.hasMips32()">;
    129 def HasMips32r2  : Predicate<"Subtarget.hasMips32r2()">;
    130 def HasMips64    : Predicate<"Subtarget.hasMips64()">;
    131 def NotMips64    : Predicate<"!Subtarget.hasMips64()">;
    132 def HasMips64r2  : Predicate<"Subtarget.hasMips64r2()">;
    133 def IsN64       : Predicate<"Subtarget.isABI_N64()">;
    134 def NotN64      : Predicate<"!Subtarget.isABI_N64()">;
    135 
    136 //===----------------------------------------------------------------------===//
    137 // Mips Operand, Complex Patterns and Transformations Definitions.
    138 //===----------------------------------------------------------------------===//
    139 
    140 // Instruction operand types
    141 def brtarget    : Operand<OtherVT>;
    142 def calltarget  : Operand<i32>;
    143 def simm16      : Operand<i32>;
    144 def simm16_64   : Operand<i64>;
    145 def shamt       : Operand<i32>;
    146 
    147 // Unsigned Operand
    148 def uimm16      : Operand<i32> {
    149   let PrintMethod = "printUnsignedImm";
    150 }
    151 
    152 // Address operand
    153 def mem : Operand<i32> {
    154   let PrintMethod = "printMemOperand";
    155   let MIOperandInfo = (ops CPURegs, simm16);
    156   let EncoderMethod = "getMemEncoding";
    157 }
    158 
    159 def mem64 : Operand<i64> {
    160   let PrintMethod = "printMemOperand";
    161   let MIOperandInfo = (ops CPU64Regs, simm16_64);
    162 }
    163 
    164 def mem_ea : Operand<i32> {
    165   let PrintMethod = "printMemOperandEA";
    166   let MIOperandInfo = (ops CPURegs, simm16);
    167   let EncoderMethod = "getMemEncoding";
    168 }
    169 
    170 // size operand of ext instruction
    171 def size_ext : Operand<i32> {
    172   let EncoderMethod = "getSizeExtEncoding";
    173 }
    174 
    175 // size operand of ins instruction
    176 def size_ins : Operand<i32> {
    177   let EncoderMethod = "getSizeInsEncoding";
    178 }
    179 
    180 // Transformation Function - get the lower 16 bits.
    181 def LO16 : SDNodeXForm<imm, [{
    182   return getI32Imm((unsigned)N->getZExtValue() & 0xFFFF);
    183 }]>;
    184 
    185 // Transformation Function - get the higher 16 bits.
    186 def HI16 : SDNodeXForm<imm, [{
    187   return getI32Imm((unsigned)N->getZExtValue() >> 16);
    188 }]>;
    189 
    190 // Node immediate fits as 16-bit sign extended on target immediate.
    191 // e.g. addi, andi
    192 def immSExt16  : PatLeaf<(imm), [{ return isInt<16>(N->getSExtValue()); }]>;
    193 
    194 // Node immediate fits as 16-bit zero extended on target immediate.
    195 // The LO16 param means that only the lower 16 bits of the node
    196 // immediate are caught.
    197 // e.g. addiu, sltiu
    198 def immZExt16  : PatLeaf<(imm), [{
    199   if (N->getValueType(0) == MVT::i32)
    200     return (uint32_t)N->getZExtValue() == (unsigned short)N->getZExtValue();
    201   else
    202     return (uint64_t)N->getZExtValue() == (unsigned short)N->getZExtValue();
    203 }], LO16>;
    204 
    205 // shamt field must fit in 5 bits.
    206 def immZExt5 : PatLeaf<(imm), [{
    207   return N->getZExtValue() == ((N->getZExtValue()) & 0x1f) ;
    208 }]>;
    209 
    210 // Mips Address Mode! SDNode frameindex could possibily be a match
    211 // since load and store instructions from stack used it.
    212 def addr : ComplexPattern<iPTR, 2, "SelectAddr", [frameindex], []>;
    213 
    214 //===----------------------------------------------------------------------===//
    215 // Pattern fragment for load/store
    216 //===----------------------------------------------------------------------===//
    217 class UnalignedLoad<PatFrag Node> : PatFrag<(ops node:$ptr), (Node node:$ptr), [{
    218   LoadSDNode *LD = cast<LoadSDNode>(N);
    219   return LD->getMemoryVT().getSizeInBits()/8 > LD->getAlignment();
    220 }]>;
    221 
    222 class AlignedLoad<PatFrag Node> : PatFrag<(ops node:$ptr), (Node node:$ptr), [{
    223   LoadSDNode *LD = cast<LoadSDNode>(N);
    224   return LD->getMemoryVT().getSizeInBits()/8 <= LD->getAlignment();
    225 }]>;
    226 
    227 class UnalignedStore<PatFrag Node> : PatFrag<(ops node:$val, node:$ptr),
    228                                              (Node node:$val, node:$ptr), [{
    229   StoreSDNode *SD = cast<StoreSDNode>(N);
    230   return SD->getMemoryVT().getSizeInBits()/8 > SD->getAlignment();
    231 }]>;
    232 
    233 class AlignedStore<PatFrag Node> : PatFrag<(ops node:$val, node:$ptr),
    234                                            (Node node:$val, node:$ptr), [{
    235   StoreSDNode *SD = cast<StoreSDNode>(N);
    236   return SD->getMemoryVT().getSizeInBits()/8 <= SD->getAlignment();
    237 }]>;
    238 
    239 // Load/Store PatFrags.
    240 def sextloadi16_a   : AlignedLoad<sextloadi16>;
    241 def zextloadi16_a   : AlignedLoad<zextloadi16>;
    242 def extloadi16_a    : AlignedLoad<extloadi16>;
    243 def load_a          : AlignedLoad<load>;
    244 def sextloadi32_a   : AlignedLoad<sextloadi32>;
    245 def zextloadi32_a   : AlignedLoad<zextloadi32>;
    246 def extloadi32_a    : AlignedLoad<extloadi32>;
    247 def truncstorei16_a : AlignedStore<truncstorei16>;
    248 def store_a         : AlignedStore<store>;
    249 def truncstorei32_a : AlignedStore<truncstorei32>;
    250 def sextloadi16_u   : UnalignedLoad<sextloadi16>;
    251 def zextloadi16_u   : UnalignedLoad<zextloadi16>;
    252 def extloadi16_u    : UnalignedLoad<extloadi16>;
    253 def load_u          : UnalignedLoad<load>;
    254 def sextloadi32_u   : UnalignedLoad<sextloadi32>;
    255 def zextloadi32_u   : UnalignedLoad<zextloadi32>;
    256 def extloadi32_u    : UnalignedLoad<extloadi32>;
    257 def truncstorei16_u : UnalignedStore<truncstorei16>;
    258 def store_u         : UnalignedStore<store>;
    259 def truncstorei32_u : UnalignedStore<truncstorei32>;
    260 
    261 //===----------------------------------------------------------------------===//
    262 // Instructions specific format
    263 //===----------------------------------------------------------------------===//
    264 
    265 // Arithmetic and logical instructions with 3 register operands.
    266 class ArithLogicR<bits<6> op, bits<6> func, string instr_asm, SDNode OpNode,
    267                   InstrItinClass itin, RegisterClass RC, bit isComm = 0>:
    268   FR<op, func, (outs RC:$rd), (ins RC:$rs, RC:$rt),
    269      !strconcat(instr_asm, "\t$rd, $rs, $rt"),
    270      [(set RC:$rd, (OpNode RC:$rs, RC:$rt))], itin> {
    271   let shamt = 0;
    272   let isCommutable = isComm;
    273 }
    274 
    275 class ArithOverflowR<bits<6> op, bits<6> func, string instr_asm,
    276                     InstrItinClass itin, RegisterClass RC, bit isComm = 0>:
    277   FR<op, func, (outs RC:$rd), (ins RC:$rs, RC:$rt),
    278      !strconcat(instr_asm, "\t$rd, $rs, $rt"), [], itin> {
    279   let shamt = 0;
    280   let isCommutable = isComm;
    281 }
    282 
    283 // Arithmetic and logical instructions with 2 register operands.
    284 class ArithLogicI<bits<6> op, string instr_asm, SDNode OpNode,
    285                   Operand Od, PatLeaf imm_type, RegisterClass RC> :
    286   FI<op, (outs RC:$rt), (ins RC:$rs, Od:$imm16),
    287      !strconcat(instr_asm, "\t$rt, $rs, $imm16"),
    288      [(set RC:$rt, (OpNode RC:$rs, imm_type:$imm16))], IIAlu>;
    289 
    290 class ArithOverflowI<bits<6> op, string instr_asm, SDNode OpNode,
    291                      Operand Od, PatLeaf imm_type, RegisterClass RC> :
    292   FI<op, (outs RC:$rt), (ins RC:$rs, Od:$imm16),
    293      !strconcat(instr_asm, "\t$rt, $rs, $imm16"), [], IIAlu>;
    294 
    295 // Arithmetic Multiply ADD/SUB
    296 let rd = 0, shamt = 0, Defs = [HI, LO], Uses = [HI, LO] in
    297 class MArithR<bits<6> func, string instr_asm, SDNode op, bit isComm = 0> :
    298   FR<0x1c, func, (outs), (ins CPURegs:$rs, CPURegs:$rt),
    299      !strconcat(instr_asm, "\t$rs, $rt"),
    300      [(op CPURegs:$rs, CPURegs:$rt, LO, HI)], IIImul> {
    301   let rd = 0;
    302   let shamt = 0;
    303   let isCommutable = isComm;
    304 }
    305 
    306 //  Logical
    307 class LogicNOR<bits<6> op, bits<6> func, string instr_asm, RegisterClass RC>:
    308   FR<op, func, (outs RC:$rd), (ins RC:$rs, RC:$rt),
    309      !strconcat(instr_asm, "\t$rd, $rs, $rt"),
    310      [(set RC:$rd, (not (or RC:$rs, RC:$rt)))], IIAlu> {
    311   let shamt = 0;
    312   let isCommutable = 1;
    313 }
    314 
    315 // Shifts
    316 class LogicR_shift_rotate_imm<bits<6> func, bits<5> _rs, string instr_asm,
    317                               SDNode OpNode>:
    318   FR<0x00, func, (outs CPURegs:$rd), (ins CPURegs:$rt, shamt:$shamt),
    319      !strconcat(instr_asm, "\t$rd, $rt, $shamt"),
    320      [(set CPURegs:$rd, (OpNode CPURegs:$rt, (i32 immZExt5:$shamt)))], IIAlu> {
    321   let rs = _rs;
    322 }
    323 
    324 class LogicR_shift_rotate_reg<bits<6> func, bits<5> isRotate, string instr_asm,
    325                               SDNode OpNode>:
    326   FR<0x00, func, (outs CPURegs:$rd), (ins CPURegs:$rs, CPURegs:$rt),
    327      !strconcat(instr_asm, "\t$rd, $rt, $rs"),
    328      [(set CPURegs:$rd, (OpNode CPURegs:$rt, CPURegs:$rs))], IIAlu> {
    329   let shamt = isRotate;
    330 }
    331 
    332 // Load Upper Imediate
    333 class LoadUpper<bits<6> op, string instr_asm>:
    334   FI<op, (outs CPURegs:$rt), (ins uimm16:$imm16),
    335      !strconcat(instr_asm, "\t$rt, $imm16"), [], IIAlu> {
    336   let rs = 0;
    337 }
    338 
    339 class FMem<bits<6> op, dag outs, dag ins, string asmstr, list<dag> pattern,
    340           InstrItinClass itin>: FFI<op, outs, ins, asmstr, pattern> {
    341   bits<21> addr;
    342   let Inst{25-21} = addr{20-16};
    343   let Inst{15-0}  = addr{15-0};
    344 }
    345 
    346 // Memory Load/Store
    347 let canFoldAsLoad = 1 in
    348 class LoadM<bits<6> op, string instr_asm, PatFrag OpNode, RegisterClass RC,
    349             Operand MemOpnd, bit Pseudo>:
    350   FMem<op, (outs RC:$rt), (ins MemOpnd:$addr),
    351      !strconcat(instr_asm, "\t$rt, $addr"),
    352      [(set RC:$rt, (OpNode addr:$addr))], IILoad> {
    353   let isPseudo = Pseudo;
    354 }
    355 
    356 class StoreM<bits<6> op, string instr_asm, PatFrag OpNode, RegisterClass RC,
    357              Operand MemOpnd, bit Pseudo>:
    358   FMem<op, (outs), (ins RC:$rt, MemOpnd:$addr),
    359      !strconcat(instr_asm, "\t$rt, $addr"),
    360      [(OpNode RC:$rt, addr:$addr)], IIStore> {
    361   let isPseudo = Pseudo;
    362 }
    363 
    364 // 32-bit load.
    365 multiclass LoadM32<bits<6> op, string instr_asm, PatFrag OpNode,
    366                    bit Pseudo = 0> {
    367   def #NAME# : LoadM<op, instr_asm, OpNode, CPURegs, mem, Pseudo>,
    368                Requires<[NotN64]>;
    369   def _P8    : LoadM<op, instr_asm, OpNode, CPURegs, mem64, Pseudo>,
    370                Requires<[IsN64]>;
    371 } 
    372 
    373 // 64-bit load.
    374 multiclass LoadM64<bits<6> op, string instr_asm, PatFrag OpNode,
    375                    bit Pseudo = 0> {
    376   def #NAME# : LoadM<op, instr_asm, OpNode, CPU64Regs, mem, Pseudo>,
    377                Requires<[NotN64]>;
    378   def _P8    : LoadM<op, instr_asm, OpNode, CPU64Regs, mem64, Pseudo>,
    379                Requires<[IsN64]>;
    380 } 
    381 
    382 // 32-bit store.
    383 multiclass StoreM32<bits<6> op, string instr_asm, PatFrag OpNode,
    384                     bit Pseudo = 0> {
    385   def #NAME# : StoreM<op, instr_asm, OpNode, CPURegs, mem, Pseudo>,
    386                Requires<[NotN64]>;
    387   def _P8    : StoreM<op, instr_asm, OpNode, CPURegs, mem64, Pseudo>,
    388                Requires<[IsN64]>;
    389 }
    390 
    391 // 64-bit store.
    392 multiclass StoreM64<bits<6> op, string instr_asm, PatFrag OpNode,
    393                     bit Pseudo = 0> {
    394   def #NAME# : StoreM<op, instr_asm, OpNode, CPU64Regs, mem, Pseudo>,
    395                Requires<[NotN64]>;
    396   def _P8    : StoreM<op, instr_asm, OpNode, CPU64Regs, mem64, Pseudo>,
    397                Requires<[IsN64]>;
    398 }
    399 
    400 // Conditional Branch
    401 class CBranch<bits<6> op, string instr_asm, PatFrag cond_op, RegisterClass RC>:
    402   CBranchBase<op, (outs), (ins RC:$rs, RC:$rt, brtarget:$imm16),
    403               !strconcat(instr_asm, "\t$rs, $rt, $imm16"),
    404               [(brcond (i32 (cond_op RC:$rs, RC:$rt)), bb:$imm16)], IIBranch> {
    405   let isBranch = 1;
    406   let isTerminator = 1;
    407   let hasDelaySlot = 1;
    408 }
    409 
    410 class CBranchZero<bits<6> op, bits<5> _rt, string instr_asm, PatFrag cond_op,
    411                   RegisterClass RC>:
    412   CBranchBase<op, (outs), (ins RC:$rs, brtarget:$imm16),
    413               !strconcat(instr_asm, "\t$rs, $imm16"),
    414               [(brcond (i32 (cond_op RC:$rs, 0)), bb:$imm16)], IIBranch> {
    415   let rt = _rt;
    416   let isBranch = 1;
    417   let isTerminator = 1;
    418   let hasDelaySlot = 1;
    419 }
    420 
    421 // SetCC
    422 class SetCC_R<bits<6> op, bits<6> func, string instr_asm, PatFrag cond_op,
    423               RegisterClass RC>:
    424   FR<op, func, (outs CPURegs:$rd), (ins RC:$rs, RC:$rt),
    425      !strconcat(instr_asm, "\t$rd, $rs, $rt"),
    426      [(set CPURegs:$rd, (cond_op RC:$rs, RC:$rt))],
    427      IIAlu> {
    428   let shamt = 0;
    429 }
    430 
    431 class SetCC_I<bits<6> op, string instr_asm, PatFrag cond_op, Operand Od,
    432               PatLeaf imm_type, RegisterClass RC>:
    433   FI<op, (outs CPURegs:$rt), (ins RC:$rs, Od:$imm16),
    434      !strconcat(instr_asm, "\t$rt, $rs, $imm16"),
    435      [(set CPURegs:$rt, (cond_op RC:$rs, imm_type:$imm16))],
    436      IIAlu>;
    437 
    438 // Unconditional branch
    439 let isBranch=1, isTerminator=1, isBarrier=1, hasDelaySlot = 1 in
    440 class JumpFJ<bits<6> op, string instr_asm>:
    441   FJ<op, (outs), (ins brtarget:$target),
    442      !strconcat(instr_asm, "\t$target"), [(br bb:$target)], IIBranch>;
    443 
    444 let isBranch=1, isTerminator=1, isBarrier=1, rd=0, hasDelaySlot = 1 in
    445 class JumpFR<bits<6> op, bits<6> func, string instr_asm>:
    446   FR<op, func, (outs), (ins CPURegs:$rs),
    447      !strconcat(instr_asm, "\t$rs"), [(brind CPURegs:$rs)], IIBranch> {
    448   let rt = 0;
    449   let rd = 0;
    450   let shamt = 0;
    451 }
    452 
    453 // Jump and Link (Call)
    454 let isCall=1, hasDelaySlot=1,
    455   // All calls clobber the non-callee saved registers...
    456   Defs = [AT, V0, V1, A0, A1, A2, A3, T0, T1, T2, T3, T4, T5, T6, T7, T8, T9,
    457           K0, K1, D0, D1, D2, D3, D4, D5, D6, D7, D8, D9], Uses = [GP] in {
    458   class JumpLink<bits<6> op, string instr_asm>:
    459     FJ<op, (outs), (ins calltarget:$target, variable_ops),
    460        !strconcat(instr_asm, "\t$target"), [(MipsJmpLink imm:$target)],
    461        IIBranch>;
    462 
    463   class JumpLinkReg<bits<6> op, bits<6> func, string instr_asm>:
    464     FR<op, func, (outs), (ins CPURegs:$rs, variable_ops),
    465        !strconcat(instr_asm, "\t$rs"), [(MipsJmpLink CPURegs:$rs)], IIBranch> {
    466     let rt = 0;
    467     let rd = 31;
    468     let shamt = 0;
    469   }
    470 
    471   class BranchLink<string instr_asm>:
    472     FI<0x1, (outs), (ins CPURegs:$rs, brtarget:$imm16, variable_ops),
    473        !strconcat(instr_asm, "\t$rs, $imm16"), [], IIBranch>;
    474 }
    475 
    476 // Mul, Div
    477 class Mul<bits<6> func, string instr_asm, InstrItinClass itin>:
    478   FR<0x00, func, (outs), (ins CPURegs:$rs, CPURegs:$rt),
    479      !strconcat(instr_asm, "\t$rs, $rt"), [], itin> {
    480   let rd = 0;
    481   let shamt = 0;
    482   let isCommutable = 1;
    483   let Defs = [HI, LO];
    484 }
    485 
    486 class Div<SDNode op, bits<6> func, string instr_asm, InstrItinClass itin>:
    487           FR<0x00, func, (outs), (ins CPURegs:$rs, CPURegs:$rt),
    488           !strconcat(instr_asm, "\t$$zero, $rs, $rt"),
    489           [(op CPURegs:$rs, CPURegs:$rt)], itin> {
    490   let rd = 0;
    491   let shamt = 0;
    492   let Defs = [HI, LO];
    493 }
    494 
    495 // Move from Hi/Lo
    496 class MoveFromLOHI<bits<6> func, string instr_asm>:
    497   FR<0x00, func, (outs CPURegs:$rd), (ins),
    498      !strconcat(instr_asm, "\t$rd"), [], IIHiLo> {
    499   let rs = 0;
    500   let rt = 0;
    501   let shamt = 0;
    502 }
    503 
    504 class MoveToLOHI<bits<6> func, string instr_asm>:
    505   FR<0x00, func, (outs), (ins CPURegs:$rs),
    506      !strconcat(instr_asm, "\t$rs"), [], IIHiLo> {
    507   let rt = 0;
    508   let rd = 0;
    509   let shamt = 0;
    510 }
    511 
    512 class EffectiveAddress<string instr_asm> :
    513   FMem<0x09, (outs CPURegs:$rt), (ins mem_ea:$addr),
    514      instr_asm, [(set CPURegs:$rt, addr:$addr)], IIAlu>;
    515 
    516 // Count Leading Ones/Zeros in Word
    517 class CountLeading<bits<6> func, string instr_asm, list<dag> pattern>:
    518   FR<0x1c, func, (outs CPURegs:$rd), (ins CPURegs:$rs),
    519      !strconcat(instr_asm, "\t$rd, $rs"), pattern, IIAlu>,
    520      Requires<[HasBitCount]> {
    521   let shamt = 0;
    522   let rt = rd;
    523 }
    524 
    525 // Sign Extend in Register.
    526 class SignExtInReg<bits<5> sa, string instr_asm, ValueType vt>:
    527   FR<0x1f, 0x20, (outs CPURegs:$rd), (ins CPURegs:$rt),
    528      !strconcat(instr_asm, "\t$rd, $rt"),
    529      [(set CPURegs:$rd, (sext_inreg CPURegs:$rt, vt))], NoItinerary> {
    530   let rs = 0;
    531   let shamt = sa;
    532   let Predicates = [HasSEInReg];
    533 }
    534 
    535 // Byte Swap
    536 class ByteSwap<bits<6> func, bits<5> sa, string instr_asm>:
    537   FR<0x1f, func, (outs CPURegs:$rd), (ins CPURegs:$rt),
    538      !strconcat(instr_asm, "\t$rd, $rt"),
    539      [(set CPURegs:$rd, (bswap CPURegs:$rt))], NoItinerary> {
    540   let rs = 0;
    541   let shamt = sa;
    542   let Predicates = [HasSwap];
    543 }
    544 
    545 // Read Hardware
    546 class ReadHardware: FR<0x1f, 0x3b, (outs CPURegs:$rt), (ins HWRegs:$rd),
    547     "rdhwr\t$rt, $rd", [], IIAlu> {
    548   let rs = 0;
    549   let shamt = 0;
    550 }
    551 
    552 // Ext and Ins
    553 class ExtIns<bits<6> _funct, string instr_asm, dag outs, dag ins,
    554              list<dag> pattern, InstrItinClass itin>:
    555   FR<0x1f, _funct, outs, ins, !strconcat(instr_asm, " $rt, $rs, $pos, $sz"),
    556      pattern, itin>, Requires<[HasMips32r2]> {
    557   bits<5> pos;
    558   bits<5> sz;
    559   let rd = sz;
    560   let shamt = pos;
    561 }
    562 
    563 // Atomic instructions with 2 source operands (ATOMIC_SWAP & ATOMIC_LOAD_*).
    564 class Atomic2Ops<PatFrag Op, string Opstr> :
    565   MipsPseudo<(outs CPURegs:$dst), (ins CPURegs:$ptr, CPURegs:$incr),
    566              !strconcat("atomic_", Opstr, "\t$dst, $ptr, $incr"),
    567              [(set CPURegs:$dst,
    568               (Op CPURegs:$ptr, CPURegs:$incr))]>;
    569 
    570 // Atomic Compare & Swap.
    571 class AtomicCmpSwap<PatFrag Op, string Width> :
    572   MipsPseudo<(outs CPURegs:$dst), 
    573              (ins CPURegs:$ptr, CPURegs:$cmp, CPURegs:$swap),
    574              !strconcat("atomic_cmp_swap_", Width, 
    575                         "\t$dst, $ptr, $cmp, $swap"),
    576              [(set CPURegs:$dst,
    577               (Op CPURegs:$ptr, CPURegs:$cmp, CPURegs:$swap))]>;
    578 
    579 //===----------------------------------------------------------------------===//
    580 // Pseudo instructions
    581 //===----------------------------------------------------------------------===//
    582 
    583 // As stack alignment is always done with addiu, we need a 16-bit immediate
    584 let Defs = [SP], Uses = [SP] in {
    585 def ADJCALLSTACKDOWN : MipsPseudo<(outs), (ins uimm16:$amt),
    586                                   "!ADJCALLSTACKDOWN $amt",
    587                                   [(callseq_start timm:$amt)]>;
    588 def ADJCALLSTACKUP   : MipsPseudo<(outs), (ins uimm16:$amt1, uimm16:$amt2),
    589                                   "!ADJCALLSTACKUP $amt1",
    590                                   [(callseq_end timm:$amt1, timm:$amt2)]>;
    591 }
    592 
    593 // Some assembly macros need to avoid pseudoinstructions and assembler
    594 // automatic reodering, we should reorder ourselves.
    595 def MACRO     : MipsPseudo<(outs), (ins), ".set\tmacro",     []>;
    596 def REORDER   : MipsPseudo<(outs), (ins), ".set\treorder",   []>;
    597 def NOMACRO   : MipsPseudo<(outs), (ins), ".set\tnomacro",   []>;
    598 def NOREORDER : MipsPseudo<(outs), (ins), ".set\tnoreorder", []>;
    599 
    600 // These macros are inserted to prevent GAS from complaining
    601 // when using the AT register.
    602 def NOAT      : MipsPseudo<(outs), (ins), ".set\tnoat", []>;
    603 def ATMACRO   : MipsPseudo<(outs), (ins), ".set\tat", []>;
    604 
    605 // When handling PIC code the assembler needs .cpload and .cprestore
    606 // directives. If the real instructions corresponding these directives
    607 // are used, we have the same behavior, but get also a bunch of warnings
    608 // from the assembler.
    609 def CPLOAD : MipsPseudo<(outs), (ins CPURegs:$picreg), ".cpload\t$picreg", []>;
    610 def CPRESTORE : MipsPseudo<(outs), (ins i32imm:$loc), ".cprestore\t$loc", []>;
    611 
    612 let usesCustomInserter = 1 in {
    613   def ATOMIC_LOAD_ADD_I8   : Atomic2Ops<atomic_load_add_8, "load_add_8">;
    614   def ATOMIC_LOAD_ADD_I16  : Atomic2Ops<atomic_load_add_16, "load_add_16">;
    615   def ATOMIC_LOAD_ADD_I32  : Atomic2Ops<atomic_load_add_32, "load_add_32">;
    616   def ATOMIC_LOAD_SUB_I8   : Atomic2Ops<atomic_load_sub_8, "load_sub_8">;
    617   def ATOMIC_LOAD_SUB_I16  : Atomic2Ops<atomic_load_sub_16, "load_sub_16">;
    618   def ATOMIC_LOAD_SUB_I32  : Atomic2Ops<atomic_load_sub_32, "load_sub_32">;
    619   def ATOMIC_LOAD_AND_I8   : Atomic2Ops<atomic_load_and_8, "load_and_8">;
    620   def ATOMIC_LOAD_AND_I16  : Atomic2Ops<atomic_load_and_16, "load_and_16">;
    621   def ATOMIC_LOAD_AND_I32  : Atomic2Ops<atomic_load_and_32, "load_and_32">;
    622   def ATOMIC_LOAD_OR_I8    : Atomic2Ops<atomic_load_or_8, "load_or_8">;
    623   def ATOMIC_LOAD_OR_I16   : Atomic2Ops<atomic_load_or_16, "load_or_16">;
    624   def ATOMIC_LOAD_OR_I32   : Atomic2Ops<atomic_load_or_32, "load_or_32">;
    625   def ATOMIC_LOAD_XOR_I8   : Atomic2Ops<atomic_load_xor_8, "load_xor_8">;
    626   def ATOMIC_LOAD_XOR_I16  : Atomic2Ops<atomic_load_xor_16, "load_xor_16">;
    627   def ATOMIC_LOAD_XOR_I32  : Atomic2Ops<atomic_load_xor_32, "load_xor_32">;
    628   def ATOMIC_LOAD_NAND_I8  : Atomic2Ops<atomic_load_nand_8, "load_nand_8">;
    629   def ATOMIC_LOAD_NAND_I16 : Atomic2Ops<atomic_load_nand_16, "load_nand_16">;
    630   def ATOMIC_LOAD_NAND_I32 : Atomic2Ops<atomic_load_nand_32, "load_nand_32">;
    631 
    632   def ATOMIC_SWAP_I8       : Atomic2Ops<atomic_swap_8, "swap_8">;
    633   def ATOMIC_SWAP_I16      : Atomic2Ops<atomic_swap_16, "swap_16">;
    634   def ATOMIC_SWAP_I32      : Atomic2Ops<atomic_swap_32, "swap_32">;
    635 
    636   def ATOMIC_CMP_SWAP_I8   : AtomicCmpSwap<atomic_cmp_swap_8, "8">;
    637   def ATOMIC_CMP_SWAP_I16  : AtomicCmpSwap<atomic_cmp_swap_16, "16">;
    638   def ATOMIC_CMP_SWAP_I32  : AtomicCmpSwap<atomic_cmp_swap_32, "32">;
    639 }
    640 
    641 //===----------------------------------------------------------------------===//
    642 // Instruction definition
    643 //===----------------------------------------------------------------------===//
    644 
    645 //===----------------------------------------------------------------------===//
    646 // MipsI Instructions
    647 //===----------------------------------------------------------------------===//
    648 
    649 /// Arithmetic Instructions (ALU Immediate)
    650 def ADDiu   : ArithLogicI<0x09, "addiu", add, simm16, immSExt16, CPURegs>;
    651 def ADDi    : ArithOverflowI<0x08, "addi", add, simm16, immSExt16, CPURegs>;
    652 def SLTi    : SetCC_I<0x0a, "slti", setlt, simm16, immSExt16, CPURegs>;
    653 def SLTiu   : SetCC_I<0x0b, "sltiu", setult, simm16, immSExt16, CPURegs>;
    654 def ANDi    : ArithLogicI<0x0c, "andi", and, uimm16, immZExt16, CPURegs>;
    655 def ORi     : ArithLogicI<0x0d, "ori", or, uimm16, immZExt16, CPURegs>;
    656 def XORi    : ArithLogicI<0x0e, "xori", xor, uimm16, immZExt16, CPURegs>;
    657 def LUi     : LoadUpper<0x0f, "lui">;
    658 
    659 /// Arithmetic Instructions (3-Operand, R-Type)
    660 def ADDu    : ArithLogicR<0x00, 0x21, "addu", add, IIAlu, CPURegs, 1>;
    661 def SUBu    : ArithLogicR<0x00, 0x23, "subu", sub, IIAlu, CPURegs>;
    662 def ADD     : ArithOverflowR<0x00, 0x20, "add", IIAlu, CPURegs, 1>;
    663 def SUB     : ArithOverflowR<0x00, 0x22, "sub", IIAlu, CPURegs>;
    664 def SLT     : SetCC_R<0x00, 0x2a, "slt", setlt, CPURegs>;
    665 def SLTu    : SetCC_R<0x00, 0x2b, "sltu", setult, CPURegs>;
    666 def AND     : ArithLogicR<0x00, 0x24, "and", and, IIAlu, CPURegs, 1>;
    667 def OR      : ArithLogicR<0x00, 0x25, "or",  or, IIAlu, CPURegs, 1>;
    668 def XOR     : ArithLogicR<0x00, 0x26, "xor", xor, IIAlu, CPURegs, 1>;
    669 def NOR     : LogicNOR<0x00, 0x27, "nor", CPURegs>;
    670 
    671 /// Shift Instructions
    672 def SLL     : LogicR_shift_rotate_imm<0x00, 0x00, "sll", shl>;
    673 def SRL     : LogicR_shift_rotate_imm<0x02, 0x00, "srl", srl>;
    674 def SRA     : LogicR_shift_rotate_imm<0x03, 0x00, "sra", sra>;
    675 def SLLV    : LogicR_shift_rotate_reg<0x04, 0x00, "sllv", shl>;
    676 def SRLV    : LogicR_shift_rotate_reg<0x06, 0x00, "srlv", srl>;
    677 def SRAV    : LogicR_shift_rotate_reg<0x07, 0x00, "srav", sra>;
    678 
    679 // Rotate Instructions
    680 let Predicates = [HasMips32r2] in {
    681     def ROTR    : LogicR_shift_rotate_imm<0x02, 0x01, "rotr", rotr>;
    682     def ROTRV   : LogicR_shift_rotate_reg<0x06, 0x01, "rotrv", rotr>;
    683 }
    684 
    685 /// Load and Store Instructions
    686 ///  aligned
    687 defm LB      : LoadM32<0x20, "lb",  sextloadi8>;
    688 defm LBu     : LoadM32<0x24, "lbu", zextloadi8>;
    689 defm LH      : LoadM32<0x21, "lh",  sextloadi16_a>;
    690 defm LHu     : LoadM32<0x25, "lhu", zextloadi16_a>;
    691 defm LW      : LoadM32<0x23, "lw",  load_a>;
    692 defm SB      : StoreM32<0x28, "sb", truncstorei8>;
    693 defm SH      : StoreM32<0x29, "sh", truncstorei16_a>;
    694 defm SW      : StoreM32<0x2b, "sw", store_a>;
    695 
    696 ///  unaligned
    697 defm ULH     : LoadM32<0x21, "ulh",  sextloadi16_u, 1>;
    698 defm ULHu    : LoadM32<0x25, "ulhu", zextloadi16_u, 1>;
    699 defm ULW     : LoadM32<0x23, "ulw",  load_u, 1>;
    700 defm USH     : StoreM32<0x29, "ush", truncstorei16_u, 1>;
    701 defm USW     : StoreM32<0x2b, "usw", store_u, 1>;
    702 
    703 let hasSideEffects = 1 in
    704 def SYNC : MipsInst<(outs), (ins i32imm:$stype), "sync $stype",
    705                     [(MipsSync imm:$stype)], NoItinerary, FrmOther>
    706 {
    707   bits<5> stype;
    708   let Opcode = 0;
    709   let Inst{25-11} = 0;
    710   let Inst{10-6} = stype;
    711   let Inst{5-0} = 15;
    712 }
    713 
    714 /// Load-linked, Store-conditional
    715 let mayLoad = 1 in
    716   def LL    : FMem<0x30, (outs CPURegs:$rt), (ins mem:$addr),
    717               "ll\t$rt, $addr", [], IILoad>;
    718 let mayStore = 1, Constraints = "$rt = $dst" in
    719   def SC    : FMem<0x38, (outs CPURegs:$dst), (ins CPURegs:$rt, mem:$addr),
    720               "sc\t$rt, $addr", [], IIStore>;
    721 
    722 /// Jump and Branch Instructions
    723 def J       : JumpFJ<0x02, "j">;
    724 let isIndirectBranch = 1 in
    725   def JR      : JumpFR<0x00, 0x08, "jr">;
    726 def JAL     : JumpLink<0x03, "jal">;
    727 def JALR    : JumpLinkReg<0x00, 0x09, "jalr">;
    728 def BEQ     : CBranch<0x04, "beq", seteq, CPURegs>;
    729 def BNE     : CBranch<0x05, "bne", setne, CPURegs>;
    730 def BGEZ    : CBranchZero<0x01, 1, "bgez", setge, CPURegs>;
    731 def BGTZ    : CBranchZero<0x07, 0, "bgtz", setgt, CPURegs>;
    732 def BLEZ    : CBranchZero<0x06, 0, "blez", setle, CPURegs>;
    733 def BLTZ    : CBranchZero<0x01, 0, "bltz", setlt, CPURegs>;
    734 
    735 let rt=0x11 in
    736   def BGEZAL  : BranchLink<"bgezal">;
    737 let rt=0x10 in
    738   def BLTZAL  : BranchLink<"bltzal">;
    739 
    740 let isReturn=1, isTerminator=1, hasDelaySlot=1,
    741     isBarrier=1, hasCtrlDep=1, rd=0, rt=0, shamt=0 in
    742   def RET : FR <0x00, 0x08, (outs), (ins CPURegs:$target),
    743                 "jr\t$target", [(MipsRet CPURegs:$target)], IIBranch>;
    744 
    745 /// Multiply and Divide Instructions.
    746 def MULT    : Mul<0x18, "mult", IIImul>;
    747 def MULTu   : Mul<0x19, "multu", IIImul>;
    748 def SDIV    : Div<MipsDivRem, 0x1a, "div", IIIdiv>;
    749 def UDIV    : Div<MipsDivRemU, 0x1b, "divu", IIIdiv>;
    750 
    751 let Defs = [HI] in
    752   def MTHI  : MoveToLOHI<0x11, "mthi">;
    753 let Defs = [LO] in
    754   def MTLO  : MoveToLOHI<0x13, "mtlo">;
    755 
    756 let Uses = [HI] in
    757   def MFHI  : MoveFromLOHI<0x10, "mfhi">;
    758 let Uses = [LO] in
    759   def MFLO  : MoveFromLOHI<0x12, "mflo">;
    760 
    761 /// Sign Ext In Register Instructions.
    762 def SEB : SignExtInReg<0x10, "seb", i8>;
    763 def SEH : SignExtInReg<0x18, "seh", i16>;
    764 
    765 /// Count Leading
    766 def CLZ : CountLeading<0x20, "clz",
    767                        [(set CPURegs:$rd, (ctlz CPURegs:$rs))]>;
    768 def CLO : CountLeading<0x21, "clo",
    769                        [(set CPURegs:$rd, (ctlz (not CPURegs:$rs)))]>;
    770 
    771 /// Byte Swap
    772 def WSBW : ByteSwap<0x20, 0x2, "wsbw">;
    773 
    774 // Conditional moves:
    775 // These instructions are expanded in
    776 // MipsISelLowering::EmitInstrWithCustomInserter if target does not have
    777 // conditional move instructions.
    778 // flag:int, data:int
    779 class CondMovIntInt<bits<6> funct, string instr_asm> :
    780   FR<0, funct, (outs CPURegs:$rd),
    781      (ins CPURegs:$rs, CPURegs:$rt, CPURegs:$F),
    782      !strconcat(instr_asm, "\t$rd, $rs, $rt"), [], NoItinerary> {
    783   let shamt = 0;
    784   let usesCustomInserter = 1;
    785   let Constraints = "$F = $rd";
    786 }
    787 
    788 def MOVZ_I : CondMovIntInt<0x0a, "movz">;
    789 def MOVN_I : CondMovIntInt<0x0b, "movn">;
    790 
    791 /// No operation
    792 let addr=0 in
    793   def NOP   : FJ<0, (outs), (ins), "nop", [], IIAlu>;
    794 
    795 // FrameIndexes are legalized when they are operands from load/store
    796 // instructions. The same not happens for stack address copies, so an
    797 // add op with mem ComplexPattern is used and the stack address copy
    798 // can be matched. It's similar to Sparc LEA_ADDRi
    799 def LEA_ADDiu : EffectiveAddress<"addiu\t$rt, $addr">;
    800 
    801 // DynAlloc node points to dynamically allocated stack space.
    802 // $sp is added to the list of implicitly used registers to prevent dead code
    803 // elimination from removing instructions that modify $sp.
    804 let Uses = [SP] in
    805 def DynAlloc : EffectiveAddress<"addiu\t$rt, $addr">;
    806 
    807 // MADD*/MSUB*
    808 def MADD  : MArithR<0, "madd", MipsMAdd, 1>;
    809 def MADDU : MArithR<1, "maddu", MipsMAddu, 1>;
    810 def MSUB  : MArithR<4, "msub", MipsMSub>;
    811 def MSUBU : MArithR<5, "msubu", MipsMSubu>;
    812 
    813 // MUL is a assembly macro in the current used ISAs. In recent ISA's
    814 // it is a real instruction.
    815 def MUL   : ArithLogicR<0x1c, 0x02, "mul", mul, IIImul, CPURegs, 1>,
    816             Requires<[HasMips32]>;
    817 
    818 def RDHWR : ReadHardware;
    819 
    820 def EXT : ExtIns<0, "ext", (outs CPURegs:$rt),
    821                  (ins CPURegs:$rs, uimm16:$pos, size_ext:$sz),
    822                  [(set CPURegs:$rt,
    823                    (MipsExt CPURegs:$rs, immZExt5:$pos, immZExt5:$sz))],
    824                  NoItinerary>;
    825 
    826 let Constraints = "$src = $rt" in
    827 def INS : ExtIns<4, "ins", (outs CPURegs:$rt),
    828                  (ins CPURegs:$rs, uimm16:$pos, size_ins:$sz, CPURegs:$src),
    829                  [(set CPURegs:$rt,
    830                    (MipsIns CPURegs:$rs, immZExt5:$pos, immZExt5:$sz,
    831                     CPURegs:$src))],
    832                  NoItinerary>;
    833 
    834 //===----------------------------------------------------------------------===//
    835 //  Arbitrary patterns that map to one or more instructions
    836 //===----------------------------------------------------------------------===//
    837 
    838 // Small immediates
    839 def : Pat<(i32 immSExt16:$in),
    840           (ADDiu ZERO, imm:$in)>;
    841 def : Pat<(i32 immZExt16:$in),
    842           (ORi ZERO, imm:$in)>;
    843 
    844 // Arbitrary immediates
    845 def : Pat<(i32 imm:$imm),
    846           (ORi (LUi (HI16 imm:$imm)), (LO16 imm:$imm))>;
    847 
    848 // Carry patterns
    849 def : Pat<(subc CPURegs:$lhs, CPURegs:$rhs),
    850           (SUBu CPURegs:$lhs, CPURegs:$rhs)>;
    851 def : Pat<(addc CPURegs:$lhs, CPURegs:$rhs),
    852           (ADDu CPURegs:$lhs, CPURegs:$rhs)>;
    853 def : Pat<(addc  CPURegs:$src, immSExt16:$imm),
    854           (ADDiu CPURegs:$src, imm:$imm)>;
    855 
    856 // Call
    857 def : Pat<(MipsJmpLink (i32 tglobaladdr:$dst)),
    858           (JAL tglobaladdr:$dst)>;
    859 def : Pat<(MipsJmpLink (i32 texternalsym:$dst)),
    860           (JAL texternalsym:$dst)>;
    861 //def : Pat<(MipsJmpLink CPURegs:$dst),
    862 //          (JALR CPURegs:$dst)>;
    863 
    864 // hi/lo relocs
    865 def : Pat<(MipsHi tglobaladdr:$in), (LUi tglobaladdr:$in)>;
    866 def : Pat<(MipsHi tblockaddress:$in), (LUi tblockaddress:$in)>;
    867 def : Pat<(MipsLo tglobaladdr:$in), (ADDiu ZERO, tglobaladdr:$in)>;
    868 def : Pat<(MipsLo tblockaddress:$in), (ADDiu ZERO, tblockaddress:$in)>;
    869 def : Pat<(add CPURegs:$hi, (MipsLo tglobaladdr:$lo)),
    870           (ADDiu CPURegs:$hi, tglobaladdr:$lo)>;
    871 def : Pat<(add CPURegs:$hi, (MipsLo tblockaddress:$lo)),
    872           (ADDiu CPURegs:$hi, tblockaddress:$lo)>;
    873 
    874 def : Pat<(MipsHi tjumptable:$in), (LUi tjumptable:$in)>;
    875 def : Pat<(MipsLo tjumptable:$in), (ADDiu ZERO, tjumptable:$in)>;
    876 def : Pat<(add CPURegs:$hi, (MipsLo tjumptable:$lo)),
    877           (ADDiu CPURegs:$hi, tjumptable:$lo)>;
    878 
    879 def : Pat<(MipsHi tconstpool:$in), (LUi tconstpool:$in)>;
    880 def : Pat<(MipsLo tconstpool:$in), (ADDiu ZERO, tconstpool:$in)>;
    881 def : Pat<(add CPURegs:$hi, (MipsLo tconstpool:$lo)),
    882           (ADDiu CPURegs:$hi, tconstpool:$lo)>;
    883 
    884 // gp_rel relocs
    885 def : Pat<(add CPURegs:$gp, (MipsGPRel tglobaladdr:$in)),
    886           (ADDiu CPURegs:$gp, tglobaladdr:$in)>;
    887 def : Pat<(add CPURegs:$gp, (MipsGPRel tconstpool:$in)),
    888           (ADDiu CPURegs:$gp, tconstpool:$in)>;
    889 
    890 // tlsgd
    891 def : Pat<(add CPURegs:$gp, (MipsTlsGd tglobaltlsaddr:$in)),
    892           (ADDiu CPURegs:$gp, tglobaltlsaddr:$in)>;
    893 
    894 // tprel hi/lo
    895 def : Pat<(MipsTprelHi tglobaltlsaddr:$in), (LUi tglobaltlsaddr:$in)>;
    896 def : Pat<(MipsTprelLo tglobaltlsaddr:$in), (ADDiu ZERO, tglobaltlsaddr:$in)>;
    897 def : Pat<(add CPURegs:$hi, (MipsTprelLo tglobaltlsaddr:$lo)),
    898           (ADDiu CPURegs:$hi, tglobaltlsaddr:$lo)>;
    899 
    900 // wrapper_pic
    901 class WrapperPICPat<SDNode node>:
    902       Pat<(MipsWrapperPIC node:$in),
    903           (ADDiu GP, node:$in)>;
    904 
    905 def : WrapperPICPat<tglobaladdr>;
    906 def : WrapperPICPat<tconstpool>;
    907 def : WrapperPICPat<texternalsym>;
    908 def : WrapperPICPat<tblockaddress>;
    909 def : WrapperPICPat<tjumptable>;
    910 
    911 // Mips does not have "not", so we expand our way
    912 def : Pat<(not CPURegs:$in),
    913           (NOR CPURegs:$in, ZERO)>;
    914 
    915 // extended load and stores
    916 def : Pat<(extloadi1  addr:$src), (LBu addr:$src)>;
    917 def : Pat<(extloadi8  addr:$src), (LBu addr:$src)>;
    918 def : Pat<(extloadi16_a addr:$src), (LHu addr:$src)>;
    919 def : Pat<(extloadi16_u addr:$src), (ULHu addr:$src)>;
    920 
    921 // peepholes
    922 def : Pat<(store (i32 0), addr:$dst), (SW ZERO, addr:$dst)>;
    923 
    924 // brcond patterns
    925 multiclass BrcondPats<RegisterClass RC, Instruction BEQOp, Instruction BNEOp,
    926                       Instruction SLTOp, Instruction SLTuOp, Instruction SLTiOp,
    927                       Instruction SLTiuOp, Register ZEROReg> {
    928 def : Pat<(brcond (i32 (setne RC:$lhs, 0)), bb:$dst),
    929           (BNEOp RC:$lhs, ZEROReg, bb:$dst)>;
    930 def : Pat<(brcond (i32 (seteq RC:$lhs, 0)), bb:$dst),
    931           (BEQOp RC:$lhs, ZEROReg, bb:$dst)>;
    932 
    933 def : Pat<(brcond (i32 (setge RC:$lhs, RC:$rhs)), bb:$dst),
    934           (BEQ (SLTOp RC:$lhs, RC:$rhs), ZERO, bb:$dst)>;
    935 def : Pat<(brcond (i32 (setuge RC:$lhs, RC:$rhs)), bb:$dst),
    936           (BEQ (SLTuOp RC:$lhs, RC:$rhs), ZERO, bb:$dst)>;
    937 def : Pat<(brcond (i32 (setge RC:$lhs, immSExt16:$rhs)), bb:$dst),
    938           (BEQ (SLTiOp RC:$lhs, immSExt16:$rhs), ZERO, bb:$dst)>;
    939 def : Pat<(brcond (i32 (setuge RC:$lhs, immSExt16:$rhs)), bb:$dst),
    940           (BEQ (SLTiuOp RC:$lhs, immSExt16:$rhs), ZERO, bb:$dst)>;
    941 
    942 def : Pat<(brcond (i32 (setle RC:$lhs, RC:$rhs)), bb:$dst),
    943           (BEQ (SLTOp RC:$rhs, RC:$lhs), ZERO, bb:$dst)>;
    944 def : Pat<(brcond (i32 (setule RC:$lhs, RC:$rhs)), bb:$dst),
    945           (BEQ (SLTuOp RC:$rhs, RC:$lhs), ZERO, bb:$dst)>;
    946 
    947 def : Pat<(brcond RC:$cond, bb:$dst),
    948           (BNEOp RC:$cond, ZEROReg, bb:$dst)>;
    949 }
    950 
    951 defm : BrcondPats<CPURegs, BEQ, BNE, SLT, SLTu, SLTi, SLTiu, ZERO>;
    952 
    953 // select patterns
    954 multiclass MovzPats<RegisterClass RC, Instruction MOVZInst> {
    955   def : Pat<(select (i32 (setge CPURegs:$lhs, CPURegs:$rhs)), RC:$T, RC:$F),
    956             (MOVZInst RC:$T, (SLT CPURegs:$lhs, CPURegs:$rhs), RC:$F)>;
    957   def : Pat<(select (i32 (setuge CPURegs:$lhs, CPURegs:$rhs)), RC:$T, RC:$F),
    958             (MOVZInst RC:$T, (SLTu CPURegs:$lhs, CPURegs:$rhs), RC:$F)>;
    959   def : Pat<(select (i32 (setge CPURegs:$lhs, immSExt16:$rhs)), RC:$T, RC:$F),
    960             (MOVZInst RC:$T, (SLTi CPURegs:$lhs, immSExt16:$rhs), RC:$F)>;
    961   def : Pat<(select (i32 (setuge CPURegs:$lh, immSExt16:$rh)), RC:$T, RC:$F),
    962             (MOVZInst RC:$T, (SLTiu CPURegs:$lh, immSExt16:$rh), RC:$F)>;
    963   def : Pat<(select (i32 (setle CPURegs:$lhs, CPURegs:$rhs)), RC:$T, RC:$F),
    964             (MOVZInst RC:$T, (SLT CPURegs:$rhs, CPURegs:$lhs), RC:$F)>;
    965   def : Pat<(select (i32 (setule CPURegs:$lhs, CPURegs:$rhs)), RC:$T, RC:$F),
    966             (MOVZInst RC:$T, (SLTu CPURegs:$rhs, CPURegs:$lhs), RC:$F)>;
    967   def : Pat<(select (i32 (seteq CPURegs:$lhs, CPURegs:$rhs)), RC:$T, RC:$F),
    968             (MOVZInst RC:$T, (XOR CPURegs:$lhs, CPURegs:$rhs), RC:$F)>;
    969   def : Pat<(select (i32 (seteq CPURegs:$lhs, 0)), RC:$T, RC:$F),
    970             (MOVZInst RC:$T, CPURegs:$lhs, RC:$F)>;
    971 }
    972 
    973 multiclass MovnPats<RegisterClass RC, Instruction MOVNInst> {
    974   def : Pat<(select (i32 (setne CPURegs:$lhs, CPURegs:$rhs)), RC:$T, RC:$F),
    975             (MOVNInst RC:$T, (XOR CPURegs:$lhs, CPURegs:$rhs), RC:$F)>;
    976   def : Pat<(select CPURegs:$cond, RC:$T, RC:$F),
    977             (MOVNInst RC:$T, CPURegs:$cond, RC:$F)>;
    978   def : Pat<(select (i32 (setne CPURegs:$lhs, 0)), RC:$T, RC:$F),
    979             (MOVNInst RC:$T, CPURegs:$lhs, RC:$F)>;
    980 }
    981 
    982 defm : MovzPats<CPURegs, MOVZ_I>;
    983 defm : MovnPats<CPURegs, MOVN_I>;
    984 
    985 // setcc patterns
    986 multiclass SeteqPats<RegisterClass RC, Instruction SLTiuOp, Instruction XOROp,
    987                      Instruction SLTuOp, Register ZEROReg> {
    988   def : Pat<(seteq RC:$lhs, RC:$rhs),
    989             (SLTiuOp (XOROp RC:$lhs, RC:$rhs), 1)>;
    990   def : Pat<(setne RC:$lhs, RC:$rhs),
    991             (SLTuOp ZEROReg, (XOROp RC:$lhs, RC:$rhs))>;
    992 }
    993 
    994 multiclass SetlePats<RegisterClass RC, Instruction SLTOp, Instruction SLTuOp> {
    995   def : Pat<(setle RC:$lhs, RC:$rhs),
    996             (XORi (SLTOp RC:$rhs, RC:$lhs), 1)>;
    997   def : Pat<(setule RC:$lhs, RC:$rhs),
    998             (XORi (SLTuOp RC:$rhs, RC:$lhs), 1)>;
    999 }
   1000 
   1001 multiclass SetgtPats<RegisterClass RC, Instruction SLTOp, Instruction SLTuOp> {
   1002   def : Pat<(setgt RC:$lhs, RC:$rhs),
   1003             (SLTOp RC:$rhs, RC:$lhs)>;
   1004   def : Pat<(setugt RC:$lhs, RC:$rhs),
   1005             (SLTuOp RC:$rhs, RC:$lhs)>;
   1006 }
   1007 
   1008 multiclass SetgePats<RegisterClass RC, Instruction SLTOp, Instruction SLTuOp> {
   1009   def : Pat<(setge RC:$lhs, RC:$rhs),
   1010             (XORi (SLTOp RC:$lhs, RC:$rhs), 1)>;
   1011   def : Pat<(setuge RC:$lhs, RC:$rhs),
   1012             (XORi (SLTuOp RC:$lhs, RC:$rhs), 1)>;
   1013 }
   1014 
   1015 multiclass SetgeImmPats<RegisterClass RC, Instruction SLTiOp,
   1016                         Instruction SLTiuOp> {
   1017   def : Pat<(setge RC:$lhs, immSExt16:$rhs),
   1018             (XORi (SLTiOp RC:$lhs, immSExt16:$rhs), 1)>;
   1019   def : Pat<(setuge RC:$lhs, immSExt16:$rhs),
   1020             (XORi (SLTiuOp RC:$lhs, immSExt16:$rhs), 1)>;
   1021 }
   1022 
   1023 defm : SeteqPats<CPURegs, SLTiu, XOR, SLTu, ZERO>;
   1024 defm : SetlePats<CPURegs, SLT, SLTu>;
   1025 defm : SetgtPats<CPURegs, SLT, SLTu>;
   1026 defm : SetgePats<CPURegs, SLT, SLTu>;
   1027 defm : SetgeImmPats<CPURegs, SLTi, SLTiu>;
   1028 
   1029 // select MipsDynAlloc
   1030 def : Pat<(MipsDynAlloc addr:$f), (DynAlloc addr:$f)>;
   1031 
   1032 //===----------------------------------------------------------------------===//
   1033 // Floating Point Support
   1034 //===----------------------------------------------------------------------===//
   1035 
   1036 include "MipsInstrFPU.td"
   1037 include "Mips64InstrInfo.td"
   1038 
   1039