Home | History | Annotate | Download | only in XCore
      1 //===-- XCoreInstrInfo.td - Target Description for XCore ---*- tablegen -*-===//
      2 //
      3 //                     The LLVM Compiler Infrastructure
      4 //
      5 // This file is distributed under the University of Illinois Open Source
      6 // License. See LICENSE.TXT for details.
      7 //
      8 //===----------------------------------------------------------------------===//
      9 //
     10 // This file describes the XCore instructions in TableGen format.
     11 //
     12 //===----------------------------------------------------------------------===//
     13 
     14 // Uses of CP, DP are not currently reflected in the patterns, since
     15 // having a physical register as an operand prevents loop hoisting and
     16 // since the value of these registers never changes during the life of the
     17 // function.
     18 
     19 //===----------------------------------------------------------------------===//
     20 // Instruction format superclass.
     21 //===----------------------------------------------------------------------===//
     22 
     23 include "XCoreInstrFormats.td"
     24 
     25 //===----------------------------------------------------------------------===//
     26 // XCore specific DAG Nodes.
     27 //
     28 
     29 // Call
     30 def SDT_XCoreBranchLink : SDTypeProfile<0, 1, [SDTCisPtrTy<0>]>;
     31 def XCoreBranchLink     : SDNode<"XCoreISD::BL",SDT_XCoreBranchLink,
     32                             [SDNPHasChain, SDNPOptInGlue, SDNPOutGlue,
     33                              SDNPVariadic]>;
     34 
     35 def XCoreRetsp : SDNode<"XCoreISD::RETSP", SDTBrind,
     36                       [SDNPHasChain, SDNPOptInGlue, SDNPMayLoad, SDNPVariadic]>;
     37 
     38 def SDT_XCoreEhRet : SDTypeProfile<0, 2,
     39                             [SDTCisSameAs<0, 1>, SDTCisPtrTy<0>]>;
     40 def XCoreEhRet       : SDNode<"XCoreISD::EH_RETURN", SDT_XCoreEhRet,
     41                          [SDNPHasChain, SDNPOptInGlue]>;
     42 
     43 def SDT_XCoreBR_JT    : SDTypeProfile<0, 2,
     44                                       [SDTCisVT<0, i32>, SDTCisVT<1, i32>]>;
     45 
     46 def XCoreBR_JT : SDNode<"XCoreISD::BR_JT", SDT_XCoreBR_JT,
     47                         [SDNPHasChain]>;
     48 
     49 def XCoreBR_JT32 : SDNode<"XCoreISD::BR_JT32", SDT_XCoreBR_JT,
     50                         [SDNPHasChain]>;
     51 
     52 def SDT_XCoreAddress    : SDTypeProfile<1, 1,
     53                             [SDTCisSameAs<0, 1>, SDTCisPtrTy<0>]>;
     54 
     55 def pcrelwrapper : SDNode<"XCoreISD::PCRelativeWrapper", SDT_XCoreAddress,
     56                            []>;
     57 
     58 def dprelwrapper : SDNode<"XCoreISD::DPRelativeWrapper", SDT_XCoreAddress,
     59                            []>;
     60 
     61 def cprelwrapper : SDNode<"XCoreISD::CPRelativeWrapper", SDT_XCoreAddress,
     62                            []>;
     63 
     64 def frametoargsoffset : SDNode<"XCoreISD::FRAME_TO_ARGS_OFFSET", SDTIntLeaf,
     65                                []>;
     66 
     67 def SDT_XCoreStwsp    : SDTypeProfile<0, 2, [SDTCisInt<1>]>;
     68 def XCoreStwsp        : SDNode<"XCoreISD::STWSP", SDT_XCoreStwsp,
     69                                [SDNPHasChain, SDNPMayStore]>;
     70 
     71 def SDT_XCoreLdwsp    : SDTypeProfile<1, 1, [SDTCisInt<1>]>;
     72 def XCoreLdwsp        : SDNode<"XCoreISD::LDWSP", SDT_XCoreLdwsp,
     73                                [SDNPHasChain, SDNPMayLoad]>;
     74 
     75 // These are target-independent nodes, but have target-specific formats.
     76 def SDT_XCoreCallSeqStart : SDCallSeqStart<[ SDTCisVT<0, i32> ]>;
     77 def SDT_XCoreCallSeqEnd   : SDCallSeqEnd<[ SDTCisVT<0, i32>,
     78                                         SDTCisVT<1, i32> ]>;
     79 
     80 def callseq_start : SDNode<"ISD::CALLSEQ_START", SDT_XCoreCallSeqStart,
     81                            [SDNPHasChain, SDNPOutGlue]>;
     82 def callseq_end   : SDNode<"ISD::CALLSEQ_END",   SDT_XCoreCallSeqEnd,
     83                            [SDNPHasChain, SDNPOptInGlue, SDNPOutGlue]>;
     84 
     85 def SDT_XCoreMEMBARRIER : SDTypeProfile<0, 0, []>;
     86 
     87 def XCoreMemBarrier : SDNode<"XCoreISD::MEMBARRIER", SDT_XCoreMEMBARRIER,
     88                              [SDNPHasChain]>;
     89 
     90 //===----------------------------------------------------------------------===//
     91 // Instruction Pattern Stuff
     92 //===----------------------------------------------------------------------===//
     93 
     94 def div4_xform : SDNodeXForm<imm, [{
     95   // Transformation function: imm/4
     96   assert(N->getZExtValue() % 4 == 0);
     97   return getI32Imm(N->getZExtValue()/4, SDLoc(N));
     98 }]>;
     99 
    100 def msksize_xform : SDNodeXForm<imm, [{
    101   // Transformation function: get the size of a mask
    102   assert(isMask_32(N->getZExtValue()));
    103   // look for the first non-zero bit
    104   return getI32Imm(32 - countLeadingZeros((uint32_t)N->getZExtValue()),
    105                    SDLoc(N));
    106 }]>;
    107 
    108 def neg_xform : SDNodeXForm<imm, [{
    109   // Transformation function: -imm
    110   uint32_t value = N->getZExtValue();
    111   return getI32Imm(-value, SDLoc(N));
    112 }]>;
    113 
    114 def bpwsub_xform : SDNodeXForm<imm, [{
    115   // Transformation function: 32-imm
    116   uint32_t value = N->getZExtValue();
    117   return getI32Imm(32 - value, SDLoc(N));
    118 }]>;
    119 
    120 def div4neg_xform : SDNodeXForm<imm, [{
    121   // Transformation function: -imm/4
    122   uint32_t value = N->getZExtValue();
    123   assert(-value % 4 == 0);
    124   return getI32Imm(-value/4, SDLoc(N));
    125 }]>;
    126 
    127 def immUs4Neg : PatLeaf<(imm), [{
    128   uint32_t value = (uint32_t)N->getZExtValue();
    129   return (-value)%4 == 0 && (-value)/4 <= 11;
    130 }]>;
    131 
    132 def immUs4 : PatLeaf<(imm), [{
    133   uint32_t value = (uint32_t)N->getZExtValue();
    134   return value%4 == 0 && value/4 <= 11;
    135 }]>;
    136 
    137 def immUsNeg : PatLeaf<(imm), [{
    138   return -((uint32_t)N->getZExtValue()) <= 11;
    139 }]>;
    140 
    141 def immUs : PatLeaf<(imm), [{
    142   return (uint32_t)N->getZExtValue() <= 11;
    143 }]>;
    144 
    145 def immU6 : PatLeaf<(imm), [{
    146   return (uint32_t)N->getZExtValue() < (1 << 6);
    147 }]>;
    148 
    149 def immU10 : PatLeaf<(imm), [{
    150   return (uint32_t)N->getZExtValue() < (1 << 10);
    151 }]>;
    152 
    153 def immU16 : PatLeaf<(imm), [{
    154   return (uint32_t)N->getZExtValue() < (1 << 16);
    155 }]>;
    156 
    157 def immU20 : PatLeaf<(imm), [{
    158   return (uint32_t)N->getZExtValue() < (1 << 20);
    159 }]>;
    160 
    161 def immMskBitp : PatLeaf<(imm), [{ return immMskBitp(N); }]>;
    162 
    163 def immBitp : PatLeaf<(imm), [{
    164   uint32_t value = (uint32_t)N->getZExtValue();
    165   return (value >= 1 && value <= 8)
    166           || value == 16
    167           || value == 24
    168           || value == 32;
    169 }]>;
    170 
    171 def immBpwSubBitp : PatLeaf<(imm), [{
    172   uint32_t value = (uint32_t)N->getZExtValue();
    173   return (value >= 24 && value <= 31)
    174           || value == 16
    175           || value == 8
    176           || value == 0;
    177 }]>;
    178 
    179 def lda16f : PatFrag<(ops node:$addr, node:$offset),
    180                      (add node:$addr, (shl node:$offset, 1))>;
    181 def lda16b : PatFrag<(ops node:$addr, node:$offset),
    182                      (sub node:$addr, (shl node:$offset, 1))>;
    183 def ldawf : PatFrag<(ops node:$addr, node:$offset),
    184                      (add node:$addr, (shl node:$offset, 2))>;
    185 def ldawb : PatFrag<(ops node:$addr, node:$offset),
    186                      (sub node:$addr, (shl node:$offset, 2))>;
    187 
    188 // Instruction operand types
    189 def pcrel_imm  : Operand<i32>;
    190 def pcrel_imm_neg  : Operand<i32> {
    191   let DecoderMethod = "DecodeNegImmOperand";
    192 }
    193 def brtarget : Operand<OtherVT>;
    194 def brtarget_neg : Operand<OtherVT> {
    195   let DecoderMethod = "DecodeNegImmOperand";
    196 }
    197 
    198 // Addressing modes
    199 def ADDRspii : ComplexPattern<i32, 2, "SelectADDRspii", [add, frameindex], []>;
    200 
    201 // Address operands
    202 def MEMii : Operand<i32> {
    203   let MIOperandInfo = (ops i32imm, i32imm);
    204 }
    205 
    206 // Jump tables.
    207 def InlineJT : Operand<i32> {
    208   let PrintMethod = "printInlineJT";
    209 }
    210 
    211 def InlineJT32 : Operand<i32> {
    212   let PrintMethod = "printInlineJT32";
    213 }
    214 
    215 //===----------------------------------------------------------------------===//
    216 // Instruction Class Templates
    217 //===----------------------------------------------------------------------===//
    218 
    219 // Three operand short
    220 
    221 multiclass F3R_2RUS<bits<5> opc1, bits<5> opc2, string OpcStr, SDNode OpNode> {
    222   def _3r: _F3R<opc1, (outs GRRegs:$dst), (ins GRRegs:$b, GRRegs:$c),
    223                 !strconcat(OpcStr, " $dst, $b, $c"),
    224                 [(set GRRegs:$dst, (OpNode GRRegs:$b, GRRegs:$c))]>;
    225   def _2rus : _F2RUS<opc2, (outs GRRegs:$dst), (ins GRRegs:$b, i32imm:$c),
    226                      !strconcat(OpcStr, " $dst, $b, $c"),
    227                      [(set GRRegs:$dst, (OpNode GRRegs:$b, immUs:$c))]>;
    228 }
    229 
    230 multiclass F3R_2RUS_np<bits<5> opc1, bits<5> opc2, string OpcStr> {
    231   def _3r: _F3R<opc1, (outs GRRegs:$dst), (ins GRRegs:$b, GRRegs:$c),
    232                 !strconcat(OpcStr, " $dst, $b, $c"), []>;
    233   def _2rus : _F2RUS<opc2, (outs GRRegs:$dst), (ins GRRegs:$b, i32imm:$c),
    234                      !strconcat(OpcStr, " $dst, $b, $c"), []>;
    235 }
    236 
    237 multiclass F3R_2RBITP<bits<5> opc1, bits<5> opc2, string OpcStr,
    238                       SDNode OpNode> {
    239   def _3r: _F3R<opc1, (outs GRRegs:$dst), (ins GRRegs:$b, GRRegs:$c),
    240                 !strconcat(OpcStr, " $dst, $b, $c"),
    241                 [(set GRRegs:$dst, (OpNode GRRegs:$b, GRRegs:$c))]>;
    242   def _2rus : _F2RUSBitp<opc2, (outs GRRegs:$dst), (ins GRRegs:$b, i32imm:$c),
    243                          !strconcat(OpcStr, " $dst, $b, $c"),
    244                          [(set GRRegs:$dst, (OpNode GRRegs:$b, immBitp:$c))]>;
    245 }
    246 
    247 class F3R<bits<5> opc, string OpcStr, SDNode OpNode> :
    248   _F3R<opc, (outs GRRegs:$dst), (ins GRRegs:$b, GRRegs:$c),
    249        !strconcat(OpcStr, " $dst, $b, $c"),
    250        [(set GRRegs:$dst, (OpNode GRRegs:$b, GRRegs:$c))]>;
    251 
    252 class F3R_np<bits<5> opc, string OpcStr> :
    253   _F3R<opc, (outs GRRegs:$dst), (ins GRRegs:$b, GRRegs:$c),
    254        !strconcat(OpcStr, " $dst, $b, $c"), []>;
    255 // Three operand long
    256 
    257 /// FL3R_L2RUS multiclass - Define a normal FL3R/FL2RUS pattern in one shot.
    258 multiclass FL3R_L2RUS<bits<9> opc1, bits<9> opc2, string OpcStr,
    259                       SDNode OpNode> {
    260   def _l3r: _FL3R<opc1, (outs GRRegs:$dst), (ins GRRegs:$b, GRRegs:$c),
    261                   !strconcat(OpcStr, " $dst, $b, $c"),
    262                   [(set GRRegs:$dst, (OpNode GRRegs:$b, GRRegs:$c))]>;
    263   def _l2rus : _FL2RUS<opc2, (outs GRRegs:$dst), (ins GRRegs:$b, i32imm:$c),
    264                        !strconcat(OpcStr, " $dst, $b, $c"),
    265                        [(set GRRegs:$dst, (OpNode GRRegs:$b, immUs:$c))]>;
    266 }
    267 
    268 /// FL3R_L2RUS multiclass - Define a normal FL3R/FL2RUS pattern in one shot.
    269 multiclass FL3R_L2RBITP<bits<9> opc1, bits<9> opc2, string OpcStr,
    270                         SDNode OpNode> {
    271   def _l3r: _FL3R<opc1, (outs GRRegs:$dst), (ins GRRegs:$b, GRRegs:$c),
    272                   !strconcat(OpcStr, " $dst, $b, $c"),
    273                   [(set GRRegs:$dst, (OpNode GRRegs:$b, GRRegs:$c))]>;
    274   def _l2rus : _FL2RUSBitp<opc2, (outs GRRegs:$dst), (ins GRRegs:$b, i32imm:$c),
    275                            !strconcat(OpcStr, " $dst, $b, $c"),
    276                            [(set GRRegs:$dst, (OpNode GRRegs:$b, immBitp:$c))]>;
    277 }
    278 
    279 class FL3R<bits<9> opc, string OpcStr, SDNode OpNode> :
    280   _FL3R<opc, (outs GRRegs:$dst), (ins GRRegs:$b, GRRegs:$c),
    281         !strconcat(OpcStr, " $dst, $b, $c"),
    282         [(set GRRegs:$dst, (OpNode GRRegs:$b, GRRegs:$c))]>;
    283 
    284 // Register - U6
    285 // Operand register - U6
    286 multiclass FRU6_LRU6_branch<bits<6> opc, string OpcStr> {
    287   def _ru6: _FRU6<opc, (outs), (ins GRRegs:$a, brtarget:$b),
    288                   !strconcat(OpcStr, " $a, $b"), []>;
    289   def _lru6: _FLRU6<opc, (outs), (ins GRRegs:$a, brtarget:$b),
    290                     !strconcat(OpcStr, " $a, $b"), []>;
    291 }
    292 
    293 multiclass FRU6_LRU6_backwards_branch<bits<6> opc, string OpcStr> {
    294   def _ru6: _FRU6<opc, (outs), (ins GRRegs:$a, brtarget_neg:$b),
    295                   !strconcat(OpcStr, " $a, $b"), []>;
    296   def _lru6: _FLRU6<opc, (outs), (ins GRRegs:$a, brtarget_neg:$b),
    297                     !strconcat(OpcStr, " $a, $b"), []>;
    298 }
    299 
    300 
    301 // U6
    302 multiclass FU6_LU6<bits<10> opc, string OpcStr, SDNode OpNode> {
    303   def _u6: _FU6<opc, (outs), (ins i32imm:$a), !strconcat(OpcStr, " $a"),
    304                 [(OpNode immU6:$a)]>;
    305   def _lu6: _FLU6<opc, (outs), (ins i32imm:$a), !strconcat(OpcStr, " $a"),
    306                   [(OpNode immU16:$a)]>;
    307 }
    308 
    309 multiclass FU6_LU6_int<bits<10> opc, string OpcStr, Intrinsic Int> {
    310   def _u6: _FU6<opc, (outs), (ins i32imm:$a), !strconcat(OpcStr, " $a"),
    311                 [(Int immU6:$a)]>;
    312   def _lu6: _FLU6<opc, (outs), (ins i32imm:$a), !strconcat(OpcStr, " $a"),
    313                   [(Int immU16:$a)]>;
    314 }
    315 
    316 multiclass FU6_LU6_np<bits<10> opc, string OpcStr> {
    317   def _u6: _FU6<opc, (outs), (ins i32imm:$a), !strconcat(OpcStr, " $a"), []>;
    318   def _lu6: _FLU6<opc, (outs), (ins i32imm:$a), !strconcat(OpcStr, " $a"), []>;
    319 }
    320 
    321 // Two operand short
    322 
    323 class F2R_np<bits<6> opc, string OpcStr> :
    324   _F2R<opc, (outs GRRegs:$dst), (ins GRRegs:$b),
    325        !strconcat(OpcStr, " $dst, $b"), []>;
    326 
    327 // Two operand long
    328 
    329 //===----------------------------------------------------------------------===//
    330 // Pseudo Instructions
    331 //===----------------------------------------------------------------------===//
    332 
    333 let Defs = [SP], Uses = [SP] in {
    334 def ADJCALLSTACKDOWN : PseudoInstXCore<(outs), (ins i32imm:$amt),
    335                                "# ADJCALLSTACKDOWN $amt",
    336                                [(callseq_start timm:$amt)]>;
    337 def ADJCALLSTACKUP : PseudoInstXCore<(outs), (ins i32imm:$amt1, i32imm:$amt2),
    338                             "# ADJCALLSTACKUP $amt1",
    339                             [(callseq_end timm:$amt1, timm:$amt2)]>;
    340 }
    341 
    342 let isReMaterializable = 1 in
    343 def FRAME_TO_ARGS_OFFSET : PseudoInstXCore<(outs GRRegs:$dst), (ins),
    344                                "# FRAME_TO_ARGS_OFFSET $dst",
    345                                [(set GRRegs:$dst, (frametoargsoffset))]>;
    346 
    347 let isReturn = 1, isTerminator = 1, isBarrier = 1 in
    348 def EH_RETURN : PseudoInstXCore<(outs), (ins GRRegs:$s, GRRegs:$handler),
    349                                "# EH_RETURN $s, $handler",
    350                                [(XCoreEhRet GRRegs:$s, GRRegs:$handler)]>;
    351 
    352 def LDWFI : PseudoInstXCore<(outs GRRegs:$dst), (ins MEMii:$addr),
    353                              "# LDWFI $dst, $addr",
    354                              [(set GRRegs:$dst, (load ADDRspii:$addr))]>;
    355 
    356 def LDAWFI : PseudoInstXCore<(outs GRRegs:$dst), (ins MEMii:$addr),
    357                              "# LDAWFI $dst, $addr",
    358                              [(set GRRegs:$dst, ADDRspii:$addr)]>;
    359 
    360 def STWFI : PseudoInstXCore<(outs), (ins GRRegs:$src, MEMii:$addr),
    361                             "# STWFI $src, $addr",
    362                             [(store GRRegs:$src, ADDRspii:$addr)]>;
    363 
    364 // SELECT_CC_* - Used to implement the SELECT_CC DAG operation.  Expanded after
    365 // instruction selection into a branch sequence.
    366 let usesCustomInserter = 1 in {
    367   def SELECT_CC : PseudoInstXCore<(outs GRRegs:$dst),
    368                               (ins GRRegs:$cond, GRRegs:$T, GRRegs:$F),
    369                               "# SELECT_CC PSEUDO!",
    370                               [(set GRRegs:$dst,
    371                                  (select GRRegs:$cond, GRRegs:$T, GRRegs:$F))]>;
    372 }
    373 
    374 let hasSideEffects = 1 in
    375 def Int_MemBarrier : PseudoInstXCore<(outs), (ins), "#MEMBARRIER",
    376                                      [(XCoreMemBarrier)]>;
    377 
    378 //===----------------------------------------------------------------------===//
    379 // Instructions
    380 //===----------------------------------------------------------------------===//
    381 
    382 // Three operand short
    383 defm ADD : F3R_2RUS<0b00010, 0b10010, "add", add>;
    384 defm SUB : F3R_2RUS<0b00011, 0b10011, "sub", sub>;
    385 let hasSideEffects = 0 in {
    386 defm EQ : F3R_2RUS_np<0b00110, 0b10110, "eq">;
    387 def LSS_3r : F3R_np<0b11000, "lss">;
    388 def LSU_3r : F3R_np<0b11001, "lsu">;
    389 }
    390 def AND_3r : F3R<0b00111, "and", and>;
    391 def OR_3r : F3R<0b01000, "or", or>;
    392 
    393 let mayLoad=1 in {
    394 def LDW_3r : _F3R<0b01001, (outs GRRegs:$dst),
    395                   (ins GRRegs:$addr, GRRegs:$offset),
    396                   "ldw $dst, $addr[$offset]", []>;
    397 
    398 def LDW_2rus : _F2RUS<0b00001, (outs GRRegs:$dst),
    399                       (ins GRRegs:$addr, i32imm:$offset),
    400                       "ldw $dst, $addr[$offset]", []>;
    401 
    402 def LD16S_3r :  _F3R<0b10000, (outs GRRegs:$dst),
    403                      (ins GRRegs:$addr, GRRegs:$offset),
    404                      "ld16s $dst, $addr[$offset]", []>;
    405 
    406 def LD8U_3r :  _F3R<0b10001, (outs GRRegs:$dst),
    407                     (ins GRRegs:$addr, GRRegs:$offset),
    408                     "ld8u $dst, $addr[$offset]", []>;
    409 }
    410 
    411 let mayStore=1 in {
    412 def STW_l3r : _FL3R<0b000001100, (outs),
    413                     (ins GRRegs:$val, GRRegs:$addr, GRRegs:$offset),
    414                     "stw $val, $addr[$offset]", []>;
    415 
    416 def STW_2rus : _F2RUS<0b00000, (outs),
    417                       (ins GRRegs:$val, GRRegs:$addr, i32imm:$offset),
    418                       "stw $val, $addr[$offset]", []>;
    419 }
    420 
    421 defm SHL : F3R_2RBITP<0b00100, 0b10100, "shl", shl>;
    422 defm SHR : F3R_2RBITP<0b00101, 0b10101, "shr", srl>;
    423 
    424 // The first operand is treated as an immediate since it refers to a register
    425 // number in another thread.
    426 def TSETR_3r : _F3RImm<0b10111, (outs), (ins i32imm:$a, GRRegs:$b, GRRegs:$c),
    427                        "set t[$c]:r$a, $b", []>;
    428 
    429 // Three operand long
    430 def LDAWF_l3r : _FL3R<0b000111100, (outs GRRegs:$dst),
    431                       (ins GRRegs:$addr, GRRegs:$offset),
    432                       "ldaw $dst, $addr[$offset]",
    433                       [(set GRRegs:$dst,
    434                          (ldawf GRRegs:$addr, GRRegs:$offset))]>;
    435 
    436 let hasSideEffects = 0 in
    437 def LDAWF_l2rus : _FL2RUS<0b100111100, (outs GRRegs:$dst),
    438                           (ins GRRegs:$addr, i32imm:$offset),
    439                           "ldaw $dst, $addr[$offset]", []>;
    440 
    441 def LDAWB_l3r : _FL3R<0b001001100, (outs GRRegs:$dst),
    442                       (ins GRRegs:$addr, GRRegs:$offset),
    443                       "ldaw $dst, $addr[-$offset]",
    444                       [(set GRRegs:$dst,
    445                          (ldawb GRRegs:$addr, GRRegs:$offset))]>;
    446 
    447 let hasSideEffects = 0 in
    448 def LDAWB_l2rus : _FL2RUS<0b101001100, (outs GRRegs:$dst),
    449                          (ins GRRegs:$addr, i32imm:$offset),
    450                          "ldaw $dst, $addr[-$offset]", []>;
    451 
    452 def LDA16F_l3r : _FL3R<0b001011100, (outs GRRegs:$dst),
    453                        (ins GRRegs:$addr, GRRegs:$offset),
    454                        "lda16 $dst, $addr[$offset]",
    455                        [(set GRRegs:$dst,
    456                           (lda16f GRRegs:$addr, GRRegs:$offset))]>;
    457 
    458 def LDA16B_l3r : _FL3R<0b001101100, (outs GRRegs:$dst),
    459                        (ins GRRegs:$addr, GRRegs:$offset),
    460                        "lda16 $dst, $addr[-$offset]",
    461                        [(set GRRegs:$dst,
    462                           (lda16b GRRegs:$addr, GRRegs:$offset))]>;
    463 
    464 def MUL_l3r : FL3R<0b001111100, "mul", mul>;
    465 // Instructions which may trap are marked as side effecting.
    466 let hasSideEffects = 1 in {
    467 def DIVS_l3r : FL3R<0b010001100, "divs", sdiv>;
    468 def DIVU_l3r : FL3R<0b010011100, "divu", udiv>;
    469 def REMS_l3r : FL3R<0b110001100, "rems", srem>;
    470 def REMU_l3r : FL3R<0b110011100, "remu", urem>;
    471 }
    472 def XOR_l3r : FL3R<0b000011100, "xor", xor>;
    473 defm ASHR : FL3R_L2RBITP<0b000101100, 0b100101100, "ashr", sra>;
    474 
    475 let Constraints = "$src1 = $dst" in
    476 def CRC_l3r : _FL3RSrcDst<0b101011100, (outs GRRegs:$dst),
    477                           (ins GRRegs:$src1, GRRegs:$src2, GRRegs:$src3),
    478                           "crc32 $dst, $src2, $src3",
    479                           [(set GRRegs:$dst,
    480                              (int_xcore_crc32 GRRegs:$src1, GRRegs:$src2,
    481                                               GRRegs:$src3))]>;
    482 
    483 let mayStore=1 in {
    484 def ST16_l3r : _FL3R<0b100001100, (outs),
    485                      (ins GRRegs:$val, GRRegs:$addr, GRRegs:$offset),
    486                      "st16 $val, $addr[$offset]", []>;
    487 
    488 def ST8_l3r : _FL3R<0b100011100, (outs),
    489                     (ins GRRegs:$val, GRRegs:$addr, GRRegs:$offset),
    490                     "st8 $val, $addr[$offset]", []>;
    491 }
    492 
    493 def INPW_l2rus : _FL2RUSBitp<0b100101110, (outs GRRegs:$a),
    494                              (ins GRRegs:$b, i32imm:$c), "inpw $a, res[$b], $c",
    495                              []>;
    496 
    497 def OUTPW_l2rus : _FL2RUSBitp<0b100101101, (outs),
    498                               (ins GRRegs:$a, GRRegs:$b, i32imm:$c),
    499                               "outpw res[$b], $a, $c", []>;
    500 
    501 // Four operand long
    502 let Constraints = "$e = $a,$f = $b" in {
    503 def MACCU_l4r : _FL4RSrcDstSrcDst<
    504   0b000001, (outs GRRegs:$a, GRRegs:$b),
    505   (ins GRRegs:$e, GRRegs:$f, GRRegs:$c, GRRegs:$d), "maccu $a, $b, $c, $d", []>;
    506 
    507 def MACCS_l4r : _FL4RSrcDstSrcDst<
    508   0b000010, (outs GRRegs:$a, GRRegs:$b),
    509   (ins GRRegs:$e, GRRegs:$f, GRRegs:$c, GRRegs:$d), "maccs $a, $b, $c, $d", []>;
    510 }
    511 
    512 let Constraints = "$e = $b" in
    513 def CRC8_l4r : _FL4RSrcDst<0b000000, (outs GRRegs:$a, GRRegs:$b),
    514                            (ins GRRegs:$e, GRRegs:$c, GRRegs:$d),
    515                            "crc8 $b, $a, $c, $d", []>;
    516 
    517 // Five operand long
    518 
    519 def LADD_l5r : _FL5R<0b000001, (outs GRRegs:$dst1, GRRegs:$dst2),
    520                      (ins GRRegs:$src1, GRRegs:$src2, GRRegs:$src3),
    521                      "ladd $dst2, $dst1, $src1, $src2, $src3",
    522                      []>;
    523 
    524 def LSUB_l5r : _FL5R<0b000010, (outs GRRegs:$dst1, GRRegs:$dst2),
    525                      (ins GRRegs:$src1, GRRegs:$src2, GRRegs:$src3),
    526                      "lsub $dst2, $dst1, $src1, $src2, $src3", []>;
    527 
    528 def LDIVU_l5r : _FL5R<0b000000, (outs GRRegs:$dst1, GRRegs:$dst2),
    529                       (ins GRRegs:$src1, GRRegs:$src2, GRRegs:$src3),
    530                       "ldivu $dst1, $dst2, $src3, $src1, $src2", []>;
    531 
    532 // Six operand long
    533 
    534 def LMUL_l6r : _FL6R<
    535   0b00000, (outs GRRegs:$dst1, GRRegs:$dst2),
    536   (ins GRRegs:$src1, GRRegs:$src2, GRRegs:$src3, GRRegs:$src4),
    537   "lmul $dst1, $dst2, $src1, $src2, $src3, $src4", []>;
    538 
    539 // Register - U6
    540 
    541 //let Uses = [DP] in ...
    542 let hasSideEffects = 0, isReMaterializable = 1 in
    543 def LDAWDP_ru6: _FRU6<0b011000, (outs RRegs:$a), (ins i32imm:$b),
    544                       "ldaw $a, dp[$b]", []>;
    545 
    546 let isReMaterializable = 1 in                    
    547 def LDAWDP_lru6: _FLRU6<0b011000, (outs RRegs:$a), (ins i32imm:$b),
    548                         "ldaw $a, dp[$b]",
    549                         [(set RRegs:$a, (dprelwrapper tglobaladdr:$b))]>;
    550 
    551 let mayLoad=1 in
    552 def LDWDP_ru6: _FRU6<0b010110, (outs RRegs:$a), (ins i32imm:$b),
    553                      "ldw $a, dp[$b]", []>;
    554 
    555 def LDWDP_lru6: _FLRU6<0b010110, (outs RRegs:$a), (ins i32imm:$b),
    556                        "ldw $a, dp[$b]",
    557                        [(set RRegs:$a, (load (dprelwrapper tglobaladdr:$b)))]>;
    558 
    559 let mayStore=1 in
    560 def STWDP_ru6 : _FRU6<0b010100, (outs), (ins RRegs:$a, i32imm:$b),
    561                       "stw $a, dp[$b]", []>;
    562 
    563 def STWDP_lru6 : _FLRU6<0b010100, (outs), (ins RRegs:$a, i32imm:$b),
    564                         "stw $a, dp[$b]",
    565                         [(store RRegs:$a, (dprelwrapper tglobaladdr:$b))]>;
    566 
    567 //let Uses = [CP] in ..
    568 let mayLoad = 1, isReMaterializable = 1, hasSideEffects = 0 in {
    569 def LDWCP_ru6 : _FRU6<0b011011, (outs RRegs:$a), (ins i32imm:$b),
    570                       "ldw $a, cp[$b]", []>;
    571 def LDWCP_lru6: _FLRU6<0b011011, (outs RRegs:$a), (ins i32imm:$b),
    572                        "ldw $a, cp[$b]",
    573                        [(set RRegs:$a, (load (cprelwrapper tglobaladdr:$b)))]>;
    574 }
    575 
    576 let Uses = [SP] in {
    577 let mayStore=1 in {
    578 def STWSP_ru6 : _FRU6<0b010101, (outs), (ins RRegs:$a, i32imm:$b),
    579                       "stw $a, sp[$b]",
    580                       [(XCoreStwsp RRegs:$a, immU6:$b)]>;
    581 
    582 def STWSP_lru6 : _FLRU6<0b010101, (outs), (ins RRegs:$a, i32imm:$b),
    583                         "stw $a, sp[$b]",
    584                         [(XCoreStwsp RRegs:$a, immU16:$b)]>;
    585 }
    586 
    587 let mayLoad=1 in {
    588 def LDWSP_ru6 : _FRU6<0b010111, (outs RRegs:$a), (ins i32imm:$b),
    589                       "ldw $a, sp[$b]",
    590                       [(set RRegs:$a, (XCoreLdwsp immU6:$b))]>;
    591 
    592 def LDWSP_lru6 : _FLRU6<0b010111, (outs RRegs:$a), (ins i32imm:$b),
    593                         "ldw $a, sp[$b]",
    594                         [(set RRegs:$a, (XCoreLdwsp immU16:$b))]>;
    595 }
    596 
    597 let hasSideEffects = 0 in {
    598 def LDAWSP_ru6 : _FRU6<0b011001, (outs RRegs:$a), (ins i32imm:$b),
    599                        "ldaw $a, sp[$b]", []>;
    600 
    601 def LDAWSP_lru6 : _FLRU6<0b011001, (outs RRegs:$a), (ins i32imm:$b),
    602                          "ldaw $a, sp[$b]", []>;
    603 }
    604 }
    605 
    606 let isReMaterializable = 1 in {
    607 def LDC_ru6 : _FRU6<0b011010, (outs RRegs:$a), (ins i32imm:$b),
    608                     "ldc $a, $b", [(set RRegs:$a, immU6:$b)]>;
    609 
    610 def LDC_lru6 : _FLRU6<0b011010, (outs RRegs:$a), (ins i32imm:$b),
    611                       "ldc $a, $b", [(set RRegs:$a, immU16:$b)]>;
    612 }
    613 
    614 def SETC_ru6 : _FRU6<0b111010, (outs), (ins GRRegs:$a, i32imm:$b),
    615                      "setc res[$a], $b",
    616                      [(int_xcore_setc GRRegs:$a, immU6:$b)]>;
    617 
    618 def SETC_lru6 : _FLRU6<0b111010, (outs), (ins GRRegs:$a, i32imm:$b),
    619                        "setc res[$a], $b",
    620                        [(int_xcore_setc GRRegs:$a, immU16:$b)]>;
    621 
    622 // Operand register - U6
    623 let isBranch = 1, isTerminator = 1 in {
    624 defm BRFT: FRU6_LRU6_branch<0b011100, "bt">;
    625 defm BRBT: FRU6_LRU6_backwards_branch<0b011101, "bt">;
    626 defm BRFF: FRU6_LRU6_branch<0b011110, "bf">;
    627 defm BRBF: FRU6_LRU6_backwards_branch<0b011111, "bf">;
    628 }
    629 
    630 // U6
    631 let Defs = [SP], Uses = [SP] in {
    632 let hasSideEffects = 0 in
    633 defm EXTSP : FU6_LU6_np<0b0111011110, "extsp">;
    634 
    635 let mayStore = 1 in
    636 defm ENTSP : FU6_LU6_np<0b0111011101, "entsp">;
    637 
    638 let isReturn = 1, isTerminator = 1, mayLoad = 1, isBarrier = 1 in {
    639 defm RETSP : FU6_LU6<0b0111011111, "retsp", XCoreRetsp>;
    640 }
    641 }
    642 
    643 let hasSideEffects = 0 in
    644 defm EXTDP : FU6_LU6_np<0b0111001110, "extdp">;
    645 
    646 let Uses = [R11], isCall=1 in
    647 defm BLAT : FU6_LU6_np<0b0111001101, "blat">;
    648 
    649 let isBranch = 1, isTerminator = 1, isBarrier = 1 in {
    650 def BRBU_u6 : _FU6<0b0111011100, (outs), (ins brtarget_neg:$a), "bu $a", []>;
    651 
    652 def BRBU_lu6 : _FLU6<0b0111011100, (outs), (ins brtarget_neg:$a), "bu $a", []>;
    653 
    654 def BRFU_u6 : _FU6<0b0111001100, (outs), (ins brtarget:$a), "bu $a", []>;
    655 
    656 def BRFU_lu6 : _FLU6<0b0111001100, (outs), (ins brtarget:$a), "bu $a", []>;
    657 }
    658 
    659 //let Uses = [CP] in ...
    660 let Defs = [R11], hasSideEffects = 0, isReMaterializable = 1 in
    661 def LDAWCP_u6: _FU6<0b0111111101, (outs), (ins i32imm:$a), "ldaw r11, cp[$a]",
    662                     []>;
    663 
    664 let Defs = [R11], isReMaterializable = 1 in
    665 def LDAWCP_lu6: _FLU6<0b0111111101, (outs), (ins i32imm:$a), "ldaw r11, cp[$a]",
    666                       [(set R11, (cprelwrapper tglobaladdr:$a))]>;
    667 
    668 let Defs = [R11] in
    669 defm GETSR : FU6_LU6_np<0b0111111100, "getsr r11,">;
    670 
    671 defm SETSR : FU6_LU6_int<0b0111101101, "setsr", int_xcore_setsr>;
    672 
    673 defm CLRSR : FU6_LU6_int<0b0111101100, "clrsr", int_xcore_clrsr>;
    674 
    675 // setsr may cause a branch if it is used to enable events. clrsr may
    676 // branch if it is executed while events are enabled.
    677 let isBranch=1, isIndirectBranch=1, isTerminator=1, isBarrier = 1,
    678     isCodeGenOnly = 1 in {
    679 defm SETSR_branch : FU6_LU6_np<0b0111101101, "setsr">;
    680 defm CLRSR_branch : FU6_LU6_np<0b0111101100, "clrsr">;
    681 }
    682 
    683 defm KCALL : FU6_LU6_np<0b0111001111, "kcall">;
    684 
    685 let Uses = [SP], Defs = [SP], mayStore = 1 in
    686 defm KENTSP : FU6_LU6_np<0b0111101110, "kentsp">;
    687 
    688 let Uses = [SP], Defs = [SP], mayLoad = 1 in
    689 defm KRESTSP : FU6_LU6_np<0b0111101111, "krestsp">;
    690 
    691 // U10
    692 
    693 let Defs = [R11], isReMaterializable = 1 in {
    694 let hasSideEffects = 0 in
    695 def LDAPF_u10 : _FU10<0b110110, (outs), (ins pcrel_imm:$a), "ldap r11, $a", []>;
    696 
    697 def LDAPF_lu10 : _FLU10<0b110110, (outs), (ins pcrel_imm:$a), "ldap r11, $a",
    698                         [(set R11, (pcrelwrapper tglobaladdr:$a))]>;
    699 
    700 let hasSideEffects = 0 in
    701 def LDAPB_u10 : _FU10<0b110111, (outs), (ins pcrel_imm_neg:$a), "ldap r11, $a",
    702                       []>;
    703 
    704 let hasSideEffects = 0 in
    705 def LDAPB_lu10 : _FLU10<0b110111, (outs), (ins pcrel_imm_neg:$a),
    706                         "ldap r11, $a",
    707                         [(set R11, (pcrelwrapper tglobaladdr:$a))]>;
    708 
    709 let isCodeGenOnly = 1 in
    710 def LDAPF_lu10_ba : _FLU10<0b110110, (outs), (ins pcrel_imm:$a), "ldap r11, $a",
    711                            [(set R11, (pcrelwrapper tblockaddress:$a))]>;
    712 }
    713 
    714 let isCall=1,
    715 // All calls clobber the link register and the non-callee-saved registers:
    716 Defs = [R0, R1, R2, R3, R11, LR], Uses = [SP] in {
    717 def BLACP_u10 : _FU10<0b111000, (outs), (ins i32imm:$a), "bla cp[$a]", []>;
    718 
    719 def BLACP_lu10 : _FLU10<0b111000, (outs), (ins i32imm:$a), "bla cp[$a]", []>;
    720 
    721 def BLRF_u10 : _FU10<0b110100, (outs), (ins pcrel_imm:$a), "bl $a",
    722                      []>;
    723 
    724 def BLRF_lu10 : _FLU10<0b110100, (outs), (ins pcrel_imm:$a), "bl $a",
    725                        [(XCoreBranchLink tglobaladdr:$a)]>;
    726 
    727 def BLRB_u10 : _FU10<0b110101, (outs), (ins pcrel_imm_neg:$a), "bl $a", []>;
    728 
    729 def BLRB_lu10 : _FLU10<0b110101, (outs), (ins pcrel_imm_neg:$a), "bl $a", []>;
    730 }
    731 
    732 let Defs = [R11], mayLoad = 1, isReMaterializable = 1,
    733     hasSideEffects = 0 in {
    734 def LDWCP_u10 : _FU10<0b111001, (outs), (ins i32imm:$a), "ldw r11, cp[$a]", []>;
    735 
    736 def LDWCP_lu10 : _FLU10<0b111001, (outs), (ins i32imm:$a), "ldw r11, cp[$a]",
    737                         []>;
    738 }
    739 
    740 // Two operand short
    741 def NOT : _F2R<0b100010, (outs GRRegs:$dst), (ins GRRegs:$b),
    742                 "not $dst, $b", [(set GRRegs:$dst, (not GRRegs:$b))]>;
    743 
    744 def NEG : _F2R<0b100100, (outs GRRegs:$dst), (ins GRRegs:$b),
    745                 "neg $dst, $b", [(set GRRegs:$dst, (ineg GRRegs:$b))]>;
    746 
    747 let Constraints = "$src1 = $dst" in {
    748 def SEXT_rus :
    749   _FRUSSrcDstBitp<0b001101, (outs GRRegs:$dst), (ins GRRegs:$src1, i32imm:$src2),
    750                   "sext $dst, $src2",
    751                   [(set GRRegs:$dst, (int_xcore_sext GRRegs:$src1,
    752                                                      immBitp:$src2))]>;
    753 
    754 def SEXT_2r :
    755   _F2RSrcDst<0b001100, (outs GRRegs:$dst), (ins GRRegs:$src1, GRRegs:$src2),
    756              "sext $dst, $src2",
    757              [(set GRRegs:$dst, (int_xcore_sext GRRegs:$src1, GRRegs:$src2))]>;
    758 
    759 def ZEXT_rus :
    760   _FRUSSrcDstBitp<0b010001, (outs GRRegs:$dst), (ins GRRegs:$src1, i32imm:$src2),
    761                   "zext $dst, $src2",
    762                   [(set GRRegs:$dst, (int_xcore_zext GRRegs:$src1,
    763                                                      immBitp:$src2))]>;
    764 
    765 def ZEXT_2r :
    766   _F2RSrcDst<0b010000, (outs GRRegs:$dst), (ins GRRegs:$src1, GRRegs:$src2),
    767              "zext $dst, $src2",
    768              [(set GRRegs:$dst, (int_xcore_zext GRRegs:$src1, GRRegs:$src2))]>;
    769 
    770 def ANDNOT_2r :
    771   _F2RSrcDst<0b001010, (outs GRRegs:$dst), (ins GRRegs:$src1, GRRegs:$src2),
    772              "andnot $dst, $src2",
    773              [(set GRRegs:$dst, (and GRRegs:$src1, (not GRRegs:$src2)))]>;
    774 }
    775 
    776 let isReMaterializable = 1, hasSideEffects = 0 in
    777 def MKMSK_rus : _FRUSBitp<0b101001, (outs GRRegs:$dst), (ins i32imm:$size),
    778                           "mkmsk $dst, $size", []>;
    779 
    780 def MKMSK_2r : _F2R<0b101000, (outs GRRegs:$dst), (ins GRRegs:$size),
    781                     "mkmsk $dst, $size",
    782                     [(set GRRegs:$dst, (add (shl 1, GRRegs:$size), -1))]>;
    783 
    784 def GETR_rus : _FRUS<0b100000, (outs GRRegs:$dst), (ins i32imm:$type),
    785                      "getr $dst, $type",
    786                      [(set GRRegs:$dst, (int_xcore_getr immUs:$type))]>;
    787 
    788 def GETTS_2r : _F2R<0b001110, (outs GRRegs:$dst), (ins GRRegs:$r),
    789                     "getts $dst, res[$r]",
    790                     [(set GRRegs:$dst, (int_xcore_getts GRRegs:$r))]>;
    791 
    792 def SETPT_2r : _FR2R<0b001111, (outs), (ins GRRegs:$r, GRRegs:$val),
    793                      "setpt res[$r], $val",
    794                      [(int_xcore_setpt GRRegs:$r, GRRegs:$val)]>;
    795 
    796 def OUTCT_2r : _F2R<0b010010, (outs), (ins GRRegs:$r, GRRegs:$val),
    797                     "outct res[$r], $val",
    798                     [(int_xcore_outct GRRegs:$r, GRRegs:$val)]>;
    799 
    800 def OUTCT_rus : _FRUS<0b010011, (outs), (ins GRRegs:$r, i32imm:$val),
    801                        "outct res[$r], $val",
    802                        [(int_xcore_outct GRRegs:$r, immUs:$val)]>;
    803 
    804 def OUTT_2r : _FR2R<0b000011, (outs), (ins GRRegs:$r, GRRegs:$val),
    805                     "outt res[$r], $val",
    806                     [(int_xcore_outt GRRegs:$r, GRRegs:$val)]>;
    807 
    808 def OUT_2r : _FR2R<0b101010, (outs), (ins GRRegs:$r, GRRegs:$val),
    809                    "out res[$r], $val",
    810                    [(int_xcore_out GRRegs:$r, GRRegs:$val)]>;
    811 
    812 let Constraints = "$src = $dst" in
    813 def OUTSHR_2r :
    814   _F2RSrcDst<0b101011, (outs GRRegs:$dst), (ins GRRegs:$src, GRRegs:$r),
    815              "outshr res[$r], $src",
    816              [(set GRRegs:$dst, (int_xcore_outshr GRRegs:$r, GRRegs:$src))]>;
    817 
    818 def INCT_2r : _F2R<0b100001, (outs GRRegs:$dst), (ins GRRegs:$r),
    819                    "inct $dst, res[$r]",
    820                    [(set GRRegs:$dst, (int_xcore_inct GRRegs:$r))]>;
    821 
    822 def INT_2r : _F2R<0b100011, (outs GRRegs:$dst), (ins GRRegs:$r),
    823                   "int $dst, res[$r]",
    824                   [(set GRRegs:$dst, (int_xcore_int GRRegs:$r))]>;
    825 
    826 def IN_2r : _F2R<0b101100, (outs GRRegs:$dst), (ins GRRegs:$r),
    827                  "in $dst, res[$r]",
    828                  [(set GRRegs:$dst, (int_xcore_in GRRegs:$r))]>;
    829 
    830 let Constraints = "$src = $dst" in
    831 def INSHR_2r :
    832   _F2RSrcDst<0b101101, (outs GRRegs:$dst), (ins GRRegs:$src, GRRegs:$r),
    833              "inshr $dst, res[$r]",
    834              [(set GRRegs:$dst, (int_xcore_inshr GRRegs:$r, GRRegs:$src))]>;
    835 
    836 def CHKCT_2r : _F2R<0b110010, (outs), (ins GRRegs:$r, GRRegs:$val),
    837                     "chkct res[$r], $val",
    838                     [(int_xcore_chkct GRRegs:$r, GRRegs:$val)]>;
    839 
    840 def CHKCT_rus : _FRUSBitp<0b110011, (outs), (ins GRRegs:$r, i32imm:$val),
    841                           "chkct res[$r], $val",
    842                           [(int_xcore_chkct GRRegs:$r, immUs:$val)]>;
    843 
    844 def TESTCT_2r : _F2R<0b101111, (outs GRRegs:$dst), (ins GRRegs:$src),
    845                      "testct $dst, res[$src]",
    846                      [(set GRRegs:$dst, (int_xcore_testct GRRegs:$src))]>;
    847 
    848 def TESTWCT_2r : _F2R<0b110001, (outs GRRegs:$dst), (ins GRRegs:$src),
    849                       "testwct $dst, res[$src]",
    850                       [(set GRRegs:$dst, (int_xcore_testwct GRRegs:$src))]>;
    851 
    852 def SETD_2r : _FR2R<0b000101, (outs), (ins GRRegs:$r, GRRegs:$val),
    853                     "setd res[$r], $val",
    854                     [(int_xcore_setd GRRegs:$r, GRRegs:$val)]>;
    855 
    856 def SETPSC_2r : _FR2R<0b110000, (outs), (ins GRRegs:$src1, GRRegs:$src2),
    857                       "setpsc res[$src1], $src2",
    858                       [(int_xcore_setpsc GRRegs:$src1, GRRegs:$src2)]>;
    859 
    860 def GETST_2r : _F2R<0b000001, (outs GRRegs:$dst), (ins GRRegs:$r),
    861                     "getst $dst, res[$r]",
    862                     [(set GRRegs:$dst, (int_xcore_getst GRRegs:$r))]>;
    863 
    864 def INITSP_2r : _F2R<0b000100, (outs), (ins GRRegs:$src, GRRegs:$t),
    865                      "init t[$t]:sp, $src",
    866                      [(int_xcore_initsp GRRegs:$t, GRRegs:$src)]>;
    867 
    868 def INITPC_2r : _F2R<0b000000, (outs), (ins GRRegs:$src, GRRegs:$t),
    869                      "init t[$t]:pc, $src",
    870                      [(int_xcore_initpc GRRegs:$t, GRRegs:$src)]>;
    871 
    872 def INITCP_2r : _F2R<0b000110, (outs), (ins GRRegs:$src, GRRegs:$t),
    873                      "init t[$t]:cp, $src",
    874                      [(int_xcore_initcp GRRegs:$t, GRRegs:$src)]>;
    875 
    876 def INITDP_2r : _F2R<0b000010, (outs), (ins GRRegs:$src, GRRegs:$t),
    877                      "init t[$t]:dp, $src",
    878                      [(int_xcore_initdp GRRegs:$t, GRRegs:$src)]>;
    879 
    880 def PEEK_2r : _F2R<0b101110, (outs GRRegs:$dst), (ins GRRegs:$src),
    881                     "peek $dst, res[$src]",
    882                     [(set GRRegs:$dst, (int_xcore_peek GRRegs:$src))]>;
    883 
    884 def ENDIN_2r : _F2R<0b100101, (outs GRRegs:$dst), (ins GRRegs:$src),
    885                      "endin $dst, res[$src]",
    886                      [(set GRRegs:$dst, (int_xcore_endin GRRegs:$src))]>;
    887 
    888 def EEF_2r : _F2R<0b001011, (outs), (ins GRRegs:$a, GRRegs:$b),
    889                   "eef $a, res[$b]", []>;
    890 
    891 def EET_2r : _F2R<0b001001, (outs), (ins GRRegs:$a, GRRegs:$b),
    892                   "eet $a, res[$b]", []>;
    893 
    894 def TSETMR_2r : _F2RImm<0b000111, (outs), (ins i32imm:$a, GRRegs:$b),
    895                         "tsetmr r$a, $b", []>;
    896 
    897 // Two operand long
    898 def BITREV_l2r : _FL2R<0b0000011000, (outs GRRegs:$dst), (ins GRRegs:$src),
    899                        "bitrev $dst, $src",
    900                        [(set GRRegs:$dst, (int_xcore_bitrev GRRegs:$src))]>;
    901 
    902 def BYTEREV_l2r : _FL2R<0b0000011001, (outs GRRegs:$dst), (ins GRRegs:$src),
    903                         "byterev $dst, $src",
    904                         [(set GRRegs:$dst, (bswap GRRegs:$src))]>;
    905 
    906 def CLZ_l2r : _FL2R<0b0000111000, (outs GRRegs:$dst), (ins GRRegs:$src),
    907                     "clz $dst, $src",
    908                     [(set GRRegs:$dst, (ctlz GRRegs:$src))]>;
    909 
    910 def GETD_l2r : _FL2R<0b0001111001, (outs GRRegs:$dst), (ins GRRegs:$src),
    911                      "getd $dst, res[$src]", []>;
    912 
    913 def GETN_l2r : _FL2R<0b0011011001, (outs GRRegs:$dst), (ins GRRegs:$src),
    914                      "getn $dst, res[$src]", []>;
    915 
    916 def SETC_l2r : _FL2R<0b0010111001, (outs), (ins GRRegs:$r, GRRegs:$val),
    917                      "setc res[$r], $val",
    918                      [(int_xcore_setc GRRegs:$r, GRRegs:$val)]>;
    919 
    920 def SETTW_l2r : _FLR2R<0b0010011001, (outs), (ins GRRegs:$r, GRRegs:$val),
    921                        "settw res[$r], $val",
    922                        [(int_xcore_settw GRRegs:$r, GRRegs:$val)]>;
    923 
    924 def GETPS_l2r : _FL2R<0b0001011001, (outs GRRegs:$dst), (ins GRRegs:$src),
    925                       "get $dst, ps[$src]",
    926                       [(set GRRegs:$dst, (int_xcore_getps GRRegs:$src))]>;
    927 
    928 def SETPS_l2r : _FLR2R<0b0001111000, (outs), (ins GRRegs:$src1, GRRegs:$src2),
    929                        "set ps[$src1], $src2",
    930                        [(int_xcore_setps GRRegs:$src1, GRRegs:$src2)]>;
    931 
    932 def INITLR_l2r : _FL2R<0b0001011000, (outs), (ins GRRegs:$src, GRRegs:$t),
    933                        "init t[$t]:lr, $src",
    934                        [(int_xcore_initlr GRRegs:$t, GRRegs:$src)]>;
    935 
    936 def SETCLK_l2r : _FLR2R<0b0000111001, (outs), (ins GRRegs:$src1, GRRegs:$src2),
    937                         "setclk res[$src1], $src2",
    938                         [(int_xcore_setclk GRRegs:$src1, GRRegs:$src2)]>;
    939 
    940 def SETN_l2r : _FLR2R<0b0011011000, (outs), (ins GRRegs:$src1, GRRegs:$src2),
    941                       "setn res[$src1], $src2", []>;
    942 
    943 def SETRDY_l2r : _FLR2R<0b0010111000, (outs), (ins GRRegs:$src1, GRRegs:$src2),
    944                         "setrdy res[$src1], $src2",
    945                         [(int_xcore_setrdy GRRegs:$src1, GRRegs:$src2)]>;
    946 
    947 def TESTLCL_l2r : _FL2R<0b0010011000, (outs GRRegs:$dst), (ins GRRegs:$src),
    948                         "testlcl $dst, res[$src]", []>;
    949 
    950 // One operand short
    951 def MSYNC_1r : _F1R<0b000111, (outs), (ins GRRegs:$a),
    952                     "msync res[$a]",
    953                     [(int_xcore_msync GRRegs:$a)]>;
    954 def MJOIN_1r : _F1R<0b000101, (outs), (ins GRRegs:$a),
    955                     "mjoin res[$a]",
    956                     [(int_xcore_mjoin GRRegs:$a)]>;
    957 
    958 let isBranch=1, isIndirectBranch=1, isTerminator=1, isBarrier = 1 in
    959 def BAU_1r : _F1R<0b001001, (outs), (ins GRRegs:$a),
    960                  "bau $a",
    961                  [(brind GRRegs:$a)]>;
    962 
    963 let isBranch=1, isIndirectBranch=1, isTerminator=1, isBarrier = 1 in
    964 def BR_JT : PseudoInstXCore<(outs), (ins InlineJT:$t, GRRegs:$i),
    965                             "bru $i\n$t",
    966                             [(XCoreBR_JT tjumptable:$t, GRRegs:$i)]>;
    967 
    968 let isBranch=1, isIndirectBranch=1, isTerminator=1, isBarrier = 1 in
    969 def BR_JT32 : PseudoInstXCore<(outs), (ins InlineJT32:$t, GRRegs:$i),
    970                               "bru $i\n$t",
    971                               [(XCoreBR_JT32 tjumptable:$t, GRRegs:$i)]>;
    972 
    973 let isBranch=1, isIndirectBranch=1, isTerminator=1, isBarrier = 1 in
    974 def BRU_1r : _F1R<0b001010, (outs), (ins GRRegs:$a), "bru $a", []>;
    975 
    976 let Defs=[SP], hasSideEffects=0 in
    977 def SETSP_1r : _F1R<0b001011, (outs), (ins GRRegs:$a), "set sp, $a", []>;
    978 
    979 let hasSideEffects=0 in
    980 def SETDP_1r : _F1R<0b001100, (outs), (ins GRRegs:$a), "set dp, $a", []>;
    981 
    982 let hasSideEffects=0 in
    983 def SETCP_1r : _F1R<0b001101, (outs), (ins GRRegs:$a), "set cp, $a", []>;
    984 
    985 let hasCtrlDep = 1 in 
    986 def ECALLT_1r : _F1R<0b010011, (outs), (ins GRRegs:$a),
    987                  "ecallt $a",
    988                  []>;
    989 
    990 let hasCtrlDep = 1 in 
    991 def ECALLF_1r : _F1R<0b010010, (outs), (ins GRRegs:$a),
    992                  "ecallf $a",
    993                  []>;
    994 
    995 let isCall=1, 
    996 // All calls clobber the link register and the non-callee-saved registers:
    997 Defs = [R0, R1, R2, R3, R11, LR], Uses = [SP] in {
    998 def BLA_1r : _F1R<0b001000, (outs), (ins GRRegs:$a),
    999                  "bla $a",
   1000                  [(XCoreBranchLink GRRegs:$a)]>;
   1001 }
   1002 
   1003 def SYNCR_1r : _F1R<0b100001, (outs), (ins GRRegs:$a),
   1004                  "syncr res[$a]",
   1005                  [(int_xcore_syncr GRRegs:$a)]>;
   1006 
   1007 def FREER_1r : _F1R<0b000100, (outs), (ins GRRegs:$a),
   1008                "freer res[$a]",
   1009                [(int_xcore_freer GRRegs:$a)]>;
   1010 
   1011 let Uses=[R11] in {
   1012 def SETV_1r : _F1R<0b010001, (outs), (ins GRRegs:$a),
   1013                    "setv res[$a], r11",
   1014                    [(int_xcore_setv GRRegs:$a, R11)]>;
   1015 
   1016 def SETEV_1r : _F1R<0b001111, (outs), (ins GRRegs:$a),
   1017                     "setev res[$a], r11",
   1018                     [(int_xcore_setev GRRegs:$a, R11)]>;
   1019 }
   1020 
   1021 def DGETREG_1r : _F1R<0b001110, (outs GRRegs:$a), (ins), "dgetreg $a", []>;
   1022 
   1023 def EDU_1r : _F1R<0b000000, (outs), (ins GRRegs:$a), "edu res[$a]",
   1024                   [(int_xcore_edu GRRegs:$a)]>;
   1025 
   1026 def EEU_1r : _F1R<0b000001, (outs), (ins GRRegs:$a),
   1027                "eeu res[$a]",
   1028                [(int_xcore_eeu GRRegs:$a)]>;
   1029 
   1030 def KCALL_1r : _F1R<0b010000, (outs), (ins GRRegs:$a), "kcall $a", []>;
   1031 
   1032 def WAITEF_1R : _F1R<0b000011, (outs), (ins GRRegs:$a), "waitef $a", []>;
   1033 
   1034 def WAITET_1R : _F1R<0b000010, (outs), (ins GRRegs:$a), "waitet $a", []>;
   1035 
   1036 def TSTART_1R : _F1R<0b000110, (outs), (ins GRRegs:$a), "start t[$a]", []>;
   1037 
   1038 def CLRPT_1R : _F1R<0b100000, (outs), (ins GRRegs:$a), "clrpt res[$a]",
   1039                     [(int_xcore_clrpt GRRegs:$a)]>;
   1040 
   1041 // Zero operand short
   1042 
   1043 def CLRE_0R : _F0R<0b0000001101, (outs), (ins), "clre", [(int_xcore_clre)]>;
   1044 
   1045 def DCALL_0R : _F0R<0b0000011100, (outs), (ins), "dcall", []>;
   1046 
   1047 let Defs = [SP], Uses = [SP] in
   1048 def DENTSP_0R : _F0R<0b0001001100, (outs), (ins), "dentsp", []>;
   1049 
   1050 let Defs = [SP] in
   1051 def DRESTSP_0R : _F0R<0b0001001101, (outs), (ins), "drestsp", []>;
   1052 
   1053 def DRET_0R : _F0R<0b0000011110, (outs), (ins), "dret", []>;
   1054 
   1055 def FREET_0R : _F0R<0b0000001111, (outs), (ins), "freet", []>;
   1056 
   1057 let Defs = [R11] in {
   1058 def GETID_0R : _F0R<0b0001001110, (outs), (ins),
   1059                     "get r11, id",
   1060                     [(set R11, (int_xcore_getid))]>;
   1061 
   1062 def GETED_0R : _F0R<0b0000111110, (outs), (ins),
   1063                     "get r11, ed",
   1064                     [(set R11, (int_xcore_geted))]>;
   1065 
   1066 def GETET_0R : _F0R<0b0000111111, (outs), (ins),
   1067                     "get r11, et",
   1068                     [(set R11, (int_xcore_getet))]>;
   1069 
   1070 def GETKEP_0R : _F0R<0b0001001111, (outs), (ins),
   1071                      "get r11, kep", []>;
   1072 
   1073 def GETKSP_0R : _F0R<0b0001011100, (outs), (ins),
   1074                      "get r11, ksp", []>;
   1075 }
   1076 
   1077 let Defs = [SP] in
   1078 def KRET_0R : _F0R<0b0000011101, (outs), (ins), "kret", []>;
   1079 
   1080 let Uses = [SP], mayLoad = 1 in {
   1081 def LDET_0R : _F0R<0b0001011110, (outs), (ins), "ldw et, sp[4]", []>;
   1082 
   1083 def LDSED_0R : _F0R<0b0001011101, (outs), (ins), "ldw sed, sp[3]", []>;
   1084 
   1085 def LDSPC_0R : _F0R<0b0000101100, (outs), (ins), "ldw spc, sp[1]", []>;
   1086 
   1087 def LDSSR_0R : _F0R<0b0000101110, (outs), (ins), "ldw ssr, sp[2]", []>;
   1088 }
   1089 
   1090 let Uses=[R11] in
   1091 def SETKEP_0R : _F0R<0b0000011111, (outs), (ins), "set kep, r11", []>;
   1092 
   1093 def SSYNC_0r : _F0R<0b0000001110, (outs), (ins),
   1094                     "ssync",
   1095                     [(int_xcore_ssync)]>;
   1096 
   1097 let Uses = [SP], mayStore = 1 in {
   1098 def STET_0R : _F0R<0b0000111101, (outs), (ins), "stw et, sp[4]", []>;
   1099 
   1100 def STSED_0R : _F0R<0b0000111100, (outs), (ins), "stw sed, sp[3]", []>;
   1101 
   1102 def STSPC_0R : _F0R<0b0000101101, (outs), (ins), "stw spc, sp[1]", []>;
   1103 
   1104 def STSSR_0R : _F0R<0b0000101111, (outs), (ins), "stw ssr, sp[2]", []>;
   1105 }
   1106 
   1107 let isBranch=1, isIndirectBranch=1, isTerminator=1, isBarrier = 1,
   1108     hasSideEffects = 1 in
   1109 def WAITEU_0R : _F0R<0b0000001100, (outs), (ins),
   1110                      "waiteu",
   1111                      [(brind (int_xcore_waitevent))]>;
   1112 
   1113 //===----------------------------------------------------------------------===//
   1114 // Non-Instruction Patterns
   1115 //===----------------------------------------------------------------------===//
   1116 
   1117 def : Pat<(XCoreBranchLink texternalsym:$addr), (BLRF_lu10 texternalsym:$addr)>;
   1118 
   1119 /// sext_inreg
   1120 def : Pat<(sext_inreg GRRegs:$b, i1), (SEXT_rus GRRegs:$b, 1)>;
   1121 def : Pat<(sext_inreg GRRegs:$b, i8), (SEXT_rus GRRegs:$b, 8)>;
   1122 def : Pat<(sext_inreg GRRegs:$b, i16), (SEXT_rus GRRegs:$b, 16)>;
   1123 
   1124 /// loads
   1125 def : Pat<(zextloadi8 (add GRRegs:$addr, GRRegs:$offset)),
   1126           (LD8U_3r GRRegs:$addr, GRRegs:$offset)>;
   1127 def : Pat<(zextloadi8 GRRegs:$addr), (LD8U_3r GRRegs:$addr, (LDC_ru6 0))>;
   1128 
   1129 def : Pat<(sextloadi16 (lda16f GRRegs:$addr, GRRegs:$offset)),
   1130           (LD16S_3r GRRegs:$addr, GRRegs:$offset)>;
   1131 def : Pat<(sextloadi16 GRRegs:$addr), (LD16S_3r GRRegs:$addr, (LDC_ru6 0))>;
   1132 
   1133 def : Pat<(load (ldawf GRRegs:$addr, GRRegs:$offset)),
   1134           (LDW_3r GRRegs:$addr, GRRegs:$offset)>;
   1135 def : Pat<(load (add GRRegs:$addr, immUs4:$offset)),
   1136           (LDW_2rus GRRegs:$addr, (div4_xform immUs4:$offset))>;
   1137 def : Pat<(load GRRegs:$addr), (LDW_2rus GRRegs:$addr, 0)>;
   1138 
   1139 /// anyext
   1140 def : Pat<(extloadi8 (add GRRegs:$addr, GRRegs:$offset)),
   1141           (LD8U_3r GRRegs:$addr, GRRegs:$offset)>;
   1142 def : Pat<(extloadi8 GRRegs:$addr), (LD8U_3r GRRegs:$addr, (LDC_ru6 0))>;
   1143 def : Pat<(extloadi16 (lda16f GRRegs:$addr, GRRegs:$offset)),
   1144           (LD16S_3r GRRegs:$addr, GRRegs:$offset)>;
   1145 def : Pat<(extloadi16 GRRegs:$addr), (LD16S_3r GRRegs:$addr, (LDC_ru6 0))>;
   1146 
   1147 /// stores
   1148 def : Pat<(truncstorei8 GRRegs:$val, (add GRRegs:$addr, GRRegs:$offset)),
   1149           (ST8_l3r GRRegs:$val, GRRegs:$addr, GRRegs:$offset)>;
   1150 def : Pat<(truncstorei8 GRRegs:$val, GRRegs:$addr),
   1151           (ST8_l3r GRRegs:$val, GRRegs:$addr, (LDC_ru6 0))>;
   1152           
   1153 def : Pat<(truncstorei16 GRRegs:$val, (lda16f GRRegs:$addr, GRRegs:$offset)),
   1154           (ST16_l3r GRRegs:$val, GRRegs:$addr, GRRegs:$offset)>;
   1155 def : Pat<(truncstorei16 GRRegs:$val, GRRegs:$addr),
   1156           (ST16_l3r GRRegs:$val, GRRegs:$addr, (LDC_ru6 0))>;
   1157 
   1158 def : Pat<(store GRRegs:$val, (ldawf GRRegs:$addr, GRRegs:$offset)),
   1159           (STW_l3r GRRegs:$val, GRRegs:$addr, GRRegs:$offset)>;
   1160 def : Pat<(store GRRegs:$val, (add GRRegs:$addr, immUs4:$offset)),
   1161           (STW_2rus GRRegs:$val, GRRegs:$addr, (div4_xform immUs4:$offset))>;
   1162 def : Pat<(store GRRegs:$val, GRRegs:$addr),
   1163           (STW_2rus GRRegs:$val, GRRegs:$addr, 0)>;
   1164 
   1165 /// cttz
   1166 def : Pat<(cttz GRRegs:$src), (CLZ_l2r (BITREV_l2r GRRegs:$src))>;
   1167 
   1168 /// trap
   1169 def : Pat<(trap), (ECALLF_1r (LDC_ru6 0))>;
   1170 
   1171 ///
   1172 /// branch patterns
   1173 ///
   1174 
   1175 // unconditional branch
   1176 def : Pat<(br bb:$addr), (BRFU_lu6 bb:$addr)>;
   1177 
   1178 // direct match equal/notequal zero brcond
   1179 def : Pat<(brcond (setne GRRegs:$lhs, 0), bb:$dst),
   1180           (BRFT_lru6 GRRegs:$lhs, bb:$dst)>;
   1181 def : Pat<(brcond (seteq GRRegs:$lhs, 0), bb:$dst),
   1182           (BRFF_lru6 GRRegs:$lhs, bb:$dst)>;
   1183 
   1184 def : Pat<(brcond (setle GRRegs:$lhs, GRRegs:$rhs), bb:$dst),
   1185           (BRFF_lru6 (LSS_3r GRRegs:$rhs, GRRegs:$lhs), bb:$dst)>;
   1186 def : Pat<(brcond (setule GRRegs:$lhs, GRRegs:$rhs), bb:$dst),
   1187           (BRFF_lru6 (LSU_3r GRRegs:$rhs, GRRegs:$lhs), bb:$dst)>;
   1188 def : Pat<(brcond (setge GRRegs:$lhs, GRRegs:$rhs), bb:$dst),
   1189           (BRFF_lru6 (LSS_3r GRRegs:$lhs, GRRegs:$rhs), bb:$dst)>;
   1190 def : Pat<(brcond (setuge GRRegs:$lhs, GRRegs:$rhs), bb:$dst),
   1191           (BRFF_lru6 (LSU_3r GRRegs:$lhs, GRRegs:$rhs), bb:$dst)>;
   1192 def : Pat<(brcond (setne GRRegs:$lhs, GRRegs:$rhs), bb:$dst),
   1193           (BRFF_lru6 (EQ_3r GRRegs:$lhs, GRRegs:$rhs), bb:$dst)>;
   1194 def : Pat<(brcond (setne GRRegs:$lhs, immUs:$rhs), bb:$dst),
   1195           (BRFF_lru6 (EQ_2rus GRRegs:$lhs, immUs:$rhs), bb:$dst)>;
   1196 
   1197 // generic brcond pattern
   1198 def : Pat<(brcond GRRegs:$cond, bb:$addr), (BRFT_lru6 GRRegs:$cond, bb:$addr)>;
   1199 
   1200 
   1201 ///
   1202 /// Select patterns
   1203 ///
   1204 
   1205 // direct match equal/notequal zero select
   1206 def : Pat<(select (setne GRRegs:$lhs, 0), GRRegs:$T, GRRegs:$F),
   1207         (SELECT_CC GRRegs:$lhs, GRRegs:$T, GRRegs:$F)>;
   1208 
   1209 def : Pat<(select (seteq GRRegs:$lhs, 0), GRRegs:$T, GRRegs:$F),
   1210         (SELECT_CC GRRegs:$lhs, GRRegs:$F, GRRegs:$T)>;
   1211 
   1212 def : Pat<(select (setle GRRegs:$lhs, GRRegs:$rhs), GRRegs:$T, GRRegs:$F),
   1213           (SELECT_CC (LSS_3r GRRegs:$rhs, GRRegs:$lhs), GRRegs:$F, GRRegs:$T)>;
   1214 def : Pat<(select (setule GRRegs:$lhs, GRRegs:$rhs), GRRegs:$T, GRRegs:$F),
   1215           (SELECT_CC (LSU_3r GRRegs:$rhs, GRRegs:$lhs), GRRegs:$F, GRRegs:$T)>;
   1216 def : Pat<(select (setge GRRegs:$lhs, GRRegs:$rhs), GRRegs:$T, GRRegs:$F),
   1217           (SELECT_CC (LSS_3r GRRegs:$lhs, GRRegs:$rhs), GRRegs:$F, GRRegs:$T)>;
   1218 def : Pat<(select (setuge GRRegs:$lhs, GRRegs:$rhs), GRRegs:$T, GRRegs:$F),
   1219           (SELECT_CC (LSU_3r GRRegs:$lhs, GRRegs:$rhs), GRRegs:$F, GRRegs:$T)>;
   1220 def : Pat<(select (setne GRRegs:$lhs, GRRegs:$rhs), GRRegs:$T, GRRegs:$F),
   1221           (SELECT_CC (EQ_3r GRRegs:$lhs, GRRegs:$rhs), GRRegs:$F, GRRegs:$T)>;
   1222 def : Pat<(select (setne GRRegs:$lhs, immUs:$rhs), GRRegs:$T, GRRegs:$F),
   1223           (SELECT_CC (EQ_2rus GRRegs:$lhs, immUs:$rhs), GRRegs:$F, GRRegs:$T)>;
   1224 
   1225 ///
   1226 /// setcc patterns, only matched when none of the above brcond
   1227 /// patterns match
   1228 ///
   1229 
   1230 // setcc 2 register operands
   1231 def : Pat<(setle GRRegs:$lhs, GRRegs:$rhs),
   1232           (EQ_2rus (LSS_3r GRRegs:$rhs, GRRegs:$lhs), 0)>;
   1233 def : Pat<(setule GRRegs:$lhs, GRRegs:$rhs),
   1234           (EQ_2rus (LSU_3r GRRegs:$rhs, GRRegs:$lhs), 0)>;
   1235 
   1236 def : Pat<(setgt GRRegs:$lhs, GRRegs:$rhs),
   1237           (LSS_3r GRRegs:$rhs, GRRegs:$lhs)>;
   1238 def : Pat<(setugt GRRegs:$lhs, GRRegs:$rhs),
   1239           (LSU_3r GRRegs:$rhs, GRRegs:$lhs)>;
   1240 
   1241 def : Pat<(setge GRRegs:$lhs, GRRegs:$rhs),
   1242           (EQ_2rus (LSS_3r GRRegs:$lhs, GRRegs:$rhs), 0)>;
   1243 def : Pat<(setuge GRRegs:$lhs, GRRegs:$rhs),
   1244           (EQ_2rus (LSU_3r GRRegs:$lhs, GRRegs:$rhs), 0)>;
   1245 
   1246 def : Pat<(setlt GRRegs:$lhs, GRRegs:$rhs),
   1247           (LSS_3r GRRegs:$lhs, GRRegs:$rhs)>;
   1248 def : Pat<(setult GRRegs:$lhs, GRRegs:$rhs),
   1249           (LSU_3r GRRegs:$lhs, GRRegs:$rhs)>;
   1250 
   1251 def : Pat<(setne GRRegs:$lhs, GRRegs:$rhs),
   1252           (EQ_2rus (EQ_3r GRRegs:$lhs, GRRegs:$rhs), 0)>;
   1253 
   1254 def : Pat<(seteq GRRegs:$lhs, GRRegs:$rhs),
   1255           (EQ_3r GRRegs:$lhs, GRRegs:$rhs)>;
   1256 
   1257 // setcc reg/imm operands
   1258 def : Pat<(seteq GRRegs:$lhs, immUs:$rhs),
   1259           (EQ_2rus GRRegs:$lhs, immUs:$rhs)>;
   1260 def : Pat<(setne GRRegs:$lhs, immUs:$rhs),
   1261           (EQ_2rus (EQ_2rus GRRegs:$lhs, immUs:$rhs), 0)>;
   1262 
   1263 // misc
   1264 def : Pat<(add GRRegs:$addr, immUs4:$offset),
   1265           (LDAWF_l2rus GRRegs:$addr, (div4_xform immUs4:$offset))>;
   1266 
   1267 def : Pat<(sub GRRegs:$addr, immUs4:$offset),
   1268           (LDAWB_l2rus GRRegs:$addr, (div4_xform immUs4:$offset))>;
   1269 
   1270 def : Pat<(and GRRegs:$val, immMskBitp:$mask),
   1271           (ZEXT_rus GRRegs:$val, (msksize_xform immMskBitp:$mask))>;
   1272 
   1273 // (sub X, imm) gets canonicalized to (add X, -imm).  Match this form.
   1274 def : Pat<(add GRRegs:$src1, immUsNeg:$src2),
   1275           (SUB_2rus GRRegs:$src1, (neg_xform immUsNeg:$src2))>;
   1276 
   1277 def : Pat<(add GRRegs:$src1, immUs4Neg:$src2),
   1278           (LDAWB_l2rus GRRegs:$src1, (div4neg_xform immUs4Neg:$src2))>;
   1279 
   1280 ///
   1281 /// Some peepholes
   1282 ///
   1283 
   1284 def : Pat<(mul GRRegs:$src, 3),
   1285           (LDA16F_l3r GRRegs:$src, GRRegs:$src)>;
   1286 
   1287 def : Pat<(mul GRRegs:$src, 5),
   1288           (LDAWF_l3r GRRegs:$src, GRRegs:$src)>;
   1289 
   1290 def : Pat<(mul GRRegs:$src, -3),
   1291           (LDAWB_l3r GRRegs:$src, GRRegs:$src)>;
   1292 
   1293 // ashr X, 32 is equivalent to ashr X, 31 on the XCore.
   1294 def : Pat<(sra GRRegs:$src, 31),
   1295           (ASHR_l2rus GRRegs:$src, 32)>;
   1296 
   1297 def : Pat<(brcond (setlt GRRegs:$lhs, 0), bb:$dst),
   1298           (BRFT_lru6 (ASHR_l2rus GRRegs:$lhs, 32), bb:$dst)>;
   1299 
   1300 // setge X, 0 is canonicalized to setgt X, -1
   1301 def : Pat<(brcond (setgt GRRegs:$lhs, -1), bb:$dst),
   1302           (BRFF_lru6 (ASHR_l2rus GRRegs:$lhs, 32), bb:$dst)>;
   1303 
   1304 def : Pat<(select (setlt GRRegs:$lhs, 0), GRRegs:$T, GRRegs:$F),
   1305           (SELECT_CC (ASHR_l2rus GRRegs:$lhs, 32), GRRegs:$T, GRRegs:$F)>;
   1306 
   1307 def : Pat<(select (setgt GRRegs:$lhs, -1), GRRegs:$T, GRRegs:$F),
   1308           (SELECT_CC (ASHR_l2rus GRRegs:$lhs, 32), GRRegs:$F, GRRegs:$T)>;
   1309 
   1310 def : Pat<(setgt GRRegs:$lhs, -1),
   1311           (EQ_2rus (ASHR_l2rus GRRegs:$lhs, 32), 0)>;
   1312 
   1313 def : Pat<(sra (shl GRRegs:$src, immBpwSubBitp:$imm), immBpwSubBitp:$imm),
   1314           (SEXT_rus GRRegs:$src, (bpwsub_xform immBpwSubBitp:$imm))>;
   1315 
   1316 def : Pat<(load (cprelwrapper tconstpool:$b)),
   1317           (LDWCP_lru6 tconstpool:$b)>;
   1318 
   1319 def : Pat<(cprelwrapper tconstpool:$b),
   1320           (LDAWCP_lu6 tconstpool:$b)>;
   1321