Home | History | Annotate | Download | only in MBlaze
      1 //===- MBlazeInstrInfo.td - MBlaze Instruction defs --------*- 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 //===----------------------------------------------------------------------===//
     11 // Instruction format superclass
     12 //===----------------------------------------------------------------------===//
     13 include "MBlazeInstrFormats.td"
     14 
     15 //===----------------------------------------------------------------------===//
     16 // MBlaze type profiles
     17 //===----------------------------------------------------------------------===//
     18 
     19 // def SDTMBlazeSelectCC : SDTypeProfile<1, 3, [SDTCisSameAs<0, 1>]>;
     20 def SDT_MBlazeRet     : SDTypeProfile<0, 1, [SDTCisInt<0>]>;
     21 def SDT_MBlazeIRet    : SDTypeProfile<0, 1, [SDTCisInt<0>]>;
     22 def SDT_MBlazeJmpLink : SDTypeProfile<0, -1, [SDTCisVT<0, i32>]>;
     23 def SDT_MBCallSeqStart : SDCallSeqStart<[SDTCisVT<0, i32>]>;
     24 def SDT_MBCallSeqEnd   : SDCallSeqEnd<[SDTCisVT<0, i32>, SDTCisVT<1, i32>]>;
     25 
     26 //===----------------------------------------------------------------------===//
     27 // MBlaze specific nodes
     28 //===----------------------------------------------------------------------===//
     29 
     30 def MBlazeRet     : SDNode<"MBlazeISD::Ret", SDT_MBlazeRet,
     31                            [SDNPHasChain, SDNPOptInGlue]>;
     32 def MBlazeIRet    : SDNode<"MBlazeISD::IRet", SDT_MBlazeIRet,
     33                            [SDNPHasChain, SDNPOptInGlue]>;
     34 
     35 def MBlazeJmpLink : SDNode<"MBlazeISD::JmpLink",SDT_MBlazeJmpLink,
     36                            [SDNPHasChain,SDNPOptInGlue,SDNPOutGlue,
     37                             SDNPVariadic]>;
     38 
     39 def MBWrapper   : SDNode<"MBlazeISD::Wrap", SDTIntUnaryOp>;
     40 
     41 def callseq_start : SDNode<"ISD::CALLSEQ_START", SDT_MBCallSeqStart,
     42                            [SDNPHasChain, SDNPOutGlue]>;
     43 
     44 def callseq_end   : SDNode<"ISD::CALLSEQ_END", SDT_MBCallSeqEnd,
     45                            [SDNPHasChain, SDNPOptInGlue, SDNPOutGlue]>;
     46 
     47 //===----------------------------------------------------------------------===//
     48 // MBlaze Instruction Predicate Definitions.
     49 //===----------------------------------------------------------------------===//
     50 // def HasPipe3     : Predicate<"Subtarget.hasPipe3()">;
     51 def HasBarrel    : Predicate<"Subtarget.hasBarrel()">;
     52 // def NoBarrel     : Predicate<"!Subtarget.hasBarrel()">;
     53 def HasDiv       : Predicate<"Subtarget.hasDiv()">;
     54 def HasMul       : Predicate<"Subtarget.hasMul()">;
     55 // def HasFSL       : Predicate<"Subtarget.hasFSL()">;
     56 // def HasEFSL      : Predicate<"Subtarget.hasEFSL()">;
     57 // def HasMSRSet    : Predicate<"Subtarget.hasMSRSet()">;
     58 // def HasException : Predicate<"Subtarget.hasException()">;
     59 def HasPatCmp    : Predicate<"Subtarget.hasPatCmp()">;
     60 def HasFPU       : Predicate<"Subtarget.hasFPU()">;
     61 // def HasESR       : Predicate<"Subtarget.hasESR()">;
     62 // def HasPVR       : Predicate<"Subtarget.hasPVR()">;
     63 def HasMul64     : Predicate<"Subtarget.hasMul64()">;
     64 def HasSqrt      : Predicate<"Subtarget.hasSqrt()">;
     65 // def HasMMU       : Predicate<"Subtarget.hasMMU()">;
     66 
     67 //===----------------------------------------------------------------------===//
     68 // MBlaze Operand, Complex Patterns and Transformations Definitions.
     69 //===----------------------------------------------------------------------===//
     70 
     71 def MBlazeMemAsmOperand : AsmOperandClass {
     72   let Name = "Mem";
     73   let SuperClasses = [];
     74 }
     75 
     76 def MBlazeFslAsmOperand : AsmOperandClass {
     77   let Name = "Fsl";
     78   let SuperClasses = [];
     79 }
     80 
     81 // Instruction operand types
     82 def brtarget    : Operand<OtherVT>;
     83 def calltarget  : Operand<i32>;
     84 def simm16      : Operand<i32>;
     85 def uimm5       : Operand<i32>;
     86 def uimm15      : Operand<i32>;
     87 def fimm        : Operand<f32>;
     88 
     89 // Unsigned Operand
     90 def uimm16      : Operand<i32> {
     91   let PrintMethod = "printUnsignedImm";
     92 }
     93 
     94 // FSL Operand
     95 def fslimm      : Operand<i32> {
     96   let PrintMethod = "printFSLImm";
     97   let ParserMatchClass = MBlazeFslAsmOperand;
     98 }
     99 
    100 // Address operand
    101 def memri : Operand<i32> {
    102   let PrintMethod = "printMemOperand";
    103   let MIOperandInfo = (ops GPR, simm16);
    104   let ParserMatchClass = MBlazeMemAsmOperand;
    105 }
    106 
    107 def memrr : Operand<i32> {
    108   let PrintMethod = "printMemOperand";
    109   let MIOperandInfo = (ops GPR, GPR);
    110   let ParserMatchClass = MBlazeMemAsmOperand;
    111 }
    112 
    113 // Node immediate fits as 16-bit sign extended on target immediate.
    114 def immSExt16  : PatLeaf<(imm), [{
    115   return (N->getZExtValue() >> 16) == 0;
    116 }]>;
    117 
    118 // Node immediate fits as 16-bit zero extended on target immediate.
    119 // The LO16 param means that only the lower 16 bits of the node
    120 // immediate are caught.
    121 // e.g. addiu, sltiu
    122 def immZExt16  : PatLeaf<(imm), [{
    123   return (N->getZExtValue() >> 16) == 0;
    124 }]>;
    125 
    126 // FSL immediate field must fit in 4 bits.
    127 def immZExt4 : PatLeaf<(imm), [{
    128   return N->getZExtValue() == ((N->getZExtValue()) & 0xf) ;
    129 }]>;
    130 
    131 // shamt field must fit in 5 bits.
    132 def immZExt5 : PatLeaf<(imm), [{
    133   return N->getZExtValue() == ((N->getZExtValue()) & 0x1f) ;
    134 }]>;
    135 
    136 // MBlaze Address Mode. SDNode frameindex could possibily be a match
    137 // since load and store instructions from stack used it.
    138 def iaddr : ComplexPattern<i32, 2, "SelectAddrRegImm", [frameindex], []>;
    139 def xaddr : ComplexPattern<i32, 2, "SelectAddrRegReg", [], []>;
    140 
    141 //===----------------------------------------------------------------------===//
    142 // Pseudo instructions
    143 //===----------------------------------------------------------------------===//
    144 
    145 // As stack alignment is always done with addiu, we need a 16-bit immediate
    146 let Defs = [R1], Uses = [R1] in {
    147 def ADJCALLSTACKDOWN : MBlazePseudo<(outs), (ins simm16:$amt),
    148                                   "#ADJCALLSTACKDOWN $amt",
    149                                   [(callseq_start timm:$amt)]>;
    150 def ADJCALLSTACKUP   : MBlazePseudo<(outs),
    151                                   (ins uimm16:$amt1, simm16:$amt2),
    152                                   "#ADJCALLSTACKUP $amt1",
    153                                   [(callseq_end timm:$amt1, timm:$amt2)]>;
    154 }
    155 
    156 //===----------------------------------------------------------------------===//
    157 // Instructions specific format
    158 //===----------------------------------------------------------------------===//
    159 
    160 //===----------------------------------------------------------------------===//
    161 // Arithmetic Instructions
    162 //===----------------------------------------------------------------------===//
    163 class Arith<bits<6> op, bits<11> flags, string instr_asm, SDNode OpNode,
    164             InstrItinClass itin> :
    165             TA<op, flags, (outs GPR:$dst), (ins GPR:$b, GPR:$c),
    166                !strconcat(instr_asm, "   $dst, $b, $c"),
    167                [(set GPR:$dst, (OpNode GPR:$b, GPR:$c))], itin>;
    168 
    169 class ArithI<bits<6> op, string instr_asm, SDNode OpNode,
    170              Operand Od, PatLeaf imm_type> :
    171              TB<op, (outs GPR:$dst), (ins GPR:$b, Od:$c),
    172                 !strconcat(instr_asm, "   $dst, $b, $c"),
    173                 [(set GPR:$dst, (OpNode GPR:$b, imm_type:$c))], IIC_ALU>;
    174 
    175 class ArithI32<bits<6> op, string instr_asm,Operand Od, PatLeaf imm_type> :
    176                TB<op, (outs GPR:$dst), (ins GPR:$b, Od:$c),
    177                   !strconcat(instr_asm, "   $dst, $b, $c"),
    178                   [], IIC_ALU>;
    179 
    180 class ShiftI<bits<6> op, bits<2> flags, string instr_asm, SDNode OpNode,
    181              Operand Od, PatLeaf imm_type> :
    182              SHT<op, flags, (outs GPR:$dst), (ins GPR:$b, Od:$c),
    183                  !strconcat(instr_asm, "   $dst, $b, $c"),
    184                  [(set GPR:$dst, (OpNode GPR:$b, imm_type:$c))], IIC_SHT>;
    185 
    186 class ArithR<bits<6> op, bits<11> flags, string instr_asm, SDNode OpNode,
    187             InstrItinClass itin> :
    188             TAR<op, flags, (outs GPR:$dst), (ins GPR:$b, GPR:$c),
    189                 !strconcat(instr_asm, "   $dst, $c, $b"),
    190                 [(set GPR:$dst, (OpNode GPR:$b, GPR:$c))], itin>;
    191 
    192 class ArithRI<bits<6> op, string instr_asm, SDNode OpNode,
    193              Operand Od, PatLeaf imm_type> :
    194              TBR<op, (outs GPR:$dst), (ins Od:$b, GPR:$c),
    195                  !strconcat(instr_asm, "   $dst, $c, $b"),
    196                  [(set GPR:$dst, (OpNode imm_type:$b, GPR:$c))], IIC_ALU>;
    197 
    198 class ArithN<bits<6> op, bits<11> flags, string instr_asm,
    199             InstrItinClass itin> :
    200             TA<op, flags, (outs GPR:$dst), (ins GPR:$b, GPR:$c),
    201                !strconcat(instr_asm, "   $dst, $b, $c"),
    202                [], itin>;
    203 
    204 class ArithNI<bits<6> op, string instr_asm,Operand Od, PatLeaf imm_type> :
    205              TB<op, (outs GPR:$dst), (ins GPR:$b, Od:$c),
    206                 !strconcat(instr_asm, "   $dst, $b, $c"),
    207                 [], IIC_ALU>;
    208 
    209 class ArithRN<bits<6> op, bits<11> flags, string instr_asm,
    210             InstrItinClass itin> :
    211             TAR<op, flags, (outs GPR:$dst), (ins GPR:$c, GPR:$b),
    212                 !strconcat(instr_asm, "   $dst, $b, $c"),
    213                 [], itin>;
    214 
    215 class ArithRNI<bits<6> op, string instr_asm,Operand Od, PatLeaf imm_type> :
    216              TBR<op, (outs GPR:$dst), (ins Od:$c, GPR:$b),
    217                  !strconcat(instr_asm, "   $dst, $b, $c"),
    218                  [], IIC_ALU>;
    219 
    220 //===----------------------------------------------------------------------===//
    221 // Misc Arithmetic Instructions
    222 //===----------------------------------------------------------------------===//
    223 
    224 class Logic<bits<6> op, bits<11> flags, string instr_asm, SDNode OpNode> :
    225             TA<op, flags, (outs GPR:$dst), (ins GPR:$b, GPR:$c),
    226                !strconcat(instr_asm, "   $dst, $b, $c"),
    227                [(set GPR:$dst, (OpNode GPR:$b, GPR:$c))], IIC_ALU>;
    228 
    229 class LogicI<bits<6> op, string instr_asm, SDNode OpNode> :
    230              TB<op, (outs GPR:$dst), (ins GPR:$b, uimm16:$c),
    231                 !strconcat(instr_asm, "   $dst, $b, $c"),
    232                 [(set GPR:$dst, (OpNode GPR:$b, immZExt16:$c))],
    233                 IIC_ALU>;
    234 
    235 class LogicI32<bits<6> op, string instr_asm> :
    236                TB<op, (outs GPR:$dst), (ins GPR:$b, uimm16:$c),
    237                   !strconcat(instr_asm, "   $dst, $b, $c"),
    238                   [], IIC_ALU>;
    239 
    240 class PatCmp<bits<6> op, bits<11> flags, string instr_asm> :
    241              TA<op, flags, (outs GPR:$dst), (ins GPR:$b, GPR:$c),
    242                 !strconcat(instr_asm, "   $dst, $b, $c"),
    243                  [], IIC_ALU>;
    244 
    245 //===----------------------------------------------------------------------===//
    246 // Memory Access Instructions
    247 //===----------------------------------------------------------------------===//
    248 
    249 let mayLoad = 1 in {
    250 class LoadM<bits<6> op, bits<11> flags, string instr_asm> :
    251             TA<op, flags, (outs GPR:$dst), (ins memrr:$addr),
    252                !strconcat(instr_asm, "   $dst, $addr"),
    253                [], IIC_MEMl>;
    254 }
    255 
    256 class LoadMI<bits<6> op, string instr_asm, PatFrag OpNode> :
    257              TB<op, (outs GPR:$dst), (ins memri:$addr),
    258                 !strconcat(instr_asm, "   $dst, $addr"),
    259                 [(set (i32 GPR:$dst), (OpNode iaddr:$addr))], IIC_MEMl>;
    260 
    261 let mayStore = 1 in {
    262 class StoreM<bits<6> op, bits<11> flags, string instr_asm> :
    263              TA<op, flags, (outs), (ins GPR:$dst, memrr:$addr),
    264                 !strconcat(instr_asm, "   $dst, $addr"),
    265                 [], IIC_MEMs>;
    266 }
    267 
    268 class StoreMI<bits<6> op, string instr_asm, PatFrag OpNode> :
    269               TB<op, (outs), (ins GPR:$dst, memri:$addr),
    270                  !strconcat(instr_asm, "   $dst, $addr"),
    271                  [(OpNode (i32 GPR:$dst), iaddr:$addr)], IIC_MEMs>;
    272 
    273 //===----------------------------------------------------------------------===//
    274 // Branch Instructions
    275 //===----------------------------------------------------------------------===//
    276 class Branch<bits<6> op, bits<5> br, bits<11> flags, string instr_asm> :
    277              TA<op, flags, (outs), (ins GPR:$target),
    278                 !strconcat(instr_asm, "   $target"),
    279                 [], IIC_BR> {
    280   let rd = 0x0;
    281   let ra = br;
    282   let Form = FCCR;
    283 }
    284 
    285 class BranchI<bits<6> op, bits<5> br, string instr_asm> :
    286               TB<op, (outs), (ins brtarget:$target),
    287                  !strconcat(instr_asm, "   $target"),
    288                  [], IIC_BR> {
    289   let rd = 0;
    290   let ra = br;
    291   let Form = FCCI;
    292 }
    293 
    294 //===----------------------------------------------------------------------===//
    295 // Branch and Link Instructions
    296 //===----------------------------------------------------------------------===//
    297 class BranchL<bits<6> op, bits<5> br, bits<11> flags, string instr_asm> :
    298               TA<op, flags, (outs), (ins GPR:$link, GPR:$target, variable_ops),
    299                  !strconcat(instr_asm, "   $link, $target"),
    300                  [], IIC_BRl> {
    301   let ra = br;
    302   let Form = FRCR;
    303 }
    304 
    305 class BranchLI<bits<6> op, bits<5> br, string instr_asm> :
    306                TB<op, (outs), (ins GPR:$link, calltarget:$target, variable_ops),
    307                   !strconcat(instr_asm, "   $link, $target"),
    308                   [], IIC_BRl> {
    309   let ra = br;
    310   let Form = FRCI;
    311 }
    312 
    313 //===----------------------------------------------------------------------===//
    314 // Conditional Branch Instructions
    315 //===----------------------------------------------------------------------===//
    316 class BranchC<bits<6> op, bits<5> br, bits<11> flags, string instr_asm> :
    317               TA<op, flags, (outs),
    318                  (ins GPR:$a, GPR:$b),
    319                  !strconcat(instr_asm, "   $a, $b"),
    320                  [], IIC_BRc> {
    321   let rd = br;
    322   let Form = FCRR;
    323 }
    324 
    325 class BranchCI<bits<6> op, bits<5> br, string instr_asm> :
    326                TB<op, (outs), (ins GPR:$a, brtarget:$offset),
    327                   !strconcat(instr_asm, "   $a, $offset"),
    328                   [], IIC_BRc> {
    329   let rd = br;
    330   let Form = FCRI;
    331 }
    332 
    333 //===----------------------------------------------------------------------===//
    334 // MBlaze arithmetic instructions
    335 //===----------------------------------------------------------------------===//
    336 
    337 let isCommutable = 1, isAsCheapAsAMove = 1 in {
    338   def ADDK   :  Arith<0x04, 0x000, "addk   ", add,  IIC_ALU>;
    339   def AND    :  Logic<0x21, 0x000, "and    ", and>;
    340   def OR     :  Logic<0x20, 0x000, "or     ", or>;
    341   def XOR    :  Logic<0x22, 0x000, "xor    ", xor>;
    342 
    343   let Predicates=[HasPatCmp] in {
    344     def PCMPBF : PatCmp<0x20, 0x400, "pcmpbf ">;
    345     def PCMPEQ : PatCmp<0x22, 0x400, "pcmpeq ">;
    346     def PCMPNE : PatCmp<0x23, 0x400, "pcmpne ">;
    347   }
    348 
    349   let Defs = [CARRY] in {
    350     def ADD    :  Arith<0x00, 0x000, "add    ", addc, IIC_ALU>;
    351 
    352     let Uses = [CARRY] in {
    353       def ADDC   :  Arith<0x02, 0x000, "addc   ", adde, IIC_ALU>;
    354     }
    355   }
    356 
    357   let Uses = [CARRY] in {
    358     def ADDKC  : ArithN<0x06, 0x000, "addkc  ", IIC_ALU>;
    359   }
    360 }
    361 
    362 let isAsCheapAsAMove = 1 in {
    363   def ANDN   :  ArithN<0x23, 0x000, "andn   ", IIC_ALU>;
    364   def CMP    :  ArithN<0x05, 0x001, "cmp    ", IIC_ALU>;
    365   def CMPU   :  ArithN<0x05, 0x003, "cmpu   ", IIC_ALU>;
    366   def RSUBK  :  ArithR<0x05, 0x000, "rsubk  ", sub,  IIC_ALU>;
    367 
    368   let Defs = [CARRY] in {
    369     def RSUB   :  ArithR<0x01, 0x000, "rsub   ", subc, IIC_ALU>;
    370 
    371     let Uses = [CARRY] in {
    372       def RSUBC  :  ArithR<0x03, 0x000, "rsubc  ", sube, IIC_ALU>;
    373     }
    374   }
    375 
    376   let Uses = [CARRY] in {
    377     def RSUBKC : ArithRN<0x07, 0x000, "rsubkc ", IIC_ALU>;
    378   }
    379 }
    380 
    381 let isCommutable = 1, Predicates=[HasMul] in {
    382   def MUL    : Arith<0x10, 0x000, "mul    ", mul,   IIC_ALUm>;
    383 }
    384 
    385 let isCommutable = 1, Predicates=[HasMul,HasMul64] in {
    386   def MULH   : Arith<0x10, 0x001, "mulh   ", mulhs, IIC_ALUm>;
    387   def MULHU  : Arith<0x10, 0x003, "mulhu  ", mulhu, IIC_ALUm>;
    388 }
    389 
    390 let Predicates=[HasMul,HasMul64] in {
    391   def MULHSU : ArithN<0x10, 0x002, "mulhsu ", IIC_ALUm>;
    392 }
    393 
    394 let Predicates=[HasBarrel] in {
    395   def BSRL   :   Arith<0x11, 0x000, "bsrl   ", srl, IIC_SHT>;
    396   def BSRA   :   Arith<0x11, 0x200, "bsra   ", sra, IIC_SHT>;
    397   def BSLL   :   Arith<0x11, 0x400, "bsll   ", shl, IIC_SHT>;
    398   def BSRLI  :  ShiftI<0x19, 0x0, "bsrli  ", srl, uimm5, immZExt5>;
    399   def BSRAI  :  ShiftI<0x19, 0x1, "bsrai  ", sra, uimm5, immZExt5>;
    400   def BSLLI  :  ShiftI<0x19, 0x2, "bslli  ", shl, uimm5, immZExt5>;
    401 }
    402 
    403 let Predicates=[HasDiv] in {
    404   def IDIV   :  ArithR<0x12, 0x000, "idiv   ", sdiv, IIC_ALUd>;
    405   def IDIVU  :  ArithR<0x12, 0x002, "idivu  ", udiv, IIC_ALUd>;
    406 }
    407 
    408 //===----------------------------------------------------------------------===//
    409 // MBlaze immediate mode arithmetic instructions
    410 //===----------------------------------------------------------------------===//
    411 
    412 let isAsCheapAsAMove = 1 in {
    413   def ADDIK   :   ArithI<0x0C, "addik  ", add,  simm16, immSExt16>;
    414   def RSUBIK  :  ArithRI<0x0D, "rsubik ", sub, simm16, immSExt16>;
    415   def ANDNI   :  ArithNI<0x2B, "andni  ", uimm16, immZExt16>;
    416   def ANDI    :   LogicI<0x29, "andi   ", and>;
    417   def ORI     :   LogicI<0x28, "ori    ", or>;
    418   def XORI    :   LogicI<0x2A, "xori   ", xor>;
    419 
    420   let Defs = [CARRY] in {
    421     def ADDI    :   ArithI<0x08, "addi   ", addc, simm16, immSExt16>;
    422     def RSUBI   :  ArithRI<0x09, "rsubi  ", subc,  simm16, immSExt16>;
    423 
    424     let Uses = [CARRY] in {
    425       def ADDIC   :   ArithI<0x0A, "addic  ", adde, simm16, immSExt16>;
    426       def RSUBIC  :  ArithRI<0x0B, "rsubic ", sube, simm16, immSExt16>;
    427     }
    428   }
    429 
    430   let Uses = [CARRY] in {
    431     def ADDIKC  :  ArithNI<0x0E, "addikc ", simm16, immSExt16>;
    432     def RSUBIKC : ArithRNI<0x0F, "rsubikc", simm16, immSExt16>;
    433   }
    434 }
    435 
    436 let Predicates=[HasMul] in {
    437   def MULI    :   ArithI<0x18, "muli   ", mul, simm16, immSExt16>;
    438 }
    439 
    440 //===----------------------------------------------------------------------===//
    441 // MBlaze memory access instructions
    442 //===----------------------------------------------------------------------===//
    443 
    444 let canFoldAsLoad = 1, isReMaterializable = 1 in {
    445   let neverHasSideEffects = 1 in {
    446     def LBU  :  LoadM<0x30, 0x000, "lbu    ">;
    447     def LBUR :  LoadM<0x30, 0x200, "lbur   ">;
    448 
    449     def LHU  :  LoadM<0x31, 0x000, "lhu    ">;
    450     def LHUR :  LoadM<0x31, 0x200, "lhur   ">;
    451 
    452     def LW   :  LoadM<0x32, 0x000, "lw     ">;
    453     def LWR  :  LoadM<0x32, 0x200, "lwr    ">;
    454 
    455     let Defs = [CARRY] in {
    456       def LWX  :  LoadM<0x32, 0x400, "lwx    ">;
    457     }
    458   }
    459 
    460   def LBUI : LoadMI<0x38, "lbui   ", zextloadi8>;
    461   def LHUI : LoadMI<0x39, "lhui   ", zextloadi16>;
    462   def LWI  : LoadMI<0x3A, "lwi    ", load>;
    463 }
    464 
    465 def SB  :  StoreM<0x34, 0x000, "sb     ">;
    466 def SBR :  StoreM<0x34, 0x200, "sbr    ">;
    467 
    468 def SH  :  StoreM<0x35, 0x000, "sh     ">;
    469 def SHR :  StoreM<0x35, 0x200, "shr    ">;
    470 
    471 def SW  :  StoreM<0x36, 0x000, "sw     ">;
    472 def SWR :  StoreM<0x36, 0x200, "swr    ">;
    473 
    474 let Defs = [CARRY] in {
    475   def SWX :  StoreM<0x36, 0x400, "swx    ">;
    476 }
    477 
    478 def SBI : StoreMI<0x3C, "sbi    ", truncstorei8>;
    479 def SHI : StoreMI<0x3D, "shi    ", truncstorei16>;
    480 def SWI : StoreMI<0x3E, "swi    ", store>;
    481 
    482 //===----------------------------------------------------------------------===//
    483 // MBlaze branch instructions
    484 //===----------------------------------------------------------------------===//
    485 
    486 let isBranch = 1, isTerminator = 1, hasCtrlDep = 1, isBarrier = 1 in {
    487   def BRI    :  BranchI<0x2E, 0x00, "bri    ">;
    488   def BRAI   :  BranchI<0x2E, 0x08, "brai   ">;
    489 }
    490 
    491 let isBranch = 1, isTerminator = 1, hasCtrlDep = 1 in {
    492   def BEQI   : BranchCI<0x2F, 0x00, "beqi   ">;
    493   def BNEI   : BranchCI<0x2F, 0x01, "bnei   ">;
    494   def BLTI   : BranchCI<0x2F, 0x02, "blti   ">;
    495   def BLEI   : BranchCI<0x2F, 0x03, "blei   ">;
    496   def BGTI   : BranchCI<0x2F, 0x04, "bgti   ">;
    497   def BGEI   : BranchCI<0x2F, 0x05, "bgei   ">;
    498 }
    499 
    500 let isBranch = 1, isIndirectBranch = 1, isTerminator = 1, hasCtrlDep = 1,
    501     isBarrier = 1 in {
    502   def BR     :   Branch<0x26, 0x00, 0x000, "br     ">;
    503   def BRA    :   Branch<0x26, 0x08, 0x000, "bra    ">;
    504 }
    505 
    506 let isBranch = 1, isIndirectBranch = 1, isTerminator = 1, hasCtrlDep = 1 in {
    507   def BEQ    :  BranchC<0x27, 0x00, 0x000, "beq    ">;
    508   def BNE    :  BranchC<0x27, 0x01, 0x000, "bne    ">;
    509   def BLT    :  BranchC<0x27, 0x02, 0x000, "blt    ">;
    510   def BLE    :  BranchC<0x27, 0x03, 0x000, "ble    ">;
    511   def BGT    :  BranchC<0x27, 0x04, 0x000, "bgt    ">;
    512   def BGE    :  BranchC<0x27, 0x05, 0x000, "bge    ">;
    513 }
    514 
    515 let isBranch = 1, isTerminator = 1, hasDelaySlot = 1, hasCtrlDep = 1,
    516     isBarrier = 1 in {
    517   def BRID   :  BranchI<0x2E, 0x10, "brid   ">;
    518   def BRAID  :  BranchI<0x2E, 0x18, "braid  ">;
    519 }
    520 
    521 let isBranch = 1, isTerminator = 1, hasDelaySlot = 1, hasCtrlDep = 1 in {
    522   def BEQID  : BranchCI<0x2F, 0x10, "beqid  ">;
    523   def BNEID  : BranchCI<0x2F, 0x11, "bneid  ">;
    524   def BLTID  : BranchCI<0x2F, 0x12, "bltid  ">;
    525   def BLEID  : BranchCI<0x2F, 0x13, "bleid  ">;
    526   def BGTID  : BranchCI<0x2F, 0x14, "bgtid  ">;
    527   def BGEID  : BranchCI<0x2F, 0x15, "bgeid  ">;
    528 }
    529 
    530 let isBranch = 1, isIndirectBranch = 1, isTerminator = 1,
    531     hasDelaySlot = 1, hasCtrlDep = 1, isBarrier = 1 in {
    532   def BRD    :   Branch<0x26, 0x10, 0x000, "brd    ">;
    533   def BRAD   :   Branch<0x26, 0x18, 0x000, "brad   ">;
    534 }
    535 
    536 let isBranch = 1, isIndirectBranch = 1, isTerminator = 1,
    537     hasDelaySlot = 1, hasCtrlDep = 1 in {
    538   def BEQD   :  BranchC<0x27, 0x10, 0x000, "beqd   ">;
    539   def BNED   :  BranchC<0x27, 0x11, 0x000, "bned   ">;
    540   def BLTD   :  BranchC<0x27, 0x12, 0x000, "bltd   ">;
    541   def BLED   :  BranchC<0x27, 0x13, 0x000, "bled   ">;
    542   def BGTD   :  BranchC<0x27, 0x14, 0x000, "bgtd   ">;
    543   def BGED   :  BranchC<0x27, 0x15, 0x000, "bged   ">;
    544 }
    545 
    546 let isCall =1, hasDelaySlot = 1,
    547     Defs = [R3,R4,R5,R6,R7,R8,R9,R10,R11,R12,CARRY],
    548     Uses = [R1] in {
    549   def BRLID  : BranchLI<0x2E, 0x14, "brlid  ">;
    550   def BRALID : BranchLI<0x2E, 0x1C, "bralid ">;
    551 }
    552 
    553 let isCall = 1, hasDelaySlot = 1,
    554     Defs = [R3,R4,R5,R6,R7,R8,R9,R10,R11,R12,CARRY],
    555     Uses = [R1] in {
    556   def BRLD   : BranchL<0x26, 0x14, 0x000, "brld   ">;
    557   def BRALD  : BranchL<0x26, 0x1C, 0x000, "brald  ">;
    558 }
    559 
    560 let isReturn=1, isTerminator=1, hasDelaySlot=1, isBarrier=1,
    561     rd=0x10, Form=FCRI in {
    562   def RTSD   : TB<0x2D, (outs), (ins GPR:$target, simm16:$imm),
    563                   "rtsd      $target, $imm",
    564                   [],
    565                   IIC_BR>;
    566 }
    567 
    568 let isReturn=1, isTerminator=1, hasDelaySlot=1, isBarrier=1,
    569     rd=0x11, Form=FCRI in {
    570   def RTID   : TB<0x2D, (outs), (ins GPR:$target, simm16:$imm),
    571                   "rtid      $target, $imm",
    572                   [],
    573                   IIC_BR>;
    574 }
    575 
    576 let isReturn=1, isTerminator=1, hasDelaySlot=1, isBarrier=1,
    577     rd=0x12, Form=FCRI in {
    578   def RTBD   : TB<0x2D, (outs), (ins GPR:$target, simm16:$imm),
    579                   "rtbd      $target, $imm",
    580                   [],
    581                   IIC_BR>;
    582 }
    583 
    584 let isReturn=1, isTerminator=1, hasDelaySlot=1, isBarrier=1,
    585     rd=0x14, Form=FCRI in {
    586   def RTED   : TB<0x2D, (outs), (ins GPR:$target, simm16:$imm),
    587                   "rted      $target, $imm",
    588                   [],
    589                   IIC_BR>;
    590 }
    591 
    592 //===----------------------------------------------------------------------===//
    593 // MBlaze misc instructions
    594 //===----------------------------------------------------------------------===//
    595 
    596 let neverHasSideEffects = 1 in {
    597   def NOP :  MBlazeInst< 0x20, FC, (outs), (ins), "nop    ", [], IIC_ALU>;
    598 }
    599 
    600 let usesCustomInserter = 1 in {
    601   def Select_CC : MBlazePseudo<(outs GPR:$dst),
    602     (ins GPR:$T, GPR:$F, GPR:$CMP, i32imm:$CC), // F T reversed
    603     "; SELECT_CC PSEUDO!",
    604     []>;
    605 
    606   def ShiftL : MBlazePseudo<(outs GPR:$dst),
    607     (ins GPR:$L, GPR:$R),
    608     "; ShiftL PSEUDO!",
    609     []>;
    610 
    611   def ShiftRA : MBlazePseudo<(outs GPR:$dst),
    612     (ins GPR:$L, GPR:$R),
    613     "; ShiftRA PSEUDO!",
    614     []>;
    615 
    616   def ShiftRL : MBlazePseudo<(outs GPR:$dst),
    617     (ins GPR:$L, GPR:$R),
    618     "; ShiftRL PSEUDO!",
    619     []>;
    620 }
    621 
    622 let rb = 0 in {
    623   def SEXT16 : TA<0x24, 0x061, (outs GPR:$dst), (ins GPR:$src),
    624                   "sext16    $dst, $src", [], IIC_ALU>;
    625   def SEXT8  : TA<0x24, 0x060, (outs GPR:$dst), (ins GPR:$src),
    626                   "sext8     $dst, $src", [], IIC_ALU>;
    627   let Defs = [CARRY] in {
    628     def SRL    : TA<0x24, 0x041, (outs GPR:$dst), (ins GPR:$src),
    629                     "srl       $dst, $src", [], IIC_ALU>;
    630     def SRA    : TA<0x24, 0x001, (outs GPR:$dst), (ins GPR:$src),
    631                     "sra       $dst, $src", [], IIC_ALU>;
    632     let Uses = [CARRY] in {
    633       def SRC    : TA<0x24, 0x021, (outs GPR:$dst), (ins GPR:$src),
    634                       "src       $dst, $src", [], IIC_ALU>;
    635     }
    636   }
    637 }
    638 
    639 let isCodeGenOnly=1 in {
    640   def ADDIK32 : ArithI32<0x08, "addik  ", simm16, immSExt16>;
    641   def ORI32   : LogicI32<0x28, "ori    ">;
    642   def BRLID32 : BranchLI<0x2E, 0x14, "brlid  ">;
    643 }
    644 
    645 //===----------------------------------------------------------------------===//
    646 // Misc. instructions
    647 //===----------------------------------------------------------------------===//
    648 let Form=FRCS in {
    649   def MFS : SPC<0x25, 0x2, (outs GPR:$dst), (ins SPR:$src),
    650                 "mfs       $dst, $src", [], IIC_ALU>;
    651 }
    652 
    653 let Form=FCRCS in {
    654   def MTS : SPC<0x25, 0x3, (outs SPR:$dst), (ins GPR:$src),
    655                 "mts       $dst, $src", [], IIC_ALU>;
    656 }
    657 
    658 def MSRSET : MSR<0x25, 0x20, (outs GPR:$dst), (ins uimm15:$set),
    659                  "msrset    $dst, $set", [], IIC_ALU>;
    660 
    661 def MSRCLR : MSR<0x25, 0x22, (outs GPR:$dst), (ins uimm15:$clr),
    662                  "msrclr    $dst, $clr", [], IIC_ALU>;
    663 
    664 let rd=0x0, Form=FCRR in {
    665   def WDC  : TA<0x24, 0x64, (outs), (ins GPR:$a, GPR:$b),
    666                 "wdc       $a, $b", [], IIC_WDC>;
    667   def WDCF : TA<0x24, 0x74, (outs), (ins GPR:$a, GPR:$b),
    668                 "wdc.flush $a, $b", [], IIC_WDC>;
    669   def WDCC : TA<0x24, 0x66, (outs), (ins GPR:$a, GPR:$b),
    670                 "wdc.clear $a, $b", [], IIC_WDC>;
    671   def WIC  : TA<0x24, 0x68, (outs), (ins GPR:$a, GPR:$b),
    672                 "wic       $a, $b", [], IIC_WDC>;
    673 }
    674 
    675 def BRK  :  BranchL<0x26, 0x0C, 0x000, "brk    ">;
    676 def BRKI : BranchLI<0x2E, 0x0C, "brki   ">;
    677 
    678 def IMM : MBlazeInst<0x2C, FCCI, (outs), (ins simm16:$imm),
    679                      "imm       $imm", [], IIC_ALU>;
    680 
    681 //===----------------------------------------------------------------------===//
    682 // Pseudo instructions for atomic operations
    683 //===----------------------------------------------------------------------===//
    684 let usesCustomInserter=1 in {
    685   def CAS32 : MBlazePseudo<(outs GPR:$dst), (ins GPR:$ptr, GPR:$cmp, GPR:$swp),
    686     "# atomic compare and swap",
    687     [(set GPR:$dst, (atomic_cmp_swap_32 GPR:$ptr, GPR:$cmp, GPR:$swp))]>;
    688 
    689   def SWP32 : MBlazePseudo<(outs GPR:$dst), (ins GPR:$ptr, GPR:$swp),
    690     "# atomic swap",
    691     [(set GPR:$dst, (atomic_swap_32 GPR:$ptr, GPR:$swp))]>;
    692 
    693   def LAA32 : MBlazePseudo<(outs GPR:$dst), (ins GPR:$ptr, GPR:$val),
    694     "# atomic load and add",
    695     [(set GPR:$dst, (atomic_load_add_32 GPR:$ptr, GPR:$val))]>;
    696 
    697   def LAS32 : MBlazePseudo<(outs GPR:$dst), (ins GPR:$ptr, GPR:$val),
    698     "# atomic load and sub",
    699     [(set GPR:$dst, (atomic_load_sub_32 GPR:$ptr, GPR:$val))]>;
    700 
    701   def LAD32 : MBlazePseudo<(outs GPR:$dst), (ins GPR:$ptr, GPR:$val),
    702     "# atomic load and and",
    703     [(set GPR:$dst, (atomic_load_and_32 GPR:$ptr, GPR:$val))]>;
    704 
    705   def LAO32 : MBlazePseudo<(outs GPR:$dst), (ins GPR:$ptr, GPR:$val),
    706     "# atomic load and or",
    707     [(set GPR:$dst, (atomic_load_or_32 GPR:$ptr, GPR:$val))]>;
    708 
    709   def LAX32 : MBlazePseudo<(outs GPR:$dst), (ins GPR:$ptr, GPR:$val),
    710     "# atomic load and xor",
    711     [(set GPR:$dst, (atomic_load_xor_32 GPR:$ptr, GPR:$val))]>;
    712 
    713   def LAN32 : MBlazePseudo<(outs GPR:$dst), (ins GPR:$ptr, GPR:$val),
    714     "# atomic load and nand",
    715     [(set GPR:$dst, (atomic_load_nand_32 GPR:$ptr, GPR:$val))]>;
    716 
    717   def MEMBARRIER : MBlazePseudo<(outs), (ins),
    718     "# memory barrier",
    719     [(membarrier (i32 imm), (i32 imm), (i32 imm), (i32 imm), (i32 imm))]>;
    720 }
    721 
    722 //===----------------------------------------------------------------------===//
    723 //  Arbitrary patterns that map to one or more instructions
    724 //===----------------------------------------------------------------------===//
    725 
    726 // Small immediates
    727 def : Pat<(i32 0), (ADDK (i32 R0), (i32 R0))>;
    728 def : Pat<(i32 immSExt16:$imm), (ADDIK (i32 R0), imm:$imm)>;
    729 def : Pat<(i32 immZExt16:$imm), (ORI (i32 R0), imm:$imm)>;
    730 
    731 // Arbitrary immediates
    732 def : Pat<(i32 imm:$imm), (ADDIK (i32 R0), imm:$imm)>;
    733 
    734 // In register sign extension
    735 def : Pat<(sext_inreg GPR:$src, i16), (SEXT16 GPR:$src)>;
    736 def : Pat<(sext_inreg GPR:$src, i8),  (SEXT8 GPR:$src)>;
    737 
    738 // Call
    739 def : Pat<(MBlazeJmpLink (i32 tglobaladdr:$dst)),
    740           (BRLID (i32 R15), tglobaladdr:$dst)>;
    741 
    742 def : Pat<(MBlazeJmpLink (i32 texternalsym:$dst)),
    743           (BRLID (i32 R15), texternalsym:$dst)>;
    744 
    745 def : Pat<(MBlazeJmpLink GPR:$dst),
    746           (BRALD (i32 R15), GPR:$dst)>;
    747 
    748 // Shift Instructions
    749 def : Pat<(shl GPR:$L, GPR:$R), (ShiftL GPR:$L, GPR:$R)>;
    750 def : Pat<(sra GPR:$L, GPR:$R), (ShiftRA GPR:$L, GPR:$R)>;
    751 def : Pat<(srl GPR:$L, GPR:$R), (ShiftRL GPR:$L, GPR:$R)>;
    752 
    753 // SET_CC operations
    754 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETEQ),
    755           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
    756                      (CMP GPR:$R, GPR:$L), 1)>;
    757 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETNE),
    758           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
    759                      (CMP GPR:$R, GPR:$L), 2)>;
    760 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETGT),
    761           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
    762                      (CMP GPR:$R, GPR:$L), 3)>;
    763 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETLT),
    764           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
    765                      (CMP GPR:$R, GPR:$L), 4)>;
    766 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETGE),
    767           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
    768                      (CMP GPR:$R, GPR:$L), 5)>;
    769 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETLE),
    770           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
    771                      (CMP GPR:$R, GPR:$L), 6)>;
    772 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETUGT),
    773           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
    774                      (CMPU GPR:$R, GPR:$L), 3)>;
    775 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETULT),
    776           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
    777                      (CMPU GPR:$R, GPR:$L), 4)>;
    778 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETUGE),
    779           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
    780                      (CMPU GPR:$R, GPR:$L), 5)>;
    781 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETULE),
    782           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
    783                      (CMPU GPR:$R, GPR:$L), 6)>;
    784 
    785 // SELECT operations
    786 def : Pat<(select (i32 GPR:$C), (i32 GPR:$T), (i32 GPR:$F)),
    787           (Select_CC GPR:$T, GPR:$F, GPR:$C, 2)>;
    788 
    789 // SELECT_CC
    790 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
    791                     (i32 GPR:$T), (i32 GPR:$F), SETEQ),
    792           (Select_CC GPR:$T, GPR:$F, (CMP GPR:$R, GPR:$L), 1)>;
    793 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
    794                     (i32 GPR:$T), (i32 GPR:$F), SETNE),
    795           (Select_CC GPR:$T, GPR:$F, (CMP GPR:$R, GPR:$L), 2)>;
    796 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
    797                     (i32 GPR:$T), (i32 GPR:$F), SETGT),
    798           (Select_CC GPR:$T, GPR:$F, (CMP GPR:$R, GPR:$L), 3)>;
    799 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
    800                     (i32 GPR:$T), (i32 GPR:$F), SETLT),
    801           (Select_CC GPR:$T, GPR:$F, (CMP GPR:$R, GPR:$L), 4)>;
    802 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
    803                     (i32 GPR:$T), (i32 GPR:$F), SETGE),
    804           (Select_CC GPR:$T, GPR:$F, (CMP GPR:$R, GPR:$L), 5)>;
    805 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
    806                     (i32 GPR:$T), (i32 GPR:$F), SETLE),
    807           (Select_CC GPR:$T, GPR:$F, (CMP GPR:$R, GPR:$L), 6)>;
    808 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
    809                     (i32 GPR:$T), (i32 GPR:$F), SETUGT),
    810           (Select_CC GPR:$T, GPR:$F, (CMPU GPR:$R, GPR:$L), 3)>;
    811 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
    812                     (i32 GPR:$T), (i32 GPR:$F), SETULT),
    813           (Select_CC GPR:$T, GPR:$F, (CMPU GPR:$R, GPR:$L), 4)>;
    814 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
    815                     (i32 GPR:$T), (i32 GPR:$F), SETUGE),
    816           (Select_CC GPR:$T, GPR:$F, (CMPU GPR:$R, GPR:$L), 5)>;
    817 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
    818                     (i32 GPR:$T), (i32 GPR:$F), SETULE),
    819           (Select_CC GPR:$T, GPR:$F, (CMPU GPR:$R, GPR:$L), 6)>;
    820 
    821 // Ret instructions
    822 def : Pat<(MBlazeRet GPR:$target), (RTSD GPR:$target, 0x8)>;
    823 def : Pat<(MBlazeIRet GPR:$target), (RTID GPR:$target, 0x0)>;
    824 
    825 // BR instructions
    826 def : Pat<(br bb:$T), (BRID bb:$T)>;
    827 def : Pat<(brind GPR:$T), (BRAD GPR:$T)>;
    828 
    829 // BRCOND instructions
    830 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETEQ), bb:$T),
    831           (BEQID (CMP GPR:$R, GPR:$L), bb:$T)>;
    832 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETNE), bb:$T),
    833           (BNEID (CMP GPR:$R, GPR:$L), bb:$T)>;
    834 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETGT), bb:$T),
    835           (BGTID (CMP GPR:$R, GPR:$L), bb:$T)>;
    836 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETLT), bb:$T),
    837           (BLTID (CMP GPR:$R, GPR:$L), bb:$T)>;
    838 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETGE), bb:$T),
    839           (BGEID (CMP GPR:$R, GPR:$L), bb:$T)>;
    840 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETLE), bb:$T),
    841           (BLEID (CMP GPR:$R, GPR:$L), bb:$T)>;
    842 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETUGT), bb:$T),
    843           (BGTID (CMPU GPR:$R, GPR:$L), bb:$T)>;
    844 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETULT), bb:$T),
    845           (BLTID (CMPU GPR:$R, GPR:$L), bb:$T)>;
    846 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETUGE), bb:$T),
    847           (BGEID (CMPU GPR:$R, GPR:$L), bb:$T)>;
    848 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETULE), bb:$T),
    849           (BLEID (CMPU GPR:$R, GPR:$L), bb:$T)>;
    850 def : Pat<(brcond (i32 GPR:$C), bb:$T),
    851           (BNEID GPR:$C, bb:$T)>;
    852 
    853 // Jump tables, global addresses, and constant pools
    854 def : Pat<(MBWrapper tglobaladdr:$in), (ORI (i32 R0), tglobaladdr:$in)>;
    855 def : Pat<(MBWrapper tjumptable:$in),  (ORI (i32 R0), tjumptable:$in)>;
    856 def : Pat<(MBWrapper tconstpool:$in),  (ORI (i32 R0), tconstpool:$in)>;
    857 
    858 // Misc instructions
    859 def : Pat<(and (i32 GPR:$lh), (not (i32 GPR:$rh))),(ANDN GPR:$lh, GPR:$rh)>;
    860 
    861 // Convert any extend loads into zero extend loads
    862 def : Pat<(extloadi8  iaddr:$src), (i32 (LBUI iaddr:$src))>;
    863 def : Pat<(extloadi16 iaddr:$src), (i32 (LHUI iaddr:$src))>;
    864 def : Pat<(extloadi8  xaddr:$src), (i32 (LBU xaddr:$src))>;
    865 def : Pat<(extloadi16 xaddr:$src), (i32 (LHU xaddr:$src))>;
    866 
    867 // 32-bit load and store
    868 def : Pat<(store (i32 GPR:$dst), xaddr:$addr), (SW GPR:$dst, xaddr:$addr)>;
    869 def : Pat<(load xaddr:$addr), (i32 (LW xaddr:$addr))>;
    870 
    871 // 16-bit load and store
    872 def : Pat<(truncstorei16 (i32 GPR:$dst), xaddr:$addr), (SH GPR:$dst, xaddr:$addr)>;
    873 def : Pat<(zextloadi16 xaddr:$addr), (i32 (LHU xaddr:$addr))>;
    874 
    875 // 8-bit load and store
    876 def : Pat<(truncstorei8 (i32 GPR:$dst), xaddr:$addr), (SB GPR:$dst, xaddr:$addr)>;
    877 def : Pat<(zextloadi8 xaddr:$addr), (i32 (LBU xaddr:$addr))>;
    878 
    879 // Peepholes
    880 def : Pat<(store (i32 0), iaddr:$dst), (SWI (i32 R0), iaddr:$dst)>;
    881 
    882 // Atomic fence
    883 def : Pat<(atomic_fence (imm), (imm)), (MEMBARRIER)>;
    884 
    885 //===----------------------------------------------------------------------===//
    886 // Floating Point Support
    887 //===----------------------------------------------------------------------===//
    888 include "MBlazeInstrFSL.td"
    889 include "MBlazeInstrFPU.td"
    890