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