Home | History | Annotate | Download | only in Hexagon
      1 //=- HexagonInstrInfoV4.td - Target Desc. for Hexagon Target -*- tablegen -*-=//
      2 //
      3 //                     The LLVM Compiler Infrastructure
      4 //
      5 // This file is distributed under the University of Illinois Open Source
      6 // License. See LICENSE.TXT for details.
      7 //
      8 //===----------------------------------------------------------------------===//
      9 //
     10 // This file describes the Hexagon V4 instructions in TableGen format.
     11 //
     12 //===----------------------------------------------------------------------===//
     13 
     14 def DuplexIClass0:  InstDuplex < 0 >;
     15 def DuplexIClass1:  InstDuplex < 1 >;
     16 def DuplexIClass2:  InstDuplex < 2 >;
     17 let isExtendable = 1 in {
     18   def DuplexIClass3:  InstDuplex < 3 >;
     19   def DuplexIClass4:  InstDuplex < 4 >;
     20   def DuplexIClass5:  InstDuplex < 5 >;
     21   def DuplexIClass6:  InstDuplex < 6 >;
     22   def DuplexIClass7:  InstDuplex < 7 >;
     23 }
     24 def DuplexIClass8:  InstDuplex < 8 >;
     25 def DuplexIClass9:  InstDuplex < 9 >;
     26 def DuplexIClassA:  InstDuplex < 0xA >;
     27 def DuplexIClassB:  InstDuplex < 0xB >;
     28 def DuplexIClassC:  InstDuplex < 0xC >;
     29 def DuplexIClassD:  InstDuplex < 0xD >;
     30 def DuplexIClassE:  InstDuplex < 0xE >;
     31 def DuplexIClassF:  InstDuplex < 0xF >;
     32 
     33 def addrga: PatLeaf<(i32 AddrGA:$Addr)>;
     34 def addrgp: PatLeaf<(i32 AddrGP:$Addr)>;
     35 
     36 let hasSideEffects = 0 in
     37 class T_Immext<Operand ImmType>
     38   : EXTENDERInst<(outs), (ins ImmType:$imm),
     39                  "immext(#$imm)", []> {
     40     bits<32> imm;
     41     let IClass = 0b0000;
     42 
     43     let Inst{27-16} = imm{31-20};
     44     let Inst{13-0} = imm{19-6};
     45   }
     46 
     47 def A4_ext : T_Immext<u26_6Imm>;
     48 let isCodeGenOnly = 1 in {
     49   let isBranch = 1 in
     50     def A4_ext_b : T_Immext<brtarget>;
     51   let isCall = 1 in
     52     def A4_ext_c : T_Immext<calltarget>;
     53   def A4_ext_g : T_Immext<globaladdress>;
     54 }
     55 
     56 def BITPOS32 : SDNodeXForm<imm, [{
     57    // Return the bit position we will set [0-31].
     58    // As an SDNode.
     59    int32_t imm = N->getSExtValue();
     60    return XformMskToBitPosU5Imm(imm, SDLoc(N));
     61 }]>;
     62 
     63 
     64 // Hexagon V4 Architecture spec defines 8 instruction classes:
     65 // LD ST ALU32 XTYPE J JR MEMOP NV CR SYSTEM(system is not implemented in the
     66 // compiler)
     67 
     68 // LD Instructions:
     69 // ========================================
     70 // Loads (8/16/32/64 bit)
     71 // Deallocframe
     72 
     73 // ST Instructions:
     74 // ========================================
     75 // Stores (8/16/32/64 bit)
     76 // Allocframe
     77 
     78 // ALU32 Instructions:
     79 // ========================================
     80 // Arithmetic / Logical (32 bit)
     81 // Vector Halfword
     82 
     83 // XTYPE Instructions (32/64 bit):
     84 // ========================================
     85 // Arithmetic, Logical, Bit Manipulation
     86 // Multiply (Integer, Fractional, Complex)
     87 // Permute / Vector Permute Operations
     88 // Predicate Operations
     89 // Shift / Shift with Add/Sub/Logical
     90 // Vector Byte ALU
     91 // Vector Halfword (ALU, Shift, Multiply)
     92 // Vector Word (ALU, Shift)
     93 
     94 // J Instructions:
     95 // ========================================
     96 // Jump/Call PC-relative
     97 
     98 // JR Instructions:
     99 // ========================================
    100 // Jump/Call Register
    101 
    102 // MEMOP Instructions:
    103 // ========================================
    104 // Operation on memory (8/16/32 bit)
    105 
    106 // NV Instructions:
    107 // ========================================
    108 // New-value Jumps
    109 // New-value Stores
    110 
    111 // CR Instructions:
    112 // ========================================
    113 // Control-Register Transfers
    114 // Hardware Loop Setup
    115 // Predicate Logicals & Reductions
    116 
    117 // SYSTEM Instructions (not implemented in the compiler):
    118 // ========================================
    119 // Prefetch
    120 // Cache Maintenance
    121 // Bus Operations
    122 
    123 
    124 //===----------------------------------------------------------------------===//
    125 // ALU32 +
    126 //===----------------------------------------------------------------------===//
    127 
    128 class T_ALU32_3op_not<string mnemonic, bits<3> MajOp, bits<3> MinOp,
    129                       bit OpsRev>
    130   : T_ALU32_3op<mnemonic, MajOp, MinOp, OpsRev, 0> {
    131   let AsmString = "$Rd = "#mnemonic#"($Rs, ~$Rt)";
    132 }
    133 
    134 let BaseOpcode = "andn_rr", CextOpcode = "andn" in
    135 def A4_andn    : T_ALU32_3op_not<"and", 0b001, 0b100, 1>;
    136 let BaseOpcode = "orn_rr", CextOpcode = "orn" in
    137 def A4_orn     : T_ALU32_3op_not<"or",  0b001, 0b101, 1>;
    138 
    139 let CextOpcode = "rcmp.eq" in
    140 def A4_rcmpeq  : T_ALU32_3op<"cmp.eq",  0b011, 0b010, 0, 1>;
    141 let CextOpcode = "!rcmp.eq" in
    142 def A4_rcmpneq : T_ALU32_3op<"!cmp.eq", 0b011, 0b011, 0, 1>;
    143 
    144 def C4_cmpneq  : T_ALU32_3op_cmp<"!cmp.eq",  0b00, 1, 1>;
    145 def C4_cmplte  : T_ALU32_3op_cmp<"!cmp.gt",  0b10, 1, 0>;
    146 def C4_cmplteu : T_ALU32_3op_cmp<"!cmp.gtu", 0b11, 1, 0>;
    147 
    148 // Pats for instruction selection.
    149 
    150 // A class to embed the usual comparison patfrags within a zext to i32.
    151 // The seteq/setne frags use "lhs" and "rhs" as operands, so use the same
    152 // names, or else the frag's "body" won't match the operands.
    153 class CmpInReg<PatFrag Op>
    154   : PatFrag<(ops node:$lhs, node:$rhs),(i32 (zext (i1 Op.Fragment)))>;
    155 
    156 def: T_cmp32_rr_pat<A4_rcmpeq,  CmpInReg<seteq>, i32>;
    157 def: T_cmp32_rr_pat<A4_rcmpneq, CmpInReg<setne>, i32>;
    158 
    159 def: T_cmp32_rr_pat<C4_cmpneq,  setne,  i1>;
    160 def: T_cmp32_rr_pat<C4_cmplteu, setule, i1>;
    161 
    162 def: T_cmp32_rr_pat<C4_cmplteu, RevCmp<setuge>, i1>;
    163 
    164 class T_CMP_rrbh<string mnemonic, bits<3> MinOp, bit IsComm>
    165   : SInst<(outs PredRegs:$Pd), (ins IntRegs:$Rs, IntRegs:$Rt),
    166     "$Pd = "#mnemonic#"($Rs, $Rt)", [], "", S_3op_tc_2early_SLOT23>,
    167     ImmRegRel {
    168   let InputType = "reg";
    169   let CextOpcode = mnemonic;
    170   let isCompare = 1;
    171   let isCommutable = IsComm;
    172   let hasSideEffects = 0;
    173 
    174   bits<2> Pd;
    175   bits<5> Rs;
    176   bits<5> Rt;
    177 
    178   let IClass = 0b1100;
    179   let Inst{27-21} = 0b0111110;
    180   let Inst{20-16} = Rs;
    181   let Inst{12-8} = Rt;
    182   let Inst{7-5} = MinOp;
    183   let Inst{1-0} = Pd;
    184 }
    185 
    186 def A4_cmpbeq  : T_CMP_rrbh<"cmpb.eq",  0b110, 1>;
    187 def A4_cmpbgt  : T_CMP_rrbh<"cmpb.gt",  0b010, 0>;
    188 def A4_cmpbgtu : T_CMP_rrbh<"cmpb.gtu", 0b111, 0>;
    189 def A4_cmpheq  : T_CMP_rrbh<"cmph.eq",  0b011, 1>;
    190 def A4_cmphgt  : T_CMP_rrbh<"cmph.gt",  0b100, 0>;
    191 def A4_cmphgtu : T_CMP_rrbh<"cmph.gtu", 0b101, 0>;
    192 
    193 let AddedComplexity = 100 in {
    194   def: Pat<(i1 (seteq (and (xor (i32 IntRegs:$Rs), (i32 IntRegs:$Rt)),
    195                        255), 0)),
    196            (A4_cmpbeq IntRegs:$Rs, IntRegs:$Rt)>;
    197   def: Pat<(i1 (setne (and (xor (i32 IntRegs:$Rs), (i32 IntRegs:$Rt)),
    198                        255), 0)),
    199            (C2_not (A4_cmpbeq IntRegs:$Rs, IntRegs:$Rt))>;
    200   def: Pat<(i1 (seteq (and (xor (i32 IntRegs:$Rs), (i32 IntRegs:$Rt)),
    201                            65535), 0)),
    202            (A4_cmpheq IntRegs:$Rs, IntRegs:$Rt)>;
    203   def: Pat<(i1 (setne (and (xor (i32 IntRegs:$Rs), (i32 IntRegs:$Rt)),
    204                            65535), 0)),
    205            (C2_not (A4_cmpheq IntRegs:$Rs, IntRegs:$Rt))>;
    206 }
    207 
    208 class T_CMP_ribh<string mnemonic, bits<2> MajOp, bit IsHalf, bit IsComm,
    209                  Operand ImmType, bit IsImmExt, bit IsImmSigned, int ImmBits>
    210   : ALU64Inst<(outs PredRegs:$Pd), (ins IntRegs:$Rs, ImmType:$Imm),
    211     "$Pd = "#mnemonic#"($Rs, #$Imm)", [], "", ALU64_tc_2early_SLOT23>,
    212     ImmRegRel {
    213   let InputType = "imm";
    214   let CextOpcode = mnemonic;
    215   let isCompare = 1;
    216   let isCommutable = IsComm;
    217   let hasSideEffects = 0;
    218   let isExtendable = IsImmExt;
    219   let opExtendable = !if (IsImmExt, 2, 0);
    220   let isExtentSigned = IsImmSigned;
    221   let opExtentBits = ImmBits;
    222 
    223   bits<2> Pd;
    224   bits<5> Rs;
    225   bits<8> Imm;
    226 
    227   let IClass = 0b1101;
    228   let Inst{27-24} = 0b1101;
    229   let Inst{22-21} = MajOp;
    230   let Inst{20-16} = Rs;
    231   let Inst{12-5} = Imm;
    232   let Inst{4} = 0b0;
    233   let Inst{3} = IsHalf;
    234   let Inst{1-0} = Pd;
    235 }
    236 
    237 def A4_cmpbeqi  : T_CMP_ribh<"cmpb.eq",  0b00, 0, 1, u8Imm, 0, 0, 8>;
    238 def A4_cmpbgti  : T_CMP_ribh<"cmpb.gt",  0b01, 0, 0, s8Imm, 0, 1, 8>;
    239 def A4_cmpbgtui : T_CMP_ribh<"cmpb.gtu", 0b10, 0, 0, u7Ext, 1, 0, 7>;
    240 def A4_cmpheqi  : T_CMP_ribh<"cmph.eq",  0b00, 1, 1, s8Ext, 1, 1, 8>;
    241 def A4_cmphgti  : T_CMP_ribh<"cmph.gt",  0b01, 1, 0, s8Ext, 1, 1, 8>;
    242 def A4_cmphgtui : T_CMP_ribh<"cmph.gtu", 0b10, 1, 0, u7Ext, 1, 0, 7>;
    243 
    244 class T_RCMP_EQ_ri<string mnemonic, bit IsNeg>
    245   : ALU32_ri<(outs IntRegs:$Rd), (ins IntRegs:$Rs, s8Ext:$s8),
    246     "$Rd = "#mnemonic#"($Rs, #$s8)", [], "", ALU32_2op_tc_1_SLOT0123>,
    247     ImmRegRel {
    248   let InputType = "imm";
    249   let CextOpcode = !if (IsNeg, "!rcmp.eq", "rcmp.eq");
    250   let isExtendable = 1;
    251   let opExtendable = 2;
    252   let isExtentSigned = 1;
    253   let opExtentBits = 8;
    254   let hasNewValue = 1;
    255 
    256   bits<5> Rd;
    257   bits<5> Rs;
    258   bits<8> s8;
    259 
    260   let IClass = 0b0111;
    261   let Inst{27-24} = 0b0011;
    262   let Inst{22} = 0b1;
    263   let Inst{21} = IsNeg;
    264   let Inst{20-16} = Rs;
    265   let Inst{13} = 0b1;
    266   let Inst{12-5} = s8;
    267   let Inst{4-0} = Rd;
    268 }
    269 
    270 def A4_rcmpeqi  : T_RCMP_EQ_ri<"cmp.eq",  0>;
    271 def A4_rcmpneqi : T_RCMP_EQ_ri<"!cmp.eq", 1>;
    272 
    273 def: Pat<(i32 (zext (i1 (seteq (i32 IntRegs:$Rs), s32ImmPred:$s8)))),
    274          (A4_rcmpeqi IntRegs:$Rs, s32ImmPred:$s8)>;
    275 def: Pat<(i32 (zext (i1 (setne (i32 IntRegs:$Rs), s32ImmPred:$s8)))),
    276          (A4_rcmpneqi IntRegs:$Rs, s32ImmPred:$s8)>;
    277 
    278 // Preserve the S2_tstbit_r generation
    279 def: Pat<(i32 (zext (i1 (setne (i32 (and (i32 (shl 1, (i32 IntRegs:$src2))),
    280                                          (i32 IntRegs:$src1))), 0)))),
    281          (C2_muxii (S2_tstbit_r IntRegs:$src1, IntRegs:$src2), 1, 0)>;
    282 
    283 //===----------------------------------------------------------------------===//
    284 // ALU32 -
    285 //===----------------------------------------------------------------------===//
    286 
    287 
    288 //===----------------------------------------------------------------------===//
    289 // ALU32/PERM +
    290 //===----------------------------------------------------------------------===//
    291 
    292 // Combine a word and an immediate into a register pair.
    293 let hasSideEffects = 0, isExtentSigned = 1, isExtendable = 1,
    294     opExtentBits = 8 in
    295 class T_Combine1 <bits<2> MajOp, dag ins, string AsmStr>
    296   : ALU32Inst <(outs DoubleRegs:$Rdd), ins, AsmStr> {
    297     bits<5> Rdd;
    298     bits<5> Rs;
    299     bits<8> s8;
    300 
    301     let IClass      = 0b0111;
    302     let Inst{27-24} = 0b0011;
    303     let Inst{22-21} = MajOp;
    304     let Inst{20-16} = Rs;
    305     let Inst{13}    = 0b1;
    306     let Inst{12-5}  = s8;
    307     let Inst{4-0}   = Rdd;
    308   }
    309 
    310 let opExtendable = 2 in
    311 def A4_combineri : T_Combine1<0b00, (ins IntRegs:$Rs, s8Ext:$s8),
    312                                     "$Rdd = combine($Rs, #$s8)">;
    313 
    314 let opExtendable = 1 in
    315 def A4_combineir : T_Combine1<0b01, (ins s8Ext:$s8, IntRegs:$Rs),
    316                                     "$Rdd = combine(#$s8, $Rs)">;
    317 
    318 // The complexity of the combines involving immediates should be greater
    319 // than the complexity of the combine with two registers.
    320 let AddedComplexity = 50 in {
    321 def: Pat<(HexagonCOMBINE IntRegs:$r, s32ImmPred:$i),
    322          (A4_combineri IntRegs:$r, s32ImmPred:$i)>;
    323 
    324 def: Pat<(HexagonCOMBINE s32ImmPred:$i, IntRegs:$r),
    325          (A4_combineir s32ImmPred:$i, IntRegs:$r)>;
    326 }
    327 
    328 // A4_combineii: Set two small immediates.
    329 let hasSideEffects = 0, isExtendable = 1, opExtentBits = 6, opExtendable = 2 in
    330 def A4_combineii: ALU32Inst<(outs DoubleRegs:$Rdd), (ins s8Imm:$s8, u6Ext:$U6),
    331   "$Rdd = combine(#$s8, #$U6)"> {
    332     bits<5> Rdd;
    333     bits<8> s8;
    334     bits<6> U6;
    335 
    336     let IClass = 0b0111;
    337     let Inst{27-23} = 0b11001;
    338     let Inst{20-16} = U6{5-1};
    339     let Inst{13}    = U6{0};
    340     let Inst{12-5}  = s8;
    341     let Inst{4-0}   = Rdd;
    342   }
    343 
    344 // The complexity of the combine with two immediates should be greater than
    345 // the complexity of a combine involving a register.
    346 let AddedComplexity = 75 in
    347 def: Pat<(HexagonCOMBINE s8ImmPred:$s8, u32ImmPred:$u6),
    348          (A4_combineii imm:$s8, imm:$u6)>;
    349 
    350 //===----------------------------------------------------------------------===//
    351 // ALU32/PERM -
    352 //===----------------------------------------------------------------------===//
    353 
    354 //===----------------------------------------------------------------------===//
    355 // LD +
    356 //===----------------------------------------------------------------------===//
    357 
    358 def Zext64: OutPatFrag<(ops node:$Rs),
    359   (i64 (A4_combineir 0, (i32 $Rs)))>;
    360 def Sext64: OutPatFrag<(ops node:$Rs),
    361   (i64 (A2_sxtw (i32 $Rs)))>;
    362 
    363 // Patterns to generate indexed loads with different forms of the address:
    364 // - frameindex,
    365 // - base + offset,
    366 // - base (without offset).
    367 multiclass Loadxm_pat<PatFrag Load, ValueType VT, PatFrag ValueMod,
    368                       PatLeaf ImmPred, InstHexagon MI> {
    369   def: Pat<(VT (Load AddrFI:$fi)),
    370            (VT (ValueMod (MI AddrFI:$fi, 0)))>;
    371   def: Pat<(VT (Load (add AddrFI:$fi, ImmPred:$Off))),
    372            (VT (ValueMod (MI AddrFI:$fi, imm:$Off)))>;
    373   def: Pat<(VT (Load (add IntRegs:$Rs, ImmPred:$Off))),
    374            (VT (ValueMod (MI IntRegs:$Rs, imm:$Off)))>;
    375   def: Pat<(VT (Load (i32 IntRegs:$Rs))),
    376            (VT (ValueMod (MI IntRegs:$Rs, 0)))>;
    377 }
    378 
    379 defm: Loadxm_pat<extloadi1,   i64, Zext64, s32_0ImmPred, L2_loadrub_io>;
    380 defm: Loadxm_pat<extloadi8,   i64, Zext64, s32_0ImmPred, L2_loadrub_io>;
    381 defm: Loadxm_pat<extloadi16,  i64, Zext64, s31_1ImmPred, L2_loadruh_io>;
    382 defm: Loadxm_pat<zextloadi1,  i64, Zext64, s32_0ImmPred, L2_loadrub_io>;
    383 defm: Loadxm_pat<zextloadi8,  i64, Zext64, s32_0ImmPred, L2_loadrub_io>;
    384 defm: Loadxm_pat<zextloadi16, i64, Zext64, s31_1ImmPred, L2_loadruh_io>;
    385 defm: Loadxm_pat<sextloadi8,  i64, Sext64, s32_0ImmPred, L2_loadrb_io>;
    386 defm: Loadxm_pat<sextloadi16, i64, Sext64, s31_1ImmPred, L2_loadrh_io>;
    387 
    388 // Map Rdd = anyext(Rs) -> Rdd = combine(#0, Rs).
    389 def: Pat<(i64 (anyext (i32 IntRegs:$src1))), (Zext64 IntRegs:$src1)>;
    390 
    391 //===----------------------------------------------------------------------===//
    392 // Template class for load instructions with Absolute set addressing mode.
    393 //===----------------------------------------------------------------------===//
    394 let isExtended = 1, opExtendable = 2, opExtentBits = 6, addrMode = AbsoluteSet,
    395     hasSideEffects = 0 in
    396 class T_LD_abs_set<string mnemonic, RegisterClass RC, bits<4>MajOp>:
    397             LDInst<(outs RC:$dst1, IntRegs:$dst2),
    398             (ins u6Ext:$addr),
    399             "$dst1 = "#mnemonic#"($dst2 = #$addr)",
    400             []> {
    401   bits<7> name;
    402   bits<5> dst1;
    403   bits<5> dst2;
    404   bits<6> addr;
    405 
    406   let IClass = 0b1001;
    407   let Inst{27-25} = 0b101;
    408   let Inst{24-21} = MajOp;
    409   let Inst{13-12} = 0b01;
    410   let Inst{4-0}   = dst1;
    411   let Inst{20-16} = dst2;
    412   let Inst{11-8}  = addr{5-2};
    413   let Inst{6-5}   = addr{1-0};
    414 }
    415 
    416 let accessSize = ByteAccess, hasNewValue = 1 in {
    417   def L4_loadrb_ap   : T_LD_abs_set <"memb",   IntRegs, 0b1000>;
    418   def L4_loadrub_ap  : T_LD_abs_set <"memub",  IntRegs, 0b1001>;
    419 }
    420 
    421 let accessSize = HalfWordAccess, hasNewValue = 1 in {
    422   def L4_loadrh_ap  : T_LD_abs_set <"memh",  IntRegs, 0b1010>;
    423   def L4_loadruh_ap : T_LD_abs_set <"memuh", IntRegs, 0b1011>;
    424   def L4_loadbsw2_ap : T_LD_abs_set <"membh",  IntRegs, 0b0001>;
    425   def L4_loadbzw2_ap : T_LD_abs_set <"memubh", IntRegs, 0b0011>;
    426 }
    427 
    428 let accessSize = WordAccess, hasNewValue = 1 in
    429   def L4_loadri_ap : T_LD_abs_set <"memw", IntRegs, 0b1100>;
    430 
    431 let accessSize = WordAccess in {
    432   def L4_loadbzw4_ap : T_LD_abs_set <"memubh", DoubleRegs, 0b0101>;
    433   def L4_loadbsw4_ap : T_LD_abs_set <"membh",  DoubleRegs, 0b0111>;
    434 }
    435 
    436 let accessSize = DoubleWordAccess in
    437 def L4_loadrd_ap : T_LD_abs_set <"memd", DoubleRegs, 0b1110>;
    438 
    439 let accessSize = ByteAccess in
    440   def L4_loadalignb_ap : T_LD_abs_set <"memb_fifo", DoubleRegs, 0b0100>;
    441 
    442 let accessSize = HalfWordAccess in
    443 def L4_loadalignh_ap : T_LD_abs_set <"memh_fifo", DoubleRegs, 0b0010>;
    444 
    445 // Load - Indirect with long offset
    446 let InputType = "imm", addrMode = BaseLongOffset, isExtended = 1,
    447 opExtentBits = 6, opExtendable = 3 in
    448 class T_LoadAbsReg <string mnemonic, string CextOp, RegisterClass RC,
    449                     bits<4> MajOp>
    450   : LDInst <(outs RC:$dst), (ins IntRegs:$src1, u2Imm:$src2, u6Ext:$src3),
    451   "$dst = "#mnemonic#"($src1<<#$src2 + #$src3)",
    452   [] >, ImmRegShl {
    453     bits<5> dst;
    454     bits<5> src1;
    455     bits<2> src2;
    456     bits<6> src3;
    457     let CextOpcode = CextOp;
    458     let hasNewValue = !if (!eq(!cast<string>(RC), "DoubleRegs"), 0, 1);
    459 
    460     let IClass = 0b1001;
    461     let Inst{27-25} = 0b110;
    462     let Inst{24-21} = MajOp;
    463     let Inst{20-16} = src1;
    464     let Inst{13}    = src2{1};
    465     let Inst{12}    = 0b1;
    466     let Inst{11-8}  = src3{5-2};
    467     let Inst{7}     = src2{0};
    468     let Inst{6-5}   = src3{1-0};
    469     let Inst{4-0}   = dst;
    470   }
    471 
    472 let accessSize = ByteAccess in {
    473   def L4_loadrb_ur  : T_LoadAbsReg<"memb",  "LDrib", IntRegs, 0b1000>;
    474   def L4_loadrub_ur : T_LoadAbsReg<"memub", "LDriub", IntRegs, 0b1001>;
    475   def L4_loadalignb_ur : T_LoadAbsReg<"memb_fifo", "LDrib_fifo",
    476                                       DoubleRegs, 0b0100>;
    477 }
    478 
    479 let accessSize = HalfWordAccess in {
    480   def L4_loadrh_ur   : T_LoadAbsReg<"memh",   "LDrih",    IntRegs, 0b1010>;
    481   def L4_loadruh_ur  : T_LoadAbsReg<"memuh",  "LDriuh",   IntRegs, 0b1011>;
    482   def L4_loadbsw2_ur : T_LoadAbsReg<"membh",  "LDribh2",  IntRegs, 0b0001>;
    483   def L4_loadbzw2_ur : T_LoadAbsReg<"memubh", "LDriubh2", IntRegs, 0b0011>;
    484   def L4_loadalignh_ur : T_LoadAbsReg<"memh_fifo", "LDrih_fifo",
    485                                       DoubleRegs, 0b0010>;
    486 }
    487 
    488 let accessSize = WordAccess in {
    489   def L4_loadri_ur   : T_LoadAbsReg<"memw", "LDriw", IntRegs, 0b1100>;
    490   def L4_loadbsw4_ur : T_LoadAbsReg<"membh", "LDribh4", DoubleRegs, 0b0111>;
    491   def L4_loadbzw4_ur : T_LoadAbsReg<"memubh", "LDriubh4", DoubleRegs, 0b0101>;
    492 }
    493 
    494 let accessSize = DoubleWordAccess in
    495 def L4_loadrd_ur  : T_LoadAbsReg<"memd", "LDrid", DoubleRegs, 0b1110>;
    496 
    497 
    498 multiclass T_LoadAbsReg_Pat <PatFrag ldOp, InstHexagon MI, ValueType VT = i32> {
    499   def  : Pat <(VT (ldOp (add (shl IntRegs:$src1, u2ImmPred:$src2),
    500                              (HexagonCONST32 tglobaladdr:$src3)))),
    501               (MI IntRegs:$src1, u2ImmPred:$src2, tglobaladdr:$src3)>;
    502   def  : Pat <(VT (ldOp (add IntRegs:$src1,
    503                              (HexagonCONST32 tglobaladdr:$src2)))),
    504               (MI IntRegs:$src1, 0, tglobaladdr:$src2)>;
    505 
    506   def  : Pat <(VT (ldOp (add (shl IntRegs:$src1, u2ImmPred:$src2),
    507                              (HexagonCONST32 tconstpool:$src3)))),
    508               (MI IntRegs:$src1, u2ImmPred:$src2, tconstpool:$src3)>;
    509   def  : Pat <(VT (ldOp (add IntRegs:$src1,
    510                              (HexagonCONST32 tconstpool:$src2)))),
    511               (MI IntRegs:$src1, 0, tconstpool:$src2)>;
    512 
    513   def  : Pat <(VT (ldOp (add (shl IntRegs:$src1, u2ImmPred:$src2),
    514                              (HexagonCONST32 tjumptable:$src3)))),
    515               (MI IntRegs:$src1, u2ImmPred:$src2, tjumptable:$src3)>;
    516   def  : Pat <(VT (ldOp (add IntRegs:$src1,
    517                              (HexagonCONST32 tjumptable:$src2)))),
    518               (MI IntRegs:$src1, 0, tjumptable:$src2)>;
    519 }
    520 
    521 let AddedComplexity  = 60 in {
    522 defm : T_LoadAbsReg_Pat <sextloadi8, L4_loadrb_ur>;
    523 defm : T_LoadAbsReg_Pat <zextloadi8, L4_loadrub_ur>;
    524 defm : T_LoadAbsReg_Pat <extloadi8,  L4_loadrub_ur>;
    525 
    526 defm : T_LoadAbsReg_Pat <sextloadi16, L4_loadrh_ur>;
    527 defm : T_LoadAbsReg_Pat <zextloadi16, L4_loadruh_ur>;
    528 defm : T_LoadAbsReg_Pat <extloadi16,  L4_loadruh_ur>;
    529 
    530 defm : T_LoadAbsReg_Pat <load, L4_loadri_ur>;
    531 defm : T_LoadAbsReg_Pat <load, L4_loadrd_ur, i64>;
    532 }
    533 
    534 //===----------------------------------------------------------------------===//
    535 // Template classes for the non-predicated load instructions with
    536 // base + register offset addressing mode
    537 //===----------------------------------------------------------------------===//
    538 class T_load_rr <string mnemonic, RegisterClass RC, bits<3> MajOp>:
    539    LDInst<(outs RC:$dst), (ins IntRegs:$src1, IntRegs:$src2, u2Imm:$u2),
    540   "$dst = "#mnemonic#"($src1 + $src2<<#$u2)",
    541   [], "", V4LDST_tc_ld_SLOT01>, ImmRegShl, AddrModeRel {
    542     bits<5> dst;
    543     bits<5> src1;
    544     bits<5> src2;
    545     bits<2> u2;
    546 
    547     let IClass = 0b0011;
    548 
    549     let Inst{27-24} = 0b1010;
    550     let Inst{23-21} = MajOp;
    551     let Inst{20-16} = src1;
    552     let Inst{12-8}  = src2;
    553     let Inst{13}    = u2{1};
    554     let Inst{7}     = u2{0};
    555     let Inst{4-0}   = dst;
    556   }
    557 
    558 //===----------------------------------------------------------------------===//
    559 // Template classes for the predicated load instructions with
    560 // base + register offset addressing mode
    561 //===----------------------------------------------------------------------===//
    562 let isPredicated =  1 in
    563 class T_pload_rr <string mnemonic, RegisterClass RC, bits<3> MajOp,
    564                   bit isNot, bit isPredNew>:
    565    LDInst <(outs RC:$dst),
    566            (ins PredRegs:$src1, IntRegs:$src2, IntRegs:$src3, u2Imm:$u2),
    567   !if(isNot, "if (!$src1", "if ($src1")#!if(isPredNew, ".new) ",
    568   ") ")#"$dst = "#mnemonic#"($src2+$src3<<#$u2)",
    569   [], "", V4LDST_tc_ld_SLOT01>, AddrModeRel {
    570     bits<5> dst;
    571     bits<2> src1;
    572     bits<5> src2;
    573     bits<5> src3;
    574     bits<2> u2;
    575 
    576     let isPredicatedFalse = isNot;
    577     let isPredicatedNew = isPredNew;
    578 
    579     let IClass = 0b0011;
    580 
    581     let Inst{27-26} = 0b00;
    582     let Inst{25}    = isPredNew;
    583     let Inst{24}    = isNot;
    584     let Inst{23-21} = MajOp;
    585     let Inst{20-16} = src2;
    586     let Inst{12-8}  = src3;
    587     let Inst{13}    = u2{1};
    588     let Inst{7}     = u2{0};
    589     let Inst{6-5}   = src1;
    590     let Inst{4-0}   = dst;
    591   }
    592 
    593 //===----------------------------------------------------------------------===//
    594 // multiclass for load instructions with base + register offset
    595 // addressing mode
    596 //===----------------------------------------------------------------------===//
    597 let hasSideEffects = 0, addrMode = BaseRegOffset in
    598 multiclass ld_idxd_shl <string mnemonic, string CextOp, RegisterClass RC,
    599                         bits<3> MajOp > {
    600   let CextOpcode = CextOp, BaseOpcode = CextOp#_indexed_shl,
    601       InputType = "reg" in {
    602     let isPredicable = 1 in
    603     def L4_#NAME#_rr : T_load_rr <mnemonic, RC, MajOp>;
    604 
    605     // Predicated
    606     def L4_p#NAME#t_rr : T_pload_rr <mnemonic, RC, MajOp, 0, 0>;
    607     def L4_p#NAME#f_rr : T_pload_rr <mnemonic, RC, MajOp, 1, 0>;
    608 
    609     // Predicated new
    610     def L4_p#NAME#tnew_rr : T_pload_rr <mnemonic, RC, MajOp, 0, 1>;
    611     def L4_p#NAME#fnew_rr : T_pload_rr <mnemonic, RC, MajOp, 1, 1>;
    612   }
    613 }
    614 
    615 let hasNewValue = 1, accessSize = ByteAccess in {
    616   defm loadrb  : ld_idxd_shl<"memb", "LDrib", IntRegs, 0b000>;
    617   defm loadrub : ld_idxd_shl<"memub", "LDriub", IntRegs, 0b001>;
    618 }
    619 
    620 let hasNewValue = 1, accessSize = HalfWordAccess in {
    621   defm loadrh  : ld_idxd_shl<"memh", "LDrih", IntRegs, 0b010>;
    622   defm loadruh : ld_idxd_shl<"memuh", "LDriuh", IntRegs, 0b011>;
    623 }
    624 
    625 let hasNewValue = 1, accessSize = WordAccess in
    626 defm loadri : ld_idxd_shl<"memw", "LDriw", IntRegs, 0b100>;
    627 
    628 let accessSize = DoubleWordAccess in
    629 defm loadrd  : ld_idxd_shl<"memd", "LDrid", DoubleRegs, 0b110>;
    630 
    631 // 'def pats' for load instructions with base + register offset and non-zero
    632 // immediate value. Immediate value is used to left-shift the second
    633 // register operand.
    634 class Loadxs_pat<PatFrag Load, ValueType VT, InstHexagon MI>
    635   : Pat<(VT (Load (add (i32 IntRegs:$Rs),
    636                        (i32 (shl (i32 IntRegs:$Rt), u2ImmPred:$u2))))),
    637         (VT (MI IntRegs:$Rs, IntRegs:$Rt, imm:$u2))>;
    638 
    639 let AddedComplexity = 40 in {
    640   def: Loadxs_pat<extloadi8,   i32, L4_loadrub_rr>;
    641   def: Loadxs_pat<zextloadi8,  i32, L4_loadrub_rr>;
    642   def: Loadxs_pat<sextloadi8,  i32, L4_loadrb_rr>;
    643   def: Loadxs_pat<extloadi16,  i32, L4_loadruh_rr>;
    644   def: Loadxs_pat<zextloadi16, i32, L4_loadruh_rr>;
    645   def: Loadxs_pat<sextloadi16, i32, L4_loadrh_rr>;
    646   def: Loadxs_pat<load,        i32, L4_loadri_rr>;
    647   def: Loadxs_pat<load,        i64, L4_loadrd_rr>;
    648 }
    649 
    650 // 'def pats' for load instruction base + register offset and
    651 // zero immediate value.
    652 class Loadxs_simple_pat<PatFrag Load, ValueType VT, InstHexagon MI>
    653   : Pat<(VT (Load (add (i32 IntRegs:$Rs), (i32 IntRegs:$Rt)))),
    654         (VT (MI IntRegs:$Rs, IntRegs:$Rt, 0))>;
    655 
    656 let AddedComplexity = 20 in {
    657   def: Loadxs_simple_pat<extloadi8,   i32, L4_loadrub_rr>;
    658   def: Loadxs_simple_pat<zextloadi8,  i32, L4_loadrub_rr>;
    659   def: Loadxs_simple_pat<sextloadi8,  i32, L4_loadrb_rr>;
    660   def: Loadxs_simple_pat<extloadi16,  i32, L4_loadruh_rr>;
    661   def: Loadxs_simple_pat<zextloadi16, i32, L4_loadruh_rr>;
    662   def: Loadxs_simple_pat<sextloadi16, i32, L4_loadrh_rr>;
    663   def: Loadxs_simple_pat<load,        i32, L4_loadri_rr>;
    664   def: Loadxs_simple_pat<load,        i64, L4_loadrd_rr>;
    665 }
    666 
    667 // zext i1->i64
    668 def: Pat<(i64 (zext (i1 PredRegs:$src1))),
    669          (Zext64 (C2_muxii PredRegs:$src1, 1, 0))>;
    670 
    671 // zext i32->i64
    672 def: Pat<(i64 (zext (i32 IntRegs:$src1))),
    673          (Zext64 IntRegs:$src1)>;
    674 
    675 //===----------------------------------------------------------------------===//
    676 // LD -
    677 //===----------------------------------------------------------------------===//
    678 
    679 //===----------------------------------------------------------------------===//
    680 // ST +
    681 //===----------------------------------------------------------------------===//
    682 ///
    683 //===----------------------------------------------------------------------===//
    684 // Template class for store instructions with Absolute set addressing mode.
    685 //===----------------------------------------------------------------------===//
    686 let isExtended = 1, opExtendable = 1, opExtentBits = 6,
    687     addrMode = AbsoluteSet in
    688 class T_ST_absset <string mnemonic, string BaseOp, RegisterClass RC,
    689                    bits<3> MajOp, MemAccessSize AccessSz, bit isHalf = 0>
    690   : STInst<(outs IntRegs:$dst),
    691            (ins u6Ext:$addr, RC:$src),
    692     mnemonic#"($dst = #$addr) = $src"#!if(isHalf, ".h","")>, NewValueRel {
    693     bits<5> dst;
    694     bits<6> addr;
    695     bits<5> src;
    696     let accessSize = AccessSz;
    697     let BaseOpcode = BaseOp#"_AbsSet";
    698 
    699     // Store upper-half and store doubleword cannot be NV.
    700     let isNVStorable = !if (!eq(mnemonic, "memd"), 0, !if(isHalf,0,1));
    701 
    702     let IClass = 0b1010;
    703 
    704     let Inst{27-24} = 0b1011;
    705     let Inst{23-21} = MajOp;
    706     let Inst{20-16} = dst;
    707     let Inst{13}    = 0b0;
    708     let Inst{12-8}  = src;
    709     let Inst{7}     = 0b1;
    710     let Inst{5-0}   = addr;
    711   }
    712 
    713 def S4_storerb_ap : T_ST_absset <"memb", "STrib", IntRegs, 0b000, ByteAccess>;
    714 def S4_storerh_ap : T_ST_absset <"memh", "STrih", IntRegs, 0b010,
    715                                  HalfWordAccess>;
    716 def S4_storeri_ap : T_ST_absset <"memw", "STriw", IntRegs, 0b100, WordAccess>;
    717 
    718 let isNVStorable = 0 in {
    719   def S4_storerf_ap : T_ST_absset <"memh", "STrif", IntRegs,
    720                                    0b011, HalfWordAccess, 1>;
    721   def S4_storerd_ap : T_ST_absset <"memd", "STrid", DoubleRegs,
    722                                    0b110, DoubleWordAccess>;
    723 }
    724 
    725 let opExtendable = 1, isNewValue = 1, isNVStore = 1, opNewValue = 2,
    726 isExtended = 1, opExtentBits= 6 in
    727 class T_ST_absset_nv <string mnemonic, string BaseOp, bits<2> MajOp,
    728                       MemAccessSize AccessSz >
    729   : NVInst <(outs IntRegs:$dst),
    730             (ins u6Ext:$addr, IntRegs:$src),
    731     mnemonic#"($dst = #$addr) = $src.new">, NewValueRel {
    732     bits<5> dst;
    733     bits<6> addr;
    734     bits<3> src;
    735     let accessSize = AccessSz;
    736     let BaseOpcode = BaseOp#"_AbsSet";
    737 
    738     let IClass = 0b1010;
    739 
    740     let Inst{27-21} = 0b1011101;
    741     let Inst{20-16} = dst;
    742     let Inst{13-11} = 0b000;
    743     let Inst{12-11} = MajOp;
    744     let Inst{10-8}  = src;
    745     let Inst{7}     = 0b1;
    746     let Inst{5-0}   = addr;
    747   }
    748 
    749 let mayStore = 1, addrMode = AbsoluteSet in {
    750   def S4_storerbnew_ap : T_ST_absset_nv <"memb", "STrib", 0b00, ByteAccess>;
    751   def S4_storerhnew_ap : T_ST_absset_nv <"memh", "STrih", 0b01, HalfWordAccess>;
    752   def S4_storerinew_ap : T_ST_absset_nv <"memw", "STriw", 0b10, WordAccess>;
    753 }
    754 
    755 let isExtended = 1, opExtendable = 2, opExtentBits = 6, InputType = "imm",
    756     addrMode = BaseLongOffset, AddedComplexity = 40 in
    757 class T_StoreAbsReg <string mnemonic, string CextOp, RegisterClass RC,
    758                      bits<3> MajOp, MemAccessSize AccessSz, bit isHalf = 0>
    759   : STInst<(outs),
    760            (ins IntRegs:$src1, u2Imm:$src2, u6Ext:$src3, RC:$src4),
    761    mnemonic#"($src1<<#$src2 + #$src3) = $src4"#!if(isHalf, ".h",""),
    762    []>, ImmRegShl, NewValueRel {
    763 
    764     bits<5> src1;
    765     bits<2> src2;
    766     bits<6> src3;
    767     bits<5> src4;
    768 
    769     let accessSize = AccessSz;
    770     let CextOpcode = CextOp;
    771     let BaseOpcode = CextOp#"_shl";
    772 
    773     // Store upper-half and store doubleword cannot be NV.
    774     let isNVStorable = !if (!eq(mnemonic, "memd"), 0, !if(isHalf,0,1));
    775 
    776     let IClass = 0b1010;
    777 
    778     let Inst{27-24} =0b1101;
    779     let Inst{23-21} = MajOp;
    780     let Inst{20-16} = src1;
    781     let Inst{13}    = src2{1};
    782     let Inst{12-8}  = src4;
    783     let Inst{7}     = 0b1;
    784     let Inst{6}     = src2{0};
    785     let Inst{5-0}   = src3;
    786 }
    787 
    788 def S4_storerb_ur : T_StoreAbsReg <"memb", "STrib", IntRegs, 0b000, ByteAccess>;
    789 def S4_storerh_ur : T_StoreAbsReg <"memh", "STrih", IntRegs, 0b010,
    790                                    HalfWordAccess>;
    791 def S4_storerf_ur : T_StoreAbsReg <"memh", "STrif", IntRegs, 0b011,
    792                                    HalfWordAccess, 1>;
    793 def S4_storeri_ur : T_StoreAbsReg <"memw", "STriw", IntRegs, 0b100, WordAccess>;
    794 def S4_storerd_ur : T_StoreAbsReg <"memd", "STrid", DoubleRegs, 0b110,
    795                                    DoubleWordAccess>;
    796 
    797 let AddedComplexity = 40 in
    798 multiclass T_StoreAbsReg_Pats <InstHexagon MI, RegisterClass RC, ValueType VT,
    799                            PatFrag stOp> {
    800  def : Pat<(stOp (VT RC:$src4),
    801                  (add (shl (i32 IntRegs:$src1), u2ImmPred:$src2),
    802                       u32ImmPred:$src3)),
    803           (MI IntRegs:$src1, u2ImmPred:$src2, u32ImmPred:$src3, RC:$src4)>;
    804 
    805  def : Pat<(stOp (VT RC:$src4),
    806                  (add (shl IntRegs:$src1, u2ImmPred:$src2),
    807                       (HexagonCONST32 tglobaladdr:$src3))),
    808            (MI IntRegs:$src1, u2ImmPred:$src2, tglobaladdr:$src3, RC:$src4)>;
    809 
    810  def : Pat<(stOp (VT RC:$src4),
    811                  (add IntRegs:$src1, (HexagonCONST32 tglobaladdr:$src3))),
    812            (MI IntRegs:$src1, 0, tglobaladdr:$src3, RC:$src4)>;
    813 }
    814 
    815 defm : T_StoreAbsReg_Pats <S4_storerd_ur, DoubleRegs, i64, store>;
    816 defm : T_StoreAbsReg_Pats <S4_storeri_ur, IntRegs, i32, store>;
    817 defm : T_StoreAbsReg_Pats <S4_storerb_ur, IntRegs, i32, truncstorei8>;
    818 defm : T_StoreAbsReg_Pats <S4_storerh_ur, IntRegs, i32, truncstorei16>;
    819 
    820 let mayStore = 1, isNVStore = 1, isExtended = 1, addrMode = BaseLongOffset,
    821     opExtentBits = 6, isNewValue = 1, opNewValue = 3, opExtendable = 2 in
    822 class T_StoreAbsRegNV <string mnemonic, string CextOp, bits<2> MajOp,
    823                        MemAccessSize AccessSz>
    824   : NVInst <(outs ),
    825             (ins IntRegs:$src1, u2Imm:$src2, u6Ext:$src3, IntRegs:$src4),
    826   mnemonic#"($src1<<#$src2 + #$src3) = $src4.new">, NewValueRel {
    827     bits<5> src1;
    828     bits<2> src2;
    829     bits<6> src3;
    830     bits<3> src4;
    831 
    832     let CextOpcode  = CextOp;
    833     let BaseOpcode  = CextOp#"_shl";
    834     let IClass      = 0b1010;
    835 
    836     let Inst{27-21} = 0b1101101;
    837     let Inst{12-11} = 0b00;
    838     let Inst{7}     = 0b1;
    839     let Inst{20-16} = src1;
    840     let Inst{13}    = src2{1};
    841     let Inst{12-11} = MajOp;
    842     let Inst{10-8}  = src4;
    843     let Inst{6}     = src2{0};
    844     let Inst{5-0}   = src3;
    845   }
    846 
    847 def S4_storerbnew_ur : T_StoreAbsRegNV <"memb", "STrib", 0b00, ByteAccess>;
    848 def S4_storerhnew_ur : T_StoreAbsRegNV <"memh", "STrih", 0b01, HalfWordAccess>;
    849 def S4_storerinew_ur : T_StoreAbsRegNV <"memw", "STriw", 0b10, WordAccess>;
    850 
    851 //===----------------------------------------------------------------------===//
    852 // Template classes for the non-predicated store instructions with
    853 // base + register offset addressing mode
    854 //===----------------------------------------------------------------------===//
    855 let isPredicable = 1 in
    856 class T_store_rr <string mnemonic, RegisterClass RC, bits<3> MajOp, bit isH>
    857   : STInst < (outs ), (ins IntRegs:$Rs, IntRegs:$Ru, u2Imm:$u2, RC:$Rt),
    858   mnemonic#"($Rs + $Ru<<#$u2) = $Rt"#!if(isH, ".h",""),
    859   [],"",V4LDST_tc_st_SLOT01>, ImmRegShl, AddrModeRel {
    860 
    861     bits<5> Rs;
    862     bits<5> Ru;
    863     bits<2> u2;
    864     bits<5> Rt;
    865 
    866     // Store upper-half and store doubleword cannot be NV.
    867     let isNVStorable = !if (!eq(mnemonic, "memd"), 0, !if(isH,0,1));
    868 
    869     let IClass = 0b0011;
    870 
    871     let Inst{27-24} = 0b1011;
    872     let Inst{23-21} = MajOp;
    873     let Inst{20-16} = Rs;
    874     let Inst{12-8}  = Ru;
    875     let Inst{13}    = u2{1};
    876     let Inst{7}     = u2{0};
    877     let Inst{4-0}   = Rt;
    878   }
    879 
    880 //===----------------------------------------------------------------------===//
    881 // Template classes for the predicated store instructions with
    882 // base + register offset addressing mode
    883 //===----------------------------------------------------------------------===//
    884 let isPredicated = 1 in
    885 class T_pstore_rr <string mnemonic, RegisterClass RC, bits<3> MajOp,
    886                    bit isNot, bit isPredNew, bit isH>
    887   : STInst <(outs),
    888             (ins PredRegs:$Pv, IntRegs:$Rs, IntRegs:$Ru, u2Imm:$u2, RC:$Rt),
    889 
    890   !if(isNot, "if (!$Pv", "if ($Pv")#!if(isPredNew, ".new) ",
    891   ") ")#mnemonic#"($Rs+$Ru<<#$u2) = $Rt"#!if(isH, ".h",""),
    892   [], "", V4LDST_tc_st_SLOT01> , AddrModeRel{
    893     bits<2> Pv;
    894     bits<5> Rs;
    895     bits<5> Ru;
    896     bits<2> u2;
    897     bits<5> Rt;
    898 
    899     let isPredicatedFalse = isNot;
    900     let isPredicatedNew = isPredNew;
    901     // Store upper-half and store doubleword cannot be NV.
    902     let isNVStorable = !if (!eq(mnemonic, "memd"), 0, !if(isH,0,1));
    903 
    904     let IClass = 0b0011;
    905 
    906     let Inst{27-26} = 0b01;
    907     let Inst{25}    = isPredNew;
    908     let Inst{24}    = isNot;
    909     let Inst{23-21} = MajOp;
    910     let Inst{20-16} = Rs;
    911     let Inst{12-8}  = Ru;
    912     let Inst{13}    = u2{1};
    913     let Inst{7}     = u2{0};
    914     let Inst{6-5}   = Pv;
    915     let Inst{4-0}   = Rt;
    916   }
    917 
    918 //===----------------------------------------------------------------------===//
    919 // Template classes for the new-value store instructions with
    920 // base + register offset addressing mode
    921 //===----------------------------------------------------------------------===//
    922 let isPredicable = 1, isNewValue = 1, opNewValue = 3 in
    923 class T_store_new_rr <string mnemonic, bits<2> MajOp> :
    924   NVInst < (outs ), (ins IntRegs:$Rs, IntRegs:$Ru, u2Imm:$u2, IntRegs:$Nt),
    925   mnemonic#"($Rs + $Ru<<#$u2) = $Nt.new",
    926   [],"",V4LDST_tc_st_SLOT0>, ImmRegShl, AddrModeRel {
    927 
    928     bits<5> Rs;
    929     bits<5> Ru;
    930     bits<2> u2;
    931     bits<3> Nt;
    932 
    933     let IClass = 0b0011;
    934 
    935     let Inst{27-21} = 0b1011101;
    936     let Inst{20-16} = Rs;
    937     let Inst{12-8}  = Ru;
    938     let Inst{13}    = u2{1};
    939     let Inst{7}     = u2{0};
    940     let Inst{4-3}   = MajOp;
    941     let Inst{2-0}   = Nt;
    942   }
    943 
    944 //===----------------------------------------------------------------------===//
    945 // Template classes for the predicated new-value store instructions with
    946 // base + register offset addressing mode
    947 //===----------------------------------------------------------------------===//
    948 let isPredicated = 1, isNewValue = 1, opNewValue = 4 in
    949 class T_pstore_new_rr <string mnemonic, bits<2> MajOp, bit isNot, bit isPredNew>
    950   : NVInst<(outs),
    951            (ins PredRegs:$Pv, IntRegs:$Rs, IntRegs:$Ru, u2Imm:$u2, IntRegs:$Nt),
    952    !if(isNot, "if (!$Pv", "if ($Pv")#!if(isPredNew, ".new) ",
    953    ") ")#mnemonic#"($Rs+$Ru<<#$u2) = $Nt.new",
    954    [], "", V4LDST_tc_st_SLOT0>, AddrModeRel {
    955     bits<2> Pv;
    956     bits<5> Rs;
    957     bits<5> Ru;
    958     bits<2> u2;
    959     bits<3> Nt;
    960 
    961     let isPredicatedFalse = isNot;
    962     let isPredicatedNew = isPredNew;
    963 
    964     let IClass = 0b0011;
    965     let Inst{27-26} = 0b01;
    966     let Inst{25}    = isPredNew;
    967     let Inst{24}    = isNot;
    968     let Inst{23-21} = 0b101;
    969     let Inst{20-16} = Rs;
    970     let Inst{12-8}  = Ru;
    971     let Inst{13}    = u2{1};
    972     let Inst{7}     = u2{0};
    973     let Inst{6-5}   = Pv;
    974     let Inst{4-3}   = MajOp;
    975     let Inst{2-0}   = Nt;
    976   }
    977 
    978 //===----------------------------------------------------------------------===//
    979 // multiclass for store instructions with base + register offset addressing
    980 // mode
    981 //===----------------------------------------------------------------------===//
    982 let isNVStorable = 1 in
    983 multiclass ST_Idxd_shl<string mnemonic, string CextOp, RegisterClass RC,
    984                        bits<3> MajOp, bit isH = 0> {
    985   let CextOpcode = CextOp, BaseOpcode = CextOp#_indexed_shl in {
    986     def S4_#NAME#_rr : T_store_rr <mnemonic, RC, MajOp, isH>;
    987 
    988     // Predicated
    989     def S4_p#NAME#t_rr : T_pstore_rr <mnemonic, RC, MajOp, 0, 0, isH>;
    990     def S4_p#NAME#f_rr : T_pstore_rr <mnemonic, RC, MajOp, 1, 0, isH>;
    991 
    992     // Predicated new
    993     def S4_p#NAME#tnew_rr : T_pstore_rr <mnemonic, RC, MajOp, 0, 1, isH>;
    994     def S4_p#NAME#fnew_rr : T_pstore_rr <mnemonic, RC, MajOp, 1, 1, isH>;
    995   }
    996 }
    997 
    998 //===----------------------------------------------------------------------===//
    999 // multiclass for new-value store instructions with base + register offset
   1000 // addressing mode.
   1001 //===----------------------------------------------------------------------===//
   1002 let mayStore = 1, isNVStore = 1 in
   1003 multiclass ST_Idxd_shl_nv <string mnemonic, string CextOp, RegisterClass RC,
   1004                            bits<2> MajOp> {
   1005   let CextOpcode = CextOp, BaseOpcode = CextOp#_indexed_shl in {
   1006     def S4_#NAME#new_rr : T_store_new_rr<mnemonic, MajOp>;
   1007 
   1008     // Predicated
   1009     def S4_p#NAME#newt_rr : T_pstore_new_rr <mnemonic, MajOp, 0, 0>;
   1010     def S4_p#NAME#newf_rr : T_pstore_new_rr <mnemonic, MajOp, 1, 0>;
   1011 
   1012     // Predicated new
   1013     def S4_p#NAME#newtnew_rr : T_pstore_new_rr <mnemonic, MajOp, 0, 1>;
   1014     def S4_p#NAME#newfnew_rr : T_pstore_new_rr <mnemonic, MajOp, 1, 1>;
   1015   }
   1016 }
   1017 
   1018 let addrMode = BaseRegOffset, InputType = "reg", hasSideEffects = 0 in {
   1019   let accessSize = ByteAccess in
   1020   defm storerb: ST_Idxd_shl<"memb", "STrib", IntRegs, 0b000>,
   1021                 ST_Idxd_shl_nv<"memb", "STrib", IntRegs, 0b00>;
   1022 
   1023   let accessSize = HalfWordAccess in
   1024   defm storerh: ST_Idxd_shl<"memh", "STrih", IntRegs, 0b010>,
   1025                 ST_Idxd_shl_nv<"memh", "STrih", IntRegs, 0b01>;
   1026 
   1027   let accessSize = WordAccess in
   1028   defm storeri: ST_Idxd_shl<"memw", "STriw", IntRegs, 0b100>,
   1029                 ST_Idxd_shl_nv<"memw", "STriw", IntRegs, 0b10>;
   1030 
   1031   let isNVStorable = 0, accessSize = DoubleWordAccess in
   1032   defm storerd: ST_Idxd_shl<"memd", "STrid", DoubleRegs, 0b110>;
   1033 
   1034   let isNVStorable = 0, accessSize = HalfWordAccess in
   1035   defm storerf: ST_Idxd_shl<"memh", "STrif", IntRegs, 0b011, 1>;
   1036 }
   1037 
   1038 class Storexs_pat<PatFrag Store, PatFrag Value, InstHexagon MI>
   1039   : Pat<(Store Value:$Ru, (add (i32 IntRegs:$Rs),
   1040                                (i32 (shl (i32 IntRegs:$Rt), u2ImmPred:$u2)))),
   1041         (MI IntRegs:$Rs, IntRegs:$Rt, imm:$u2, Value:$Ru)>;
   1042 
   1043 let AddedComplexity = 40 in {
   1044   def: Storexs_pat<truncstorei8,  I32, S4_storerb_rr>;
   1045   def: Storexs_pat<truncstorei16, I32, S4_storerh_rr>;
   1046   def: Storexs_pat<store,         I32, S4_storeri_rr>;
   1047   def: Storexs_pat<store,         I64, S4_storerd_rr>;
   1048 }
   1049 
   1050 // memd(Rx++#s4:3)=Rtt
   1051 // memd(Rx++#s4:3:circ(Mu))=Rtt
   1052 // memd(Rx++I:circ(Mu))=Rtt
   1053 // memd(Rx++Mu)=Rtt
   1054 // memd(Rx++Mu:brev)=Rtt
   1055 // memd(gp+#u16:3)=Rtt
   1056 
   1057 // Store doubleword conditionally.
   1058 // if ([!]Pv[.new]) memd(#u6)=Rtt
   1059 // TODO: needs to be implemented.
   1060 
   1061 //===----------------------------------------------------------------------===//
   1062 // Template class
   1063 //===----------------------------------------------------------------------===//
   1064 let isPredicable = 1, isExtendable = 1, isExtentSigned = 1, opExtentBits = 8,
   1065     opExtendable = 2 in
   1066 class T_StoreImm <string mnemonic, Operand OffsetOp, bits<2> MajOp >
   1067   : STInst <(outs ), (ins IntRegs:$Rs, OffsetOp:$offset, s8Ext:$S8),
   1068   mnemonic#"($Rs+#$offset)=#$S8",
   1069   [], "", V4LDST_tc_st_SLOT01>,
   1070   ImmRegRel, PredNewRel {
   1071     bits<5> Rs;
   1072     bits<8> S8;
   1073     bits<8> offset;
   1074     bits<6> offsetBits;
   1075 
   1076     string OffsetOpStr = !cast<string>(OffsetOp);
   1077     let offsetBits = !if (!eq(OffsetOpStr, "u6_2Imm"), offset{7-2},
   1078                      !if (!eq(OffsetOpStr, "u6_1Imm"), offset{6-1},
   1079                                          /* u6_0Imm */ offset{5-0}));
   1080 
   1081     let IClass = 0b0011;
   1082 
   1083     let Inst{27-25} = 0b110;
   1084     let Inst{22-21} = MajOp;
   1085     let Inst{20-16} = Rs;
   1086     let Inst{12-7}  = offsetBits;
   1087     let Inst{13}    = S8{7};
   1088     let Inst{6-0}   = S8{6-0};
   1089   }
   1090 
   1091 let isPredicated = 1, isExtendable = 1, isExtentSigned = 1, opExtentBits = 6,
   1092     opExtendable = 3 in
   1093 class T_StoreImm_pred <string mnemonic, Operand OffsetOp, bits<2> MajOp,
   1094                        bit isPredNot, bit isPredNew >
   1095   : STInst <(outs ),
   1096             (ins PredRegs:$Pv, IntRegs:$Rs, OffsetOp:$offset, s6Ext:$S6),
   1097   !if(isPredNot, "if (!$Pv", "if ($Pv")#!if(isPredNew, ".new) ",
   1098   ") ")#mnemonic#"($Rs+#$offset)=#$S6",
   1099   [], "", V4LDST_tc_st_SLOT01>,
   1100   ImmRegRel, PredNewRel {
   1101     bits<2> Pv;
   1102     bits<5> Rs;
   1103     bits<6> S6;
   1104     bits<8> offset;
   1105     bits<6> offsetBits;
   1106 
   1107     string OffsetOpStr = !cast<string>(OffsetOp);
   1108     let offsetBits = !if (!eq(OffsetOpStr, "u6_2Imm"), offset{7-2},
   1109                      !if (!eq(OffsetOpStr, "u6_1Imm"), offset{6-1},
   1110                                          /* u6_0Imm */ offset{5-0}));
   1111     let isPredicatedNew = isPredNew;
   1112     let isPredicatedFalse = isPredNot;
   1113 
   1114     let IClass = 0b0011;
   1115 
   1116     let Inst{27-25} = 0b100;
   1117     let Inst{24}    = isPredNew;
   1118     let Inst{23}    = isPredNot;
   1119     let Inst{22-21} = MajOp;
   1120     let Inst{20-16} = Rs;
   1121     let Inst{13}    = S6{5};
   1122     let Inst{12-7}  = offsetBits;
   1123     let Inst{6-5}   = Pv;
   1124     let Inst{4-0}   = S6{4-0};
   1125   }
   1126 
   1127 
   1128 //===----------------------------------------------------------------------===//
   1129 // multiclass for store instructions with base + immediate offset
   1130 // addressing mode and immediate stored value.
   1131 // mem[bhw](Rx++#s4:3)=#s8
   1132 // if ([!]Pv[.new]) mem[bhw](Rx++#s4:3)=#s6
   1133 //===----------------------------------------------------------------------===//
   1134 
   1135 multiclass ST_Imm_Pred <string mnemonic, Operand OffsetOp, bits<2> MajOp,
   1136                         bit PredNot> {
   1137   def _io    : T_StoreImm_pred <mnemonic, OffsetOp, MajOp, PredNot, 0>;
   1138   // Predicate new
   1139   def new_io : T_StoreImm_pred <mnemonic, OffsetOp, MajOp, PredNot, 1>;
   1140 }
   1141 
   1142 multiclass ST_Imm <string mnemonic, string CextOp, Operand OffsetOp,
   1143                    bits<2> MajOp> {
   1144   let CextOpcode = CextOp, BaseOpcode = CextOp#_imm in {
   1145     def _io : T_StoreImm <mnemonic, OffsetOp, MajOp>;
   1146 
   1147     defm t : ST_Imm_Pred <mnemonic, OffsetOp, MajOp, 0>;
   1148     defm f : ST_Imm_Pred <mnemonic, OffsetOp, MajOp, 1>;
   1149   }
   1150 }
   1151 
   1152 let hasSideEffects = 0, addrMode = BaseImmOffset,
   1153     InputType = "imm" in {
   1154   let accessSize = ByteAccess in
   1155   defm S4_storeirb : ST_Imm<"memb", "STrib", u6_0Imm, 0b00>;
   1156 
   1157   let accessSize = HalfWordAccess in
   1158   defm S4_storeirh : ST_Imm<"memh", "STrih", u6_1Imm, 0b01>;
   1159 
   1160   let accessSize = WordAccess in
   1161   defm S4_storeiri : ST_Imm<"memw", "STriw", u6_2Imm, 0b10>;
   1162 }
   1163 
   1164 def IMM_BYTE : SDNodeXForm<imm, [{
   1165   // -1 etc is  represented as 255 etc
   1166   // assigning to a byte restores our desired signed value.
   1167   int8_t imm = N->getSExtValue();
   1168   return CurDAG->getTargetConstant(imm, SDLoc(N), MVT::i32);
   1169 }]>;
   1170 
   1171 def IMM_HALF : SDNodeXForm<imm, [{
   1172   // -1 etc is  represented as 65535 etc
   1173   // assigning to a short restores our desired signed value.
   1174   int16_t imm = N->getSExtValue();
   1175   return CurDAG->getTargetConstant(imm, SDLoc(N), MVT::i32);
   1176 }]>;
   1177 
   1178 def IMM_WORD : SDNodeXForm<imm, [{
   1179   // -1 etc can be represented as 4294967295 etc
   1180   // Currently, it's not doing this. But some optimization
   1181   // might convert -1 to a large +ve number.
   1182   // assigning to a word restores our desired signed value.
   1183   int32_t imm = N->getSExtValue();
   1184   return CurDAG->getTargetConstant(imm, SDLoc(N), MVT::i32);
   1185 }]>;
   1186 
   1187 def ToImmByte : OutPatFrag<(ops node:$R), (IMM_BYTE $R)>;
   1188 def ToImmHalf : OutPatFrag<(ops node:$R), (IMM_HALF $R)>;
   1189 def ToImmWord : OutPatFrag<(ops node:$R), (IMM_WORD $R)>;
   1190 
   1191 let AddedComplexity = 40 in {
   1192   // Not using frameindex patterns for these stores, because the offset
   1193   // is not extendable. This could cause problems during removing the frame
   1194   // indices, since the offset with respect to R29/R30 may not fit in the
   1195   // u6 field.
   1196   def: Storexm_add_pat<truncstorei8, s32ImmPred, u6_0ImmPred, ToImmByte,
   1197                        S4_storeirb_io>;
   1198   def: Storexm_add_pat<truncstorei16, s32ImmPred, u6_1ImmPred, ToImmHalf,
   1199                        S4_storeirh_io>;
   1200   def: Storexm_add_pat<store, s32ImmPred, u6_2ImmPred, ToImmWord,
   1201                        S4_storeiri_io>;
   1202 }
   1203 
   1204 def: Storexm_simple_pat<truncstorei8,  s32ImmPred, ToImmByte, S4_storeirb_io>;
   1205 def: Storexm_simple_pat<truncstorei16, s32ImmPred, ToImmHalf, S4_storeirh_io>;
   1206 def: Storexm_simple_pat<store,         s32ImmPred, ToImmWord, S4_storeiri_io>;
   1207 
   1208 // memb(Rx++#s4:0:circ(Mu))=Rt
   1209 // memb(Rx++I:circ(Mu))=Rt
   1210 // memb(Rx++Mu)=Rt
   1211 // memb(Rx++Mu:brev)=Rt
   1212 // memb(gp+#u16:0)=Rt
   1213 
   1214 // Store halfword.
   1215 // TODO: needs to be implemented
   1216 // memh(Re=#U6)=Rt.H
   1217 // memh(Rs+#s11:1)=Rt.H
   1218 // memh(Rs+Ru<<#u2)=Rt.H
   1219 // TODO: needs to be implemented.
   1220 
   1221 // memh(Ru<<#u2+#U6)=Rt.H
   1222 // memh(Rx++#s4:1:circ(Mu))=Rt.H
   1223 // memh(Rx++#s4:1:circ(Mu))=Rt
   1224 // memh(Rx++I:circ(Mu))=Rt.H
   1225 // memh(Rx++I:circ(Mu))=Rt
   1226 // memh(Rx++Mu)=Rt.H
   1227 // memh(Rx++Mu)=Rt
   1228 // memh(Rx++Mu:brev)=Rt.H
   1229 // memh(Rx++Mu:brev)=Rt
   1230 // memh(gp+#u16:1)=Rt
   1231 // if ([!]Pv[.new]) memh(#u6)=Rt.H
   1232 // if ([!]Pv[.new]) memh(#u6)=Rt
   1233 
   1234 // if ([!]Pv[.new]) memh(Rs+#u6:1)=Rt.H
   1235 // TODO: needs to be implemented.
   1236 
   1237 // if ([!]Pv[.new]) memh(Rx++#s4:1)=Rt.H
   1238 // TODO: Needs to be implemented.
   1239 
   1240 // Store word.
   1241 // memw(Re=#U6)=Rt
   1242 // TODO: Needs to be implemented.
   1243 // memw(Rx++#s4:2)=Rt
   1244 // memw(Rx++#s4:2:circ(Mu))=Rt
   1245 // memw(Rx++I:circ(Mu))=Rt
   1246 // memw(Rx++Mu)=Rt
   1247 // memw(Rx++Mu:brev)=Rt
   1248 
   1249 //===----------------------------------------------------------------------===
   1250 // ST -
   1251 //===----------------------------------------------------------------------===
   1252 
   1253 
   1254 //===----------------------------------------------------------------------===//
   1255 // NV/ST +
   1256 //===----------------------------------------------------------------------===//
   1257 
   1258 let opNewValue = 2, opExtendable = 1, isExtentSigned = 1, isPredicable = 1 in
   1259 class T_store_io_nv <string mnemonic, RegisterClass RC,
   1260                     Operand ImmOp, bits<2>MajOp>
   1261   : NVInst_V4 <(outs),
   1262                (ins IntRegs:$src1, ImmOp:$src2, RC:$src3),
   1263   mnemonic#"($src1+#$src2) = $src3.new",
   1264   [],"",ST_tc_st_SLOT0> {
   1265     bits<5> src1;
   1266     bits<13> src2; // Actual address offset
   1267     bits<3> src3;
   1268     bits<11> offsetBits; // Represents offset encoding
   1269 
   1270     let opExtentBits = !if (!eq(mnemonic, "memb"), 11,
   1271                        !if (!eq(mnemonic, "memh"), 12,
   1272                        !if (!eq(mnemonic, "memw"), 13, 0)));
   1273 
   1274     let opExtentAlign = !if (!eq(mnemonic, "memb"), 0,
   1275                         !if (!eq(mnemonic, "memh"), 1,
   1276                         !if (!eq(mnemonic, "memw"), 2, 0)));
   1277 
   1278     let offsetBits = !if (!eq(mnemonic, "memb"),  src2{10-0},
   1279                      !if (!eq(mnemonic, "memh"),  src2{11-1},
   1280                      !if (!eq(mnemonic, "memw"),  src2{12-2}, 0)));
   1281 
   1282     let IClass = 0b1010;
   1283 
   1284     let Inst{27} = 0b0;
   1285     let Inst{26-25} = offsetBits{10-9};
   1286     let Inst{24-21} = 0b1101;
   1287     let Inst{20-16} = src1;
   1288     let Inst{13} = offsetBits{8};
   1289     let Inst{12-11} = MajOp;
   1290     let Inst{10-8} = src3;
   1291     let Inst{7-0} = offsetBits{7-0};
   1292   }
   1293 
   1294 let opExtendable = 2, opNewValue = 3, isPredicated = 1 in
   1295 class T_pstore_io_nv <string mnemonic, RegisterClass RC, Operand predImmOp,
   1296                          bits<2>MajOp, bit PredNot, bit isPredNew>
   1297   : NVInst_V4 <(outs),
   1298                (ins PredRegs:$src1, IntRegs:$src2, predImmOp:$src3, RC:$src4),
   1299   !if(PredNot, "if (!$src1", "if ($src1")#!if(isPredNew, ".new) ",
   1300   ") ")#mnemonic#"($src2+#$src3) = $src4.new",
   1301   [],"",V2LDST_tc_st_SLOT0> {
   1302     bits<2> src1;
   1303     bits<5> src2;
   1304     bits<9> src3;
   1305     bits<3> src4;
   1306     bits<6> offsetBits; // Represents offset encoding
   1307 
   1308     let isPredicatedNew = isPredNew;
   1309     let isPredicatedFalse = PredNot;
   1310     let opExtentBits = !if (!eq(mnemonic, "memb"), 6,
   1311                        !if (!eq(mnemonic, "memh"), 7,
   1312                        !if (!eq(mnemonic, "memw"), 8, 0)));
   1313 
   1314     let opExtentAlign = !if (!eq(mnemonic, "memb"), 0,
   1315                         !if (!eq(mnemonic, "memh"), 1,
   1316                         !if (!eq(mnemonic, "memw"), 2, 0)));
   1317 
   1318     let offsetBits = !if (!eq(mnemonic, "memb"), src3{5-0},
   1319                      !if (!eq(mnemonic, "memh"), src3{6-1},
   1320                      !if (!eq(mnemonic, "memw"), src3{7-2}, 0)));
   1321 
   1322     let IClass = 0b0100;
   1323 
   1324     let Inst{27}    = 0b0;
   1325     let Inst{26}    = PredNot;
   1326     let Inst{25}    = isPredNew;
   1327     let Inst{24-21} = 0b0101;
   1328     let Inst{20-16} = src2;
   1329     let Inst{13}    = offsetBits{5};
   1330     let Inst{12-11} = MajOp;
   1331     let Inst{10-8}  = src4;
   1332     let Inst{7-3}   = offsetBits{4-0};
   1333     let Inst{2}     = 0b0;
   1334     let Inst{1-0}   = src1;
   1335   }
   1336 
   1337 // multiclass for new-value store instructions with base + immediate offset.
   1338 //
   1339 let mayStore = 1, isNVStore = 1, isNewValue = 1, hasSideEffects = 0,
   1340     isExtendable = 1 in
   1341 multiclass ST_Idxd_nv<string mnemonic, string CextOp, RegisterClass RC,
   1342                    Operand ImmOp, Operand predImmOp, bits<2> MajOp> {
   1343 
   1344   let CextOpcode = CextOp, BaseOpcode = CextOp#_indexed in {
   1345     def S2_#NAME#new_io : T_store_io_nv <mnemonic, RC, ImmOp, MajOp>;
   1346     // Predicated
   1347     def S2_p#NAME#newt_io :T_pstore_io_nv <mnemonic, RC, predImmOp, MajOp, 0, 0>;
   1348     def S2_p#NAME#newf_io :T_pstore_io_nv <mnemonic, RC, predImmOp, MajOp, 1, 0>;
   1349     // Predicated new
   1350     def S4_p#NAME#newtnew_io :T_pstore_io_nv <mnemonic, RC, predImmOp,
   1351                                               MajOp, 0, 1>;
   1352     def S4_p#NAME#newfnew_io :T_pstore_io_nv <mnemonic, RC, predImmOp,
   1353                                               MajOp, 1, 1>;
   1354   }
   1355 }
   1356 
   1357 let addrMode = BaseImmOffset, InputType = "imm" in {
   1358   let accessSize = ByteAccess in
   1359   defm storerb: ST_Idxd_nv<"memb", "STrib", IntRegs, s11_0Ext,
   1360                            u6_0Ext, 0b00>, AddrModeRel;
   1361 
   1362   let accessSize = HalfWordAccess, opExtentAlign = 1 in
   1363   defm storerh: ST_Idxd_nv<"memh", "STrih", IntRegs, s11_1Ext,
   1364                            u6_1Ext, 0b01>, AddrModeRel;
   1365 
   1366   let accessSize = WordAccess, opExtentAlign = 2 in
   1367   defm storeri: ST_Idxd_nv<"memw", "STriw", IntRegs, s11_2Ext,
   1368                            u6_2Ext, 0b10>, AddrModeRel;
   1369 }
   1370 
   1371 //===----------------------------------------------------------------------===//
   1372 // Post increment loads with register offset.
   1373 //===----------------------------------------------------------------------===//
   1374 
   1375 let hasNewValue = 1 in
   1376 def L2_loadbsw2_pr : T_load_pr <"membh", IntRegs, 0b0001, HalfWordAccess>;
   1377 
   1378 def L2_loadbsw4_pr : T_load_pr <"membh", DoubleRegs, 0b0111, WordAccess>;
   1379 
   1380 let hasSideEffects = 0, addrMode = PostInc in
   1381 class T_loadalign_pr <string mnemonic, bits<4> MajOp, MemAccessSize AccessSz>
   1382   : LDInstPI <(outs DoubleRegs:$dst, IntRegs:$_dst_),
   1383               (ins DoubleRegs:$src1, IntRegs:$src2, ModRegs:$src3),
   1384   "$dst = "#mnemonic#"($src2++$src3)", [],
   1385   "$src1 = $dst, $src2 = $_dst_"> {
   1386     bits<5> dst;
   1387     bits<5> src2;
   1388     bits<1> src3;
   1389 
   1390     let accessSize = AccessSz;
   1391     let IClass = 0b1001;
   1392 
   1393     let Inst{27-25} = 0b110;
   1394     let Inst{24-21} = MajOp;
   1395     let Inst{20-16} = src2;
   1396     let Inst{13}    = src3;
   1397     let Inst{12}    = 0b0;
   1398     let Inst{7}     = 0b0;
   1399     let Inst{4-0}   = dst;
   1400   }
   1401 
   1402 def L2_loadalignb_pr : T_loadalign_pr <"memb_fifo", 0b0100, ByteAccess>;
   1403 def L2_loadalignh_pr : T_loadalign_pr <"memh_fifo", 0b0010, HalfWordAccess>;
   1404 
   1405 //===----------------------------------------------------------------------===//
   1406 // Template class for non-predicated post increment .new stores
   1407 // mem[bhwd](Rx++#s4:[0123])=Nt.new
   1408 //===----------------------------------------------------------------------===//
   1409 let isPredicable = 1, hasSideEffects = 0, addrMode = PostInc, isNVStore = 1,
   1410     isNewValue = 1, opNewValue = 3 in
   1411 class T_StorePI_nv <string mnemonic, Operand ImmOp, bits<2> MajOp >
   1412   : NVInstPI_V4 <(outs IntRegs:$_dst_),
   1413                  (ins IntRegs:$src1, ImmOp:$offset, IntRegs:$src2),
   1414   mnemonic#"($src1++#$offset) = $src2.new",
   1415   [], "$src1 = $_dst_">,
   1416   AddrModeRel {
   1417     bits<5> src1;
   1418     bits<3> src2;
   1419     bits<7> offset;
   1420     bits<4> offsetBits;
   1421 
   1422     string ImmOpStr = !cast<string>(ImmOp);
   1423     let offsetBits = !if (!eq(ImmOpStr, "s4_2Imm"), offset{5-2},
   1424                      !if (!eq(ImmOpStr, "s4_1Imm"), offset{4-1},
   1425                                       /* s4_0Imm */ offset{3-0}));
   1426     let IClass = 0b1010;
   1427 
   1428     let Inst{27-21} = 0b1011101;
   1429     let Inst{20-16} = src1;
   1430     let Inst{13} = 0b0;
   1431     let Inst{12-11} = MajOp;
   1432     let Inst{10-8} = src2;
   1433     let Inst{7} = 0b0;
   1434     let Inst{6-3} = offsetBits;
   1435     let Inst{1} = 0b0;
   1436   }
   1437 
   1438 //===----------------------------------------------------------------------===//
   1439 // Template class for predicated post increment .new stores
   1440 // if([!]Pv[.new]) mem[bhwd](Rx++#s4:[0123])=Nt.new
   1441 //===----------------------------------------------------------------------===//
   1442 let isPredicated = 1, hasSideEffects = 0, addrMode = PostInc, isNVStore = 1,
   1443     isNewValue = 1, opNewValue = 4 in
   1444 class T_StorePI_nv_pred <string mnemonic, Operand ImmOp,
   1445                          bits<2> MajOp, bit isPredNot, bit isPredNew >
   1446   : NVInstPI_V4 <(outs IntRegs:$_dst_),
   1447                  (ins PredRegs:$src1, IntRegs:$src2,
   1448                       ImmOp:$offset, IntRegs:$src3),
   1449   !if(isPredNot, "if (!$src1", "if ($src1")#!if(isPredNew, ".new) ",
   1450   ") ")#mnemonic#"($src2++#$offset) = $src3.new",
   1451   [], "$src2 = $_dst_">,
   1452   AddrModeRel {
   1453     bits<2> src1;
   1454     bits<5> src2;
   1455     bits<3> src3;
   1456     bits<7> offset;
   1457     bits<4> offsetBits;
   1458 
   1459     string ImmOpStr = !cast<string>(ImmOp);
   1460     let offsetBits = !if (!eq(ImmOpStr, "s4_2Imm"), offset{5-2},
   1461                      !if (!eq(ImmOpStr, "s4_1Imm"), offset{4-1},
   1462                                       /* s4_0Imm */ offset{3-0}));
   1463     let isPredicatedNew = isPredNew;
   1464     let isPredicatedFalse = isPredNot;
   1465 
   1466     let IClass = 0b1010;
   1467 
   1468     let Inst{27-21} = 0b1011101;
   1469     let Inst{20-16} = src2;
   1470     let Inst{13} = 0b1;
   1471     let Inst{12-11} = MajOp;
   1472     let Inst{10-8} = src3;
   1473     let Inst{7} = isPredNew;
   1474     let Inst{6-3} = offsetBits;
   1475     let Inst{2} = isPredNot;
   1476     let Inst{1-0} = src1;
   1477   }
   1478 
   1479 multiclass ST_PostInc_Pred_nv<string mnemonic, Operand ImmOp,
   1480                               bits<2> MajOp, bit PredNot> {
   1481   def _pi : T_StorePI_nv_pred <mnemonic, ImmOp, MajOp, PredNot, 0>;
   1482 
   1483   // Predicate new
   1484   def new_pi : T_StorePI_nv_pred <mnemonic, ImmOp, MajOp, PredNot, 1>;
   1485 }
   1486 
   1487 multiclass ST_PostInc_nv<string mnemonic, string BaseOp, Operand ImmOp,
   1488                          bits<2> MajOp> {
   1489   let BaseOpcode = "POST_"#BaseOp in {
   1490     def S2_#NAME#_pi : T_StorePI_nv <mnemonic, ImmOp, MajOp>;
   1491 
   1492     // Predicated
   1493     defm S2_p#NAME#t : ST_PostInc_Pred_nv <mnemonic, ImmOp, MajOp, 0>;
   1494     defm S2_p#NAME#f : ST_PostInc_Pred_nv <mnemonic, ImmOp, MajOp, 1>;
   1495   }
   1496 }
   1497 
   1498 let accessSize = ByteAccess in
   1499 defm storerbnew: ST_PostInc_nv <"memb", "STrib", s4_0Imm, 0b00>;
   1500 
   1501 let accessSize = HalfWordAccess in
   1502 defm storerhnew: ST_PostInc_nv <"memh", "STrih", s4_1Imm, 0b01>;
   1503 
   1504 let accessSize = WordAccess in
   1505 defm storerinew: ST_PostInc_nv <"memw", "STriw", s4_2Imm, 0b10>;
   1506 
   1507 //===----------------------------------------------------------------------===//
   1508 // Template class for post increment .new stores with register offset
   1509 //===----------------------------------------------------------------------===//
   1510 let isNewValue = 1, mayStore = 1, isNVStore = 1, opNewValue = 3 in
   1511 class T_StorePI_RegNV <string mnemonic, bits<2> MajOp, MemAccessSize AccessSz>
   1512   : NVInstPI_V4 <(outs IntRegs:$_dst_),
   1513                  (ins IntRegs:$src1, ModRegs:$src2, IntRegs:$src3),
   1514   #mnemonic#"($src1++$src2) = $src3.new",
   1515   [], "$src1 = $_dst_"> {
   1516     bits<5> src1;
   1517     bits<1> src2;
   1518     bits<3> src3;
   1519     let accessSize = AccessSz;
   1520 
   1521     let IClass = 0b1010;
   1522 
   1523     let Inst{27-21} = 0b1101101;
   1524     let Inst{20-16} = src1;
   1525     let Inst{13}    = src2;
   1526     let Inst{12-11} = MajOp;
   1527     let Inst{10-8}  = src3;
   1528     let Inst{7}     = 0b0;
   1529   }
   1530 
   1531 def S2_storerbnew_pr : T_StorePI_RegNV<"memb", 0b00, ByteAccess>;
   1532 def S2_storerhnew_pr : T_StorePI_RegNV<"memh", 0b01, HalfWordAccess>;
   1533 def S2_storerinew_pr : T_StorePI_RegNV<"memw", 0b10, WordAccess>;
   1534 
   1535 // memb(Rx++#s4:0:circ(Mu))=Nt.new
   1536 // memb(Rx++I:circ(Mu))=Nt.new
   1537 // memb(Rx++Mu:brev)=Nt.new
   1538 // memh(Rx++#s4:1:circ(Mu))=Nt.new
   1539 // memh(Rx++I:circ(Mu))=Nt.new
   1540 // memh(Rx++Mu)=Nt.new
   1541 // memh(Rx++Mu:brev)=Nt.new
   1542 
   1543 // memw(Rx++#s4:2:circ(Mu))=Nt.new
   1544 // memw(Rx++I:circ(Mu))=Nt.new
   1545 // memw(Rx++Mu)=Nt.new
   1546 // memw(Rx++Mu:brev)=Nt.new
   1547 
   1548 //===----------------------------------------------------------------------===//
   1549 // NV/ST -
   1550 //===----------------------------------------------------------------------===//
   1551 
   1552 //===----------------------------------------------------------------------===//
   1553 // NV/J +
   1554 //===----------------------------------------------------------------------===//
   1555 
   1556 //===----------------------------------------------------------------------===//
   1557 // multiclass/template class for the new-value compare jumps with the register
   1558 // operands.
   1559 //===----------------------------------------------------------------------===//
   1560 
   1561 let isExtendable = 1, opExtendable = 2, isExtentSigned = 1, opExtentBits = 11,
   1562     opExtentAlign = 2 in
   1563 class NVJrr_template<string mnemonic, bits<3> majOp, bit NvOpNum,
   1564                       bit isNegCond, bit isTak>
   1565   : NVInst_V4<(outs),
   1566     (ins IntRegs:$src1, IntRegs:$src2, brtarget:$offset),
   1567     "if ("#!if(isNegCond, "!","")#mnemonic#
   1568     "($src1"#!if(!eq(NvOpNum, 0),".new, ",", ")#
   1569     "$src2"#!if(!eq(NvOpNum, 1),".new))","))")#" jump:"
   1570     #!if(isTak, "t","nt")#" $offset", []> {
   1571 
   1572       bits<5> src1;
   1573       bits<5> src2;
   1574       bits<3> Ns;    // New-Value Operand
   1575       bits<5> RegOp; // Non-New-Value Operand
   1576       bits<11> offset;
   1577 
   1578       let isTaken = isTak;
   1579       let isPredicatedFalse = isNegCond;
   1580       let opNewValue{0} = NvOpNum;
   1581 
   1582       let Ns = !if(!eq(NvOpNum, 0), src1{2-0}, src2{2-0});
   1583       let RegOp = !if(!eq(NvOpNum, 0), src2, src1);
   1584 
   1585       let IClass = 0b0010;
   1586       let Inst{27-26} = 0b00;
   1587       let Inst{25-23} = majOp;
   1588       let Inst{22} = isNegCond;
   1589       let Inst{18-16} = Ns;
   1590       let Inst{13} = isTak;
   1591       let Inst{12-8} = RegOp;
   1592       let Inst{21-20} = offset{10-9};
   1593       let Inst{7-1} = offset{8-2};
   1594 }
   1595 
   1596 
   1597 multiclass NVJrr_cond<string mnemonic, bits<3> majOp, bit NvOpNum,
   1598                        bit isNegCond> {
   1599   // Branch not taken:
   1600   def _nt: NVJrr_template<mnemonic, majOp, NvOpNum, isNegCond, 0>;
   1601   // Branch taken:
   1602   def _t : NVJrr_template<mnemonic, majOp, NvOpNum, isNegCond, 1>;
   1603 }
   1604 
   1605 // NvOpNum = 0 -> First Operand is a new-value Register
   1606 // NvOpNum = 1 -> Second Operand is a new-value Register
   1607 
   1608 multiclass NVJrr_base<string mnemonic, string BaseOp, bits<3> majOp,
   1609                        bit NvOpNum> {
   1610   let BaseOpcode = BaseOp#_NVJ in {
   1611     defm _t_jumpnv : NVJrr_cond<mnemonic, majOp, NvOpNum, 0>; // True cond
   1612     defm _f_jumpnv : NVJrr_cond<mnemonic, majOp, NvOpNum, 1>; // False cond
   1613   }
   1614 }
   1615 
   1616 // if ([!]cmp.eq(Ns.new,Rt)) jump:[n]t #r9:2
   1617 // if ([!]cmp.gt(Ns.new,Rt)) jump:[n]t #r9:2
   1618 // if ([!]cmp.gtu(Ns.new,Rt)) jump:[n]t #r9:2
   1619 // if ([!]cmp.gt(Rt,Ns.new)) jump:[n]t #r9:2
   1620 // if ([!]cmp.gtu(Rt,Ns.new)) jump:[n]t #r9:2
   1621 
   1622 let isPredicated = 1, isBranch = 1, isNewValue = 1, isTerminator = 1,
   1623     Defs = [PC], hasSideEffects = 0 in {
   1624   defm J4_cmpeq  : NVJrr_base<"cmp.eq",  "CMPEQ",  0b000, 0>, PredRel;
   1625   defm J4_cmpgt  : NVJrr_base<"cmp.gt",  "CMPGT",  0b001, 0>, PredRel;
   1626   defm J4_cmpgtu : NVJrr_base<"cmp.gtu", "CMPGTU", 0b010, 0>, PredRel;
   1627   defm J4_cmplt  : NVJrr_base<"cmp.gt",  "CMPLT",  0b011, 1>, PredRel;
   1628   defm J4_cmpltu : NVJrr_base<"cmp.gtu", "CMPLTU", 0b100, 1>, PredRel;
   1629 }
   1630 
   1631 //===----------------------------------------------------------------------===//
   1632 // multiclass/template class for the new-value compare jumps instruction
   1633 // with a register and an unsigned immediate (U5) operand.
   1634 //===----------------------------------------------------------------------===//
   1635 
   1636 let isExtendable = 1, opExtendable = 2, isExtentSigned = 1, opExtentBits = 11,
   1637     opExtentAlign = 2 in
   1638 class NVJri_template<string mnemonic, bits<3> majOp, bit isNegCond,
   1639                          bit isTak>
   1640   : NVInst_V4<(outs),
   1641     (ins IntRegs:$src1, u5Imm:$src2, brtarget:$offset),
   1642     "if ("#!if(isNegCond, "!","")#mnemonic#"($src1.new, #$src2)) jump:"
   1643     #!if(isTak, "t","nt")#" $offset", []> {
   1644 
   1645       let isTaken = isTak;
   1646       let isPredicatedFalse = isNegCond;
   1647       let isTaken = isTak;
   1648 
   1649       bits<3> src1;
   1650       bits<5> src2;
   1651       bits<11> offset;
   1652 
   1653       let IClass = 0b0010;
   1654       let Inst{26} = 0b1;
   1655       let Inst{25-23} = majOp;
   1656       let Inst{22} = isNegCond;
   1657       let Inst{18-16} = src1;
   1658       let Inst{13} = isTak;
   1659       let Inst{12-8} = src2;
   1660       let Inst{21-20} = offset{10-9};
   1661       let Inst{7-1} = offset{8-2};
   1662 }
   1663 
   1664 multiclass NVJri_cond<string mnemonic, bits<3> majOp, bit isNegCond> {
   1665   // Branch not taken:
   1666   def _nt: NVJri_template<mnemonic, majOp, isNegCond, 0>;
   1667   // Branch taken:
   1668   def _t : NVJri_template<mnemonic, majOp, isNegCond, 1>;
   1669 }
   1670 
   1671 multiclass NVJri_base<string mnemonic, string BaseOp, bits<3> majOp> {
   1672   let BaseOpcode = BaseOp#_NVJri in {
   1673     defm _t_jumpnv : NVJri_cond<mnemonic, majOp, 0>; // True Cond
   1674     defm _f_jumpnv : NVJri_cond<mnemonic, majOp, 1>; // False cond
   1675   }
   1676 }
   1677 
   1678 // if ([!]cmp.eq(Ns.new,#U5)) jump:[n]t #r9:2
   1679 // if ([!]cmp.gt(Ns.new,#U5)) jump:[n]t #r9:2
   1680 // if ([!]cmp.gtu(Ns.new,#U5)) jump:[n]t #r9:2
   1681 
   1682 let isPredicated = 1, isBranch = 1, isNewValue = 1, isTerminator = 1,
   1683     Defs = [PC], hasSideEffects = 0 in {
   1684   defm J4_cmpeqi  : NVJri_base<"cmp.eq", "CMPEQ", 0b000>, PredRel;
   1685   defm J4_cmpgti  : NVJri_base<"cmp.gt", "CMPGT", 0b001>, PredRel;
   1686   defm J4_cmpgtui : NVJri_base<"cmp.gtu", "CMPGTU", 0b010>, PredRel;
   1687 }
   1688 
   1689 //===----------------------------------------------------------------------===//
   1690 // multiclass/template class for the new-value compare jumps instruction
   1691 // with a register and an hardcoded 0/-1 immediate value.
   1692 //===----------------------------------------------------------------------===//
   1693 
   1694 let isExtendable = 1, opExtendable = 1, isExtentSigned = 1, opExtentBits = 11,
   1695     opExtentAlign = 2 in
   1696 class NVJ_ConstImm_template<string mnemonic, bits<3> majOp, string ImmVal,
   1697                             bit isNegCond, bit isTak>
   1698   : NVInst_V4<(outs),
   1699     (ins IntRegs:$src1, brtarget:$offset),
   1700     "if ("#!if(isNegCond, "!","")#mnemonic
   1701     #"($src1.new, #"#ImmVal#")) jump:"
   1702     #!if(isTak, "t","nt")#" $offset", []> {
   1703 
   1704       let isTaken = isTak;
   1705       let isPredicatedFalse = isNegCond;
   1706       let isTaken = isTak;
   1707 
   1708       bits<3> src1;
   1709       bits<11> offset;
   1710       let IClass = 0b0010;
   1711       let Inst{26} = 0b1;
   1712       let Inst{25-23} = majOp;
   1713       let Inst{22} = isNegCond;
   1714       let Inst{18-16} = src1;
   1715       let Inst{13} = isTak;
   1716       let Inst{21-20} = offset{10-9};
   1717       let Inst{7-1} = offset{8-2};
   1718 }
   1719 
   1720 multiclass NVJ_ConstImm_cond<string mnemonic, bits<3> majOp, string ImmVal,
   1721                              bit isNegCond> {
   1722   // Branch not taken:
   1723   def _nt: NVJ_ConstImm_template<mnemonic, majOp, ImmVal, isNegCond, 0>;
   1724   // Branch taken:
   1725   def _t : NVJ_ConstImm_template<mnemonic, majOp, ImmVal, isNegCond, 1>;
   1726 }
   1727 
   1728 multiclass NVJ_ConstImm_base<string mnemonic, string BaseOp, bits<3> majOp,
   1729                              string ImmVal> {
   1730   let BaseOpcode = BaseOp#_NVJ_ConstImm in {
   1731     defm _t_jumpnv : NVJ_ConstImm_cond<mnemonic, majOp, ImmVal, 0>; // True
   1732     defm _f_jumpnv : NVJ_ConstImm_cond<mnemonic, majOp, ImmVal, 1>; // False
   1733   }
   1734 }
   1735 
   1736 // if ([!]tstbit(Ns.new,#0)) jump:[n]t #r9:2
   1737 // if ([!]cmp.eq(Ns.new,#-1)) jump:[n]t #r9:2
   1738 // if ([!]cmp.gt(Ns.new,#-1)) jump:[n]t #r9:2
   1739 
   1740 let isPredicated = 1, isBranch = 1, isNewValue = 1, isTerminator=1,
   1741     Defs = [PC], hasSideEffects = 0 in {
   1742   defm J4_tstbit0 : NVJ_ConstImm_base<"tstbit", "TSTBIT", 0b011, "0">, PredRel;
   1743   defm J4_cmpeqn1 : NVJ_ConstImm_base<"cmp.eq", "CMPEQ",  0b100, "-1">, PredRel;
   1744   defm J4_cmpgtn1 : NVJ_ConstImm_base<"cmp.gt", "CMPGT",  0b101, "-1">, PredRel;
   1745 }
   1746 
   1747 // J4_hintjumpr: Hint indirect conditional jump.
   1748 let isBranch = 1, isIndirectBranch = 1, hasSideEffects = 0 in
   1749 def J4_hintjumpr: JRInst <
   1750   (outs),
   1751   (ins IntRegs:$Rs),
   1752   "hintjr($Rs)"> {
   1753     bits<5> Rs;
   1754     let IClass = 0b0101;
   1755     let Inst{27-21} = 0b0010101;
   1756     let Inst{20-16} = Rs;
   1757   }
   1758 
   1759 //===----------------------------------------------------------------------===//
   1760 // NV/J -
   1761 //===----------------------------------------------------------------------===//
   1762 
   1763 //===----------------------------------------------------------------------===//
   1764 // CR +
   1765 //===----------------------------------------------------------------------===//
   1766 
   1767 // PC-relative add
   1768 let hasNewValue = 1, isExtendable = 1, opExtendable = 1,
   1769     isExtentSigned = 0, opExtentBits = 6, hasSideEffects = 0, Uses = [PC] in
   1770 def C4_addipc : CRInst <(outs IntRegs:$Rd), (ins u6Ext:$u6),
   1771   "$Rd = add(pc, #$u6)", [], "", CR_tc_2_SLOT3 > {
   1772     bits<5> Rd;
   1773     bits<6> u6;
   1774 
   1775     let IClass = 0b0110;
   1776     let Inst{27-16} = 0b101001001001;
   1777     let Inst{12-7} = u6;
   1778     let Inst{4-0} = Rd;
   1779   }
   1780 
   1781 
   1782 
   1783 let hasSideEffects = 0 in
   1784 class T_LOGICAL_3OP<string MnOp1, string MnOp2, bits<2> OpBits, bit IsNeg>
   1785     : CRInst<(outs PredRegs:$Pd),
   1786              (ins PredRegs:$Ps, PredRegs:$Pt, PredRegs:$Pu),
   1787              "$Pd = " # MnOp1 # "($Ps, " # MnOp2 # "($Pt, " #
   1788                    !if (IsNeg,"!","") # "$Pu))",
   1789              [], "", CR_tc_2early_SLOT23> {
   1790   bits<2> Pd;
   1791   bits<2> Ps;
   1792   bits<2> Pt;
   1793   bits<2> Pu;
   1794 
   1795   let IClass = 0b0110;
   1796   let Inst{27-24} = 0b1011;
   1797   let Inst{23} = IsNeg;
   1798   let Inst{22-21} = OpBits;
   1799   let Inst{20} = 0b1;
   1800   let Inst{17-16} = Ps;
   1801   let Inst{13} = 0b0;
   1802   let Inst{9-8} = Pt;
   1803   let Inst{7-6} = Pu;
   1804   let Inst{1-0} = Pd;
   1805 }
   1806 
   1807 def C4_and_and  : T_LOGICAL_3OP<"and", "and", 0b00, 0>;
   1808 def C4_and_or   : T_LOGICAL_3OP<"and", "or",  0b01, 0>;
   1809 def C4_or_and   : T_LOGICAL_3OP<"or",  "and", 0b10, 0>;
   1810 def C4_or_or    : T_LOGICAL_3OP<"or",  "or",  0b11, 0>;
   1811 def C4_and_andn : T_LOGICAL_3OP<"and", "and", 0b00, 1>;
   1812 def C4_and_orn  : T_LOGICAL_3OP<"and", "or",  0b01, 1>;
   1813 def C4_or_andn  : T_LOGICAL_3OP<"or",  "and", 0b10, 1>;
   1814 def C4_or_orn   : T_LOGICAL_3OP<"or",  "or",  0b11, 1>;
   1815 
   1816 // op(Ps, op(Pt, Pu))
   1817 class LogLog_pat<SDNode Op1, SDNode Op2, InstHexagon MI>
   1818   : Pat<(i1 (Op1 I1:$Ps, (Op2 I1:$Pt, I1:$Pu))),
   1819         (MI I1:$Ps, I1:$Pt, I1:$Pu)>;
   1820 
   1821 // op(Ps, op(Pt, ~Pu))
   1822 class LogLogNot_pat<SDNode Op1, SDNode Op2, InstHexagon MI>
   1823   : Pat<(i1 (Op1 I1:$Ps, (Op2 I1:$Pt, (not I1:$Pu)))),
   1824         (MI I1:$Ps, I1:$Pt, I1:$Pu)>;
   1825 
   1826 def: LogLog_pat<and, and, C4_and_and>;
   1827 def: LogLog_pat<and, or,  C4_and_or>;
   1828 def: LogLog_pat<or,  and, C4_or_and>;
   1829 def: LogLog_pat<or,  or,  C4_or_or>;
   1830 
   1831 def: LogLogNot_pat<and, and, C4_and_andn>;
   1832 def: LogLogNot_pat<and, or,  C4_and_orn>;
   1833 def: LogLogNot_pat<or,  and, C4_or_andn>;
   1834 def: LogLogNot_pat<or,  or,  C4_or_orn>;
   1835 
   1836 //===----------------------------------------------------------------------===//
   1837 // PIC: Support for PIC compilations. The patterns and SD nodes defined
   1838 // below are needed to support code generation for PIC
   1839 //===----------------------------------------------------------------------===//
   1840 
   1841 def SDT_HexagonAtGot
   1842   : SDTypeProfile<1, 3, [SDTCisVT<0, i32>, SDTCisVT<1, i32>, SDTCisVT<2, i32>]>;
   1843 def SDT_HexagonAtPcrel
   1844   : SDTypeProfile<1, 1, [SDTCisVT<0, i32>, SDTCisVT<1, i32>]>;
   1845 
   1846 // AT_GOT address-of-GOT, address-of-global, offset-in-global
   1847 def HexagonAtGot       : SDNode<"HexagonISD::AT_GOT", SDT_HexagonAtGot>;
   1848 // AT_PCREL address-of-global
   1849 def HexagonAtPcrel     : SDNode<"HexagonISD::AT_PCREL", SDT_HexagonAtPcrel>;
   1850 
   1851 def: Pat<(HexagonAtGot I32:$got, I32:$addr, (i32 0)),
   1852          (L2_loadri_io I32:$got, imm:$addr)>;
   1853 def: Pat<(HexagonAtGot I32:$got, I32:$addr, s30_2ImmPred:$off),
   1854          (A2_addi (L2_loadri_io I32:$got, imm:$addr), imm:$off)>;
   1855 def: Pat<(HexagonAtPcrel I32:$addr),
   1856          (C4_addipc imm:$addr)>;
   1857 
   1858 //===----------------------------------------------------------------------===//
   1859 // CR -
   1860 //===----------------------------------------------------------------------===//
   1861 
   1862 //===----------------------------------------------------------------------===//
   1863 // XTYPE/ALU +
   1864 //===----------------------------------------------------------------------===//
   1865 
   1866 // Logical with-not instructions.
   1867 def A4_andnp : T_ALU64_logical<"and", 0b001, 1, 0, 1>;
   1868 def A4_ornp  : T_ALU64_logical<"or",  0b011, 1, 0, 1>;
   1869 
   1870 def: Pat<(i64 (and (i64 DoubleRegs:$Rs), (i64 (not (i64 DoubleRegs:$Rt))))),
   1871          (A4_andnp DoubleRegs:$Rs, DoubleRegs:$Rt)>;
   1872 def: Pat<(i64 (or  (i64 DoubleRegs:$Rs), (i64 (not (i64 DoubleRegs:$Rt))))),
   1873          (A4_ornp DoubleRegs:$Rs, DoubleRegs:$Rt)>;
   1874 
   1875 let hasNewValue = 1, hasSideEffects = 0 in
   1876 def S4_parity: ALU64Inst<(outs IntRegs:$Rd), (ins IntRegs:$Rs, IntRegs:$Rt),
   1877       "$Rd = parity($Rs, $Rt)", [], "", ALU64_tc_2_SLOT23> {
   1878   bits<5> Rd;
   1879   bits<5> Rs;
   1880   bits<5> Rt;
   1881 
   1882   let IClass = 0b1101;
   1883   let Inst{27-21} = 0b0101111;
   1884   let Inst{20-16} = Rs;
   1885   let Inst{12-8} = Rt;
   1886   let Inst{4-0} = Rd;
   1887 }
   1888 
   1889 //  Add and accumulate.
   1890 //  Rd=add(Rs,add(Ru,#s6))
   1891 let isExtentSigned = 1, hasNewValue = 1, isExtendable = 1, opExtentBits = 6,
   1892     opExtendable = 3 in
   1893 def S4_addaddi : ALU64Inst <(outs IntRegs:$Rd),
   1894                             (ins IntRegs:$Rs, IntRegs:$Ru, s6Ext:$s6),
   1895   "$Rd = add($Rs, add($Ru, #$s6))" ,
   1896   [(set (i32 IntRegs:$Rd), (add (i32 IntRegs:$Rs),
   1897                            (add (i32 IntRegs:$Ru), s32ImmPred:$s6)))],
   1898   "", ALU64_tc_2_SLOT23> {
   1899     bits<5> Rd;
   1900     bits<5> Rs;
   1901     bits<5> Ru;
   1902     bits<6> s6;
   1903 
   1904     let IClass = 0b1101;
   1905 
   1906     let Inst{27-23} = 0b10110;
   1907     let Inst{22-21} = s6{5-4};
   1908     let Inst{20-16} = Rs;
   1909     let Inst{13}    = s6{3};
   1910     let Inst{12-8}  = Rd;
   1911     let Inst{7-5}   = s6{2-0};
   1912     let Inst{4-0}   = Ru;
   1913   }
   1914 
   1915 let isExtentSigned = 1, hasSideEffects = 0, hasNewValue = 1, isExtendable = 1,
   1916     opExtentBits = 6, opExtendable = 2 in
   1917 def S4_subaddi: ALU64Inst <(outs IntRegs:$Rd),
   1918                            (ins IntRegs:$Rs, s6Ext:$s6, IntRegs:$Ru),
   1919   "$Rd = add($Rs, sub(#$s6, $Ru))",
   1920   [], "", ALU64_tc_2_SLOT23> {
   1921     bits<5> Rd;
   1922     bits<5> Rs;
   1923     bits<6> s6;
   1924     bits<5> Ru;
   1925 
   1926     let IClass = 0b1101;
   1927 
   1928     let Inst{27-23} = 0b10111;
   1929     let Inst{22-21} = s6{5-4};
   1930     let Inst{20-16} = Rs;
   1931     let Inst{13}    = s6{3};
   1932     let Inst{12-8}  = Rd;
   1933     let Inst{7-5}   = s6{2-0};
   1934     let Inst{4-0}   = Ru;
   1935   }
   1936 
   1937 // Rd=add(Rs,sub(#s6,Ru))
   1938 def: Pat<(add (i32 IntRegs:$src1), (sub s32ImmPred:$src2,
   1939                                         (i32 IntRegs:$src3))),
   1940          (S4_subaddi IntRegs:$src1, s32ImmPred:$src2, IntRegs:$src3)>;
   1941 
   1942 // Rd=sub(add(Rs,#s6),Ru)
   1943 def: Pat<(sub (add (i32 IntRegs:$src1), s32ImmPred:$src2),
   1944                    (i32 IntRegs:$src3)),
   1945          (S4_subaddi IntRegs:$src1, s32ImmPred:$src2, IntRegs:$src3)>;
   1946 
   1947 // Rd=add(sub(Rs,Ru),#s6)
   1948 def: Pat<(add (sub (i32 IntRegs:$src1), (i32 IntRegs:$src3)),
   1949                    (s32ImmPred:$src2)),
   1950          (S4_subaddi IntRegs:$src1, s32ImmPred:$src2, IntRegs:$src3)>;
   1951 
   1952 
   1953 //  Add or subtract doublewords with carry.
   1954 //TODO:
   1955 //  Rdd=add(Rss,Rtt,Px):carry
   1956 //TODO:
   1957 //  Rdd=sub(Rss,Rtt,Px):carry
   1958 
   1959 // Extract bitfield
   1960 // Rdd=extract(Rss,#u6,#U6)
   1961 // Rdd=extract(Rss,Rtt)
   1962 // Rd=extract(Rs,Rtt)
   1963 // Rd=extract(Rs,#u5,#U5)
   1964 
   1965 def S4_extractp_rp : T_S3op_64 < "extract",  0b11, 0b100, 0>;
   1966 def S4_extractp    : T_S2op_extract <"extract",  0b1010, DoubleRegs, u6Imm>;
   1967 
   1968 let hasNewValue = 1 in {
   1969   def S4_extract_rp : T_S3op_extract<"extract",  0b01>;
   1970   def S4_extract    : T_S2op_extract <"extract",  0b1101, IntRegs, u5Imm>;
   1971 }
   1972 
   1973 // Complex add/sub halfwords/words
   1974 let Defs = [USR_OVF] in {
   1975   def S4_vxaddsubh : T_S3op_64 < "vxaddsubh", 0b01, 0b100, 0, 1>;
   1976   def S4_vxaddsubw : T_S3op_64 < "vxaddsubw", 0b01, 0b000, 0, 1>;
   1977   def S4_vxsubaddh : T_S3op_64 < "vxsubaddh", 0b01, 0b110, 0, 1>;
   1978   def S4_vxsubaddw : T_S3op_64 < "vxsubaddw", 0b01, 0b010, 0, 1>;
   1979 }
   1980 
   1981 let Defs = [USR_OVF] in {
   1982   def S4_vxaddsubhr : T_S3op_64 < "vxaddsubh", 0b11, 0b000, 0, 1, 1, 1>;
   1983   def S4_vxsubaddhr : T_S3op_64 < "vxsubaddh", 0b11, 0b010, 0, 1, 1, 1>;
   1984 }
   1985 
   1986 let Itinerary = M_tc_3x_SLOT23, Defs = [USR_OVF] in {
   1987   def M4_mac_up_s1_sat: T_MType_acc_rr<"+= mpy", 0b011, 0b000, 0, [], 0, 1, 1>;
   1988   def M4_nac_up_s1_sat: T_MType_acc_rr<"-= mpy", 0b011, 0b001, 0, [], 0, 1, 1>;
   1989 }
   1990 
   1991 // Logical xor with xor accumulation.
   1992 // Rxx^=xor(Rss,Rtt)
   1993 let hasSideEffects = 0 in
   1994 def M4_xor_xacc
   1995   : SInst <(outs DoubleRegs:$Rxx),
   1996            (ins DoubleRegs:$dst2, DoubleRegs:$Rss, DoubleRegs:$Rtt),
   1997   "$Rxx ^= xor($Rss, $Rtt)",
   1998   [(set (i64 DoubleRegs:$Rxx),
   1999    (xor (i64 DoubleRegs:$dst2), (xor (i64 DoubleRegs:$Rss),
   2000                                      (i64 DoubleRegs:$Rtt))))],
   2001   "$dst2 = $Rxx", S_3op_tc_1_SLOT23> {
   2002     bits<5> Rxx;
   2003     bits<5> Rss;
   2004     bits<5> Rtt;
   2005 
   2006     let IClass = 0b1100;
   2007 
   2008     let Inst{27-22} = 0b101010;
   2009     let Inst{20-16} = Rss;
   2010     let Inst{12-8}  = Rtt;
   2011     let Inst{7-5}   = 0b000;
   2012     let Inst{4-0}   = Rxx;
   2013   }
   2014 
   2015 // Rotate and reduce bytes
   2016 // Rdd=vrcrotate(Rss,Rt,#u2)
   2017 let hasSideEffects = 0 in
   2018 def S4_vrcrotate
   2019   : SInst <(outs DoubleRegs:$Rdd),
   2020            (ins DoubleRegs:$Rss, IntRegs:$Rt, u2Imm:$u2),
   2021   "$Rdd = vrcrotate($Rss, $Rt, #$u2)",
   2022   [], "", S_3op_tc_3x_SLOT23> {
   2023     bits<5> Rdd;
   2024     bits<5> Rss;
   2025     bits<5> Rt;
   2026     bits<2> u2;
   2027 
   2028     let IClass = 0b1100;
   2029 
   2030     let Inst{27-22} = 0b001111;
   2031     let Inst{20-16} = Rss;
   2032     let Inst{13}    = u2{1};
   2033     let Inst{12-8}  = Rt;
   2034     let Inst{7-6}   = 0b11;
   2035     let Inst{5}     = u2{0};
   2036     let Inst{4-0}   = Rdd;
   2037   }
   2038 
   2039 // Rotate and reduce bytes with accumulation
   2040 // Rxx+=vrcrotate(Rss,Rt,#u2)
   2041 let hasSideEffects = 0 in
   2042 def S4_vrcrotate_acc
   2043   : SInst <(outs DoubleRegs:$Rxx),
   2044            (ins DoubleRegs:$dst2, DoubleRegs:$Rss, IntRegs:$Rt, u2Imm:$u2),
   2045   "$Rxx += vrcrotate($Rss, $Rt, #$u2)", [],
   2046   "$dst2 = $Rxx", S_3op_tc_3x_SLOT23> {
   2047     bits<5> Rxx;
   2048     bits<5> Rss;
   2049     bits<5> Rt;
   2050     bits<2> u2;
   2051 
   2052     let IClass = 0b1100;
   2053 
   2054     let Inst{27-21} = 0b1011101;
   2055     let Inst{20-16} = Rss;
   2056     let Inst{13}    = u2{1};
   2057     let Inst{12-8}  = Rt;
   2058     let Inst{5}     = u2{0};
   2059     let Inst{4-0}   = Rxx;
   2060   }
   2061 
   2062 // Vector reduce conditional negate halfwords
   2063 let hasSideEffects = 0 in
   2064 def S2_vrcnegh
   2065   : SInst <(outs DoubleRegs:$Rxx),
   2066            (ins DoubleRegs:$dst2, DoubleRegs:$Rss, IntRegs:$Rt),
   2067   "$Rxx += vrcnegh($Rss, $Rt)", [],
   2068   "$dst2 = $Rxx", S_3op_tc_3x_SLOT23> {
   2069     bits<5> Rxx;
   2070     bits<5> Rss;
   2071     bits<5> Rt;
   2072 
   2073     let IClass = 0b1100;
   2074 
   2075     let Inst{27-21} = 0b1011001;
   2076     let Inst{20-16} = Rss;
   2077     let Inst{13}    = 0b1;
   2078     let Inst{12-8}  = Rt;
   2079     let Inst{7-5}   = 0b111;
   2080     let Inst{4-0}   = Rxx;
   2081   }
   2082 
   2083 // Split bitfield
   2084 def A4_bitspliti : T_S2op_2_di <"bitsplit", 0b110, 0b100>;
   2085 
   2086 // Arithmetic/Convergent round
   2087 def A4_cround_ri : T_S2op_2_ii <"cround", 0b111, 0b000>;
   2088 
   2089 def A4_round_ri  : T_S2op_2_ii <"round", 0b111, 0b100>;
   2090 
   2091 let Defs = [USR_OVF] in
   2092 def A4_round_ri_sat : T_S2op_2_ii <"round", 0b111, 0b110, 1>;
   2093 
   2094 // Logical-logical words.
   2095 // Compound or-and -- Rx=or(Ru,and(Rx,#s10))
   2096 let isExtentSigned = 1, hasNewValue = 1, isExtendable = 1, opExtentBits = 10,
   2097     opExtendable = 3 in
   2098 def S4_or_andix:
   2099   ALU64Inst<(outs IntRegs:$Rx),
   2100             (ins IntRegs:$Ru, IntRegs:$_src_, s10Ext:$s10),
   2101   "$Rx = or($Ru, and($_src_, #$s10))" ,
   2102   [(set (i32 IntRegs:$Rx),
   2103         (or (i32 IntRegs:$Ru), (and (i32 IntRegs:$_src_), s32ImmPred:$s10)))] ,
   2104   "$_src_ = $Rx", ALU64_tc_2_SLOT23> {
   2105     bits<5> Rx;
   2106     bits<5> Ru;
   2107     bits<10> s10;
   2108 
   2109     let IClass = 0b1101;
   2110 
   2111     let Inst{27-22} = 0b101001;
   2112     let Inst{20-16} = Rx;
   2113     let Inst{21}    = s10{9};
   2114     let Inst{13-5}  = s10{8-0};
   2115     let Inst{4-0}   = Ru;
   2116   }
   2117 
   2118 // Miscellaneous ALU64 instructions.
   2119 //
   2120 let hasNewValue = 1, hasSideEffects = 0 in
   2121 def A4_modwrapu: ALU64Inst<(outs IntRegs:$Rd), (ins IntRegs:$Rs, IntRegs:$Rt),
   2122       "$Rd = modwrap($Rs, $Rt)", [], "", ALU64_tc_2_SLOT23> {
   2123   bits<5> Rd;
   2124   bits<5> Rs;
   2125   bits<5> Rt;
   2126 
   2127   let IClass = 0b1101;
   2128   let Inst{27-21} = 0b0011111;
   2129   let Inst{20-16} = Rs;
   2130   let Inst{12-8} = Rt;
   2131   let Inst{7-5} = 0b111;
   2132   let Inst{4-0} = Rd;
   2133 }
   2134 
   2135 let hasSideEffects = 0 in
   2136 def A4_bitsplit: ALU64Inst<(outs DoubleRegs:$Rd),
   2137       (ins IntRegs:$Rs, IntRegs:$Rt),
   2138       "$Rd = bitsplit($Rs, $Rt)", [], "", ALU64_tc_1_SLOT23> {
   2139   bits<5> Rd;
   2140   bits<5> Rs;
   2141   bits<5> Rt;
   2142 
   2143   let IClass = 0b1101;
   2144   let Inst{27-24} = 0b0100;
   2145   let Inst{21} = 0b1;
   2146   let Inst{20-16} = Rs;
   2147   let Inst{12-8} = Rt;
   2148   let Inst{4-0} = Rd;
   2149 }
   2150 
   2151 let hasSideEffects = 0 in
   2152 def dep_S2_packhl: ALU64Inst<(outs DoubleRegs:$Rd),
   2153       (ins IntRegs:$Rs, IntRegs:$Rt),
   2154       "$Rd = packhl($Rs, $Rt):deprecated", [], "", ALU64_tc_1_SLOT23> {
   2155   bits<5> Rd;
   2156   bits<5> Rs;
   2157   bits<5> Rt;
   2158 
   2159   let IClass = 0b1101;
   2160   let Inst{27-24} = 0b0100;
   2161   let Inst{21} = 0b0;
   2162   let Inst{20-16} = Rs;
   2163   let Inst{12-8} = Rt;
   2164   let Inst{4-0} = Rd;
   2165 }
   2166 
   2167 let hasNewValue = 1, hasSideEffects = 0 in
   2168 def dep_A2_addsat: ALU64Inst<(outs IntRegs:$Rd),
   2169       (ins IntRegs:$Rs, IntRegs:$Rt),
   2170       "$Rd = add($Rs, $Rt):sat:deprecated", [], "", ALU64_tc_2_SLOT23> {
   2171   bits<5> Rd;
   2172   bits<5> Rs;
   2173   bits<5> Rt;
   2174 
   2175   let IClass = 0b1101;
   2176   let Inst{27-21} = 0b0101100;
   2177   let Inst{20-16} = Rs;
   2178   let Inst{12-8} = Rt;
   2179   let Inst{7} = 0b0;
   2180   let Inst{4-0} = Rd;
   2181 }
   2182 
   2183 let hasNewValue = 1, hasSideEffects = 0 in
   2184 def dep_A2_subsat: ALU64Inst<(outs IntRegs:$Rd),
   2185       (ins IntRegs:$Rs, IntRegs:$Rt),
   2186       "$Rd = sub($Rs, $Rt):sat:deprecated", [], "", ALU64_tc_2_SLOT23> {
   2187   bits<5> Rd;
   2188   bits<5> Rs;
   2189   bits<5> Rt;
   2190 
   2191   let IClass = 0b1101;
   2192   let Inst{27-21} = 0b0101100;
   2193   let Inst{20-16} = Rt;
   2194   let Inst{12-8} = Rs;
   2195   let Inst{7} = 0b1;
   2196   let Inst{4-0} = Rd;
   2197 }
   2198 
   2199 // Rx[&|]=xor(Rs,Rt)
   2200 def M4_or_xor   : T_MType_acc_rr < "|= xor", 0b110, 0b001, 0>;
   2201 def M4_and_xor  : T_MType_acc_rr < "&= xor", 0b010, 0b010, 0>;
   2202 
   2203 // Rx[&|^]=or(Rs,Rt)
   2204 def M4_xor_or   : T_MType_acc_rr < "^= or",  0b110, 0b011, 0>;
   2205 
   2206 let CextOpcode = "ORr_ORr" in
   2207 def M4_or_or    : T_MType_acc_rr < "|= or",  0b110, 0b000, 0>;
   2208 def M4_and_or   : T_MType_acc_rr < "&= or",  0b010, 0b001, 0>;
   2209 
   2210 // Rx[&|^]=and(Rs,Rt)
   2211 def M4_xor_and  : T_MType_acc_rr < "^= and", 0b110, 0b010, 0>;
   2212 
   2213 let CextOpcode = "ORr_ANDr" in
   2214 def M4_or_and   : T_MType_acc_rr < "|= and", 0b010, 0b011, 0>;
   2215 def M4_and_and  : T_MType_acc_rr < "&= and", 0b010, 0b000, 0>;
   2216 
   2217 // Rx[&|^]=and(Rs,~Rt)
   2218 def M4_xor_andn : T_MType_acc_rr < "^= and", 0b001, 0b010, 0, [], 1>;
   2219 def M4_or_andn  : T_MType_acc_rr < "|= and", 0b001, 0b000, 0, [], 1>;
   2220 def M4_and_andn : T_MType_acc_rr < "&= and", 0b001, 0b001, 0, [], 1>;
   2221 
   2222 def: T_MType_acc_pat2 <M4_or_xor, xor, or>;
   2223 def: T_MType_acc_pat2 <M4_and_xor, xor, and>;
   2224 def: T_MType_acc_pat2 <M4_or_and, and, or>;
   2225 def: T_MType_acc_pat2 <M4_and_and, and, and>;
   2226 def: T_MType_acc_pat2 <M4_xor_and, and, xor>;
   2227 def: T_MType_acc_pat2 <M4_or_or, or, or>;
   2228 def: T_MType_acc_pat2 <M4_and_or, or, and>;
   2229 def: T_MType_acc_pat2 <M4_xor_or, or, xor>;
   2230 
   2231 class T_MType_acc_pat3 <InstHexagon MI, SDNode firstOp, SDNode secOp>
   2232   : Pat <(i32 (secOp IntRegs:$src1, (firstOp IntRegs:$src2,
   2233                                               (not IntRegs:$src3)))),
   2234          (i32 (MI IntRegs:$src1, IntRegs:$src2, IntRegs:$src3))>;
   2235 
   2236 def: T_MType_acc_pat3 <M4_or_andn, and, or>;
   2237 def: T_MType_acc_pat3 <M4_and_andn, and, and>;
   2238 def: T_MType_acc_pat3 <M4_xor_andn, and, xor>;
   2239 
   2240 // Compound or-or and or-and
   2241 let isExtentSigned = 1, InputType = "imm", hasNewValue = 1, isExtendable = 1,
   2242     opExtentBits = 10, opExtendable = 3 in
   2243 class T_CompOR <string mnemonic, bits<2> MajOp, SDNode OpNode>
   2244   : MInst_acc <(outs IntRegs:$Rx),
   2245                (ins IntRegs:$src1, IntRegs:$Rs, s10Ext:$s10),
   2246   "$Rx |= "#mnemonic#"($Rs, #$s10)",
   2247   [(set (i32 IntRegs:$Rx), (or (i32 IntRegs:$src1),
   2248                            (OpNode (i32 IntRegs:$Rs), s32ImmPred:$s10)))],
   2249   "$src1 = $Rx", ALU64_tc_2_SLOT23>, ImmRegRel {
   2250     bits<5> Rx;
   2251     bits<5> Rs;
   2252     bits<10> s10;
   2253 
   2254     let IClass = 0b1101;
   2255 
   2256     let Inst{27-24} = 0b1010;
   2257     let Inst{23-22} = MajOp;
   2258     let Inst{20-16} = Rs;
   2259     let Inst{21}    = s10{9};
   2260     let Inst{13-5}  = s10{8-0};
   2261     let Inst{4-0}   = Rx;
   2262   }
   2263 
   2264 let CextOpcode = "ORr_ANDr" in
   2265 def S4_or_andi : T_CompOR <"and", 0b00, and>;
   2266 
   2267 let CextOpcode = "ORr_ORr" in
   2268 def S4_or_ori : T_CompOR <"or", 0b10, or>;
   2269 
   2270 //    Modulo wrap
   2271 //        Rd=modwrap(Rs,Rt)
   2272 //    Round
   2273 //        Rd=cround(Rs,#u5)
   2274 //        Rd=cround(Rs,Rt)
   2275 //        Rd=round(Rs,#u5)[:sat]
   2276 //        Rd=round(Rs,Rt)[:sat]
   2277 //    Vector reduce add unsigned halfwords
   2278 //        Rd=vraddh(Rss,Rtt)
   2279 //    Vector add bytes
   2280 //        Rdd=vaddb(Rss,Rtt)
   2281 //    Vector conditional negate
   2282 //        Rdd=vcnegh(Rss,Rt)
   2283 //        Rxx+=vrcnegh(Rss,Rt)
   2284 //    Vector maximum bytes
   2285 //        Rdd=vmaxb(Rtt,Rss)
   2286 //    Vector reduce maximum halfwords
   2287 //        Rxx=vrmaxh(Rss,Ru)
   2288 //        Rxx=vrmaxuh(Rss,Ru)
   2289 //    Vector reduce maximum words
   2290 //        Rxx=vrmaxuw(Rss,Ru)
   2291 //        Rxx=vrmaxw(Rss,Ru)
   2292 //    Vector minimum bytes
   2293 //        Rdd=vminb(Rtt,Rss)
   2294 //    Vector reduce minimum halfwords
   2295 //        Rxx=vrminh(Rss,Ru)
   2296 //        Rxx=vrminuh(Rss,Ru)
   2297 //    Vector reduce minimum words
   2298 //        Rxx=vrminuw(Rss,Ru)
   2299 //        Rxx=vrminw(Rss,Ru)
   2300 //    Vector subtract bytes
   2301 //        Rdd=vsubb(Rss,Rtt)
   2302 
   2303 //===----------------------------------------------------------------------===//
   2304 // XTYPE/ALU -
   2305 //===----------------------------------------------------------------------===//
   2306 
   2307 //===----------------------------------------------------------------------===//
   2308 // XTYPE/BIT +
   2309 //===----------------------------------------------------------------------===//
   2310 
   2311 // Bit reverse
   2312 def S2_brevp : T_S2op_3 <"brev", 0b11, 0b110>;
   2313 
   2314 // Bit count
   2315 def S2_ct0p : T_COUNT_LEADING_64<"ct0", 0b111, 0b010>;
   2316 def S2_ct1p : T_COUNT_LEADING_64<"ct1", 0b111, 0b100>;
   2317 def S4_clbpnorm : T_COUNT_LEADING_64<"normamt", 0b011, 0b000>;
   2318 
   2319 // Count trailing zeros: 64-bit.
   2320 def: Pat<(i32 (trunc (cttz I64:$Rss))), (S2_ct0p I64:$Rss)>;
   2321 def: Pat<(i32 (trunc (cttz_zero_undef I64:$Rss))), (S2_ct0p I64:$Rss)>;
   2322 
   2323 // Count trailing ones: 64-bit.
   2324 def: Pat<(i32 (trunc (cttz (not I64:$Rss)))), (S2_ct1p I64:$Rss)>;
   2325 def: Pat<(i32 (trunc (cttz_zero_undef (not I64:$Rss)))), (S2_ct1p I64:$Rss)>;
   2326 
   2327 // Define leading/trailing patterns that require zero-extensions to 64 bits.
   2328 def: Pat<(i64 (ctlz I64:$Rss)), (Zext64 (S2_cl0p I64:$Rss))>;
   2329 def: Pat<(i64 (ctlz_zero_undef I64:$Rss)), (Zext64 (S2_cl0p I64:$Rss))>;
   2330 def: Pat<(i64 (cttz I64:$Rss)), (Zext64 (S2_ct0p I64:$Rss))>;
   2331 def: Pat<(i64 (cttz_zero_undef I64:$Rss)), (Zext64 (S2_ct0p I64:$Rss))>;
   2332 def: Pat<(i64 (ctlz (not I64:$Rss))), (Zext64 (S2_cl1p I64:$Rss))>;
   2333 def: Pat<(i64 (ctlz_zero_undef (not I64:$Rss))), (Zext64 (S2_cl1p I64:$Rss))>;
   2334 def: Pat<(i64 (cttz (not I64:$Rss))), (Zext64 (S2_ct1p I64:$Rss))>;
   2335 def: Pat<(i64 (cttz_zero_undef (not I64:$Rss))), (Zext64 (S2_ct1p I64:$Rss))>;
   2336 
   2337 
   2338 let hasSideEffects = 0, hasNewValue = 1 in
   2339 def S4_clbaddi : SInst<(outs IntRegs:$Rd), (ins IntRegs:$Rs, s6Imm:$s6),
   2340     "$Rd = add(clb($Rs), #$s6)", [], "", S_2op_tc_2_SLOT23> {
   2341   bits<5> Rs;
   2342   bits<5> Rd;
   2343   bits<6> s6;
   2344   let IClass = 0b1000;
   2345   let Inst{27-24} = 0b1100;
   2346   let Inst{23-21} = 0b001;
   2347   let Inst{20-16} = Rs;
   2348   let Inst{13-8} = s6;
   2349   let Inst{7-5} = 0b000;
   2350   let Inst{4-0} = Rd;
   2351 }
   2352 
   2353 let hasSideEffects = 0, hasNewValue = 1 in
   2354 def S4_clbpaddi : SInst<(outs IntRegs:$Rd), (ins DoubleRegs:$Rs, s6Imm:$s6),
   2355     "$Rd = add(clb($Rs), #$s6)", [], "", S_2op_tc_2_SLOT23> {
   2356   bits<5> Rs;
   2357   bits<5> Rd;
   2358   bits<6> s6;
   2359   let IClass = 0b1000;
   2360   let Inst{27-24} = 0b1000;
   2361   let Inst{23-21} = 0b011;
   2362   let Inst{20-16} = Rs;
   2363   let Inst{13-8} = s6;
   2364   let Inst{7-5} = 0b010;
   2365   let Inst{4-0} = Rd;
   2366 }
   2367 
   2368 
   2369 // Bit test/set/clear
   2370 def S4_ntstbit_i : T_TEST_BIT_IMM<"!tstbit", 0b001>;
   2371 def S4_ntstbit_r : T_TEST_BIT_REG<"!tstbit", 1>;
   2372 
   2373 let AddedComplexity = 20 in {   // Complexity greater than cmp reg-imm.
   2374   def: Pat<(i1 (seteq (and (shl 1, u5ImmPred:$u5), (i32 IntRegs:$Rs)), 0)),
   2375            (S4_ntstbit_i (i32 IntRegs:$Rs), u5ImmPred:$u5)>;
   2376   def: Pat<(i1 (seteq (and (shl 1, (i32 IntRegs:$Rt)), (i32 IntRegs:$Rs)), 0)),
   2377            (S4_ntstbit_r (i32 IntRegs:$Rs), (i32 IntRegs:$Rt))>;
   2378 }
   2379 
   2380 // Add extra complexity to prefer these instructions over bitsset/bitsclr.
   2381 // The reason is that tstbit/ntstbit can be folded into a compound instruction:
   2382 //   if ([!]tstbit(...)) jump ...
   2383 let AddedComplexity = 100 in
   2384 def: Pat<(i1 (setne (and (i32 IntRegs:$Rs), (i32 Set5ImmPred:$u5)), (i32 0))),
   2385          (S2_tstbit_i (i32 IntRegs:$Rs), (BITPOS32 Set5ImmPred:$u5))>;
   2386 
   2387 let AddedComplexity = 100 in
   2388 def: Pat<(i1 (seteq (and (i32 IntRegs:$Rs), (i32 Set5ImmPred:$u5)), (i32 0))),
   2389          (S4_ntstbit_i (i32 IntRegs:$Rs), (BITPOS32 Set5ImmPred:$u5))>;
   2390 
   2391 def C4_nbitsset  : T_TEST_BITS_REG<"!bitsset", 0b01, 1>;
   2392 def C4_nbitsclr  : T_TEST_BITS_REG<"!bitsclr", 0b10, 1>;
   2393 def C4_nbitsclri : T_TEST_BITS_IMM<"!bitsclr", 0b10, 1>;
   2394 
   2395 // Do not increase complexity of these patterns. In the DAG, "cmp i8" may be
   2396 // represented as a compare against "value & 0xFF", which is an exact match
   2397 // for cmpb (same for cmph). The patterns below do not contain any additional
   2398 // complexity that would make them preferable, and if they were actually used
   2399 // instead of cmpb/cmph, they would result in a compare against register that
   2400 // is loaded with the byte/half mask (i.e. 0xFF or 0xFFFF).
   2401 def: Pat<(i1 (setne (and I32:$Rs, u6ImmPred:$u6), 0)),
   2402          (C4_nbitsclri I32:$Rs, u6ImmPred:$u6)>;
   2403 def: Pat<(i1 (setne (and I32:$Rs, I32:$Rt), 0)),
   2404          (C4_nbitsclr I32:$Rs, I32:$Rt)>;
   2405 def: Pat<(i1 (setne (and I32:$Rs, I32:$Rt), I32:$Rt)),
   2406          (C4_nbitsset I32:$Rs, I32:$Rt)>;
   2407 
   2408 //===----------------------------------------------------------------------===//
   2409 // XTYPE/BIT -
   2410 //===----------------------------------------------------------------------===//
   2411 
   2412 //===----------------------------------------------------------------------===//
   2413 // XTYPE/MPY +
   2414 //===----------------------------------------------------------------------===//
   2415 
   2416 // Rd=add(#u6,mpyi(Rs,#U6)) -- Multiply by immed and add immed.
   2417 
   2418 let hasNewValue = 1, isExtendable = 1, opExtentBits = 6, opExtendable = 1 in
   2419 def M4_mpyri_addi : MInst<(outs IntRegs:$Rd),
   2420   (ins u6Ext:$u6, IntRegs:$Rs, u6Imm:$U6),
   2421   "$Rd = add(#$u6, mpyi($Rs, #$U6))" ,
   2422   [(set (i32 IntRegs:$Rd),
   2423         (add (mul (i32 IntRegs:$Rs), u6ImmPred:$U6),
   2424              u32ImmPred:$u6))] ,"",ALU64_tc_3x_SLOT23> {
   2425     bits<5> Rd;
   2426     bits<6> u6;
   2427     bits<5> Rs;
   2428     bits<6> U6;
   2429 
   2430     let IClass = 0b1101;
   2431 
   2432     let Inst{27-24} = 0b1000;
   2433     let Inst{23}    = U6{5};
   2434     let Inst{22-21} = u6{5-4};
   2435     let Inst{20-16} = Rs;
   2436     let Inst{13}    = u6{3};
   2437     let Inst{12-8}  = Rd;
   2438     let Inst{7-5}   = u6{2-0};
   2439     let Inst{4-0}   = U6{4-0};
   2440   }
   2441 
   2442 // Rd=add(#u6,mpyi(Rs,Rt))
   2443 let CextOpcode = "ADD_MPY", InputType = "imm", hasNewValue = 1,
   2444     isExtendable = 1, opExtentBits = 6, opExtendable = 1 in
   2445 def M4_mpyrr_addi : MInst <(outs IntRegs:$Rd),
   2446   (ins u6Ext:$u6, IntRegs:$Rs, IntRegs:$Rt),
   2447   "$Rd = add(#$u6, mpyi($Rs, $Rt))" ,
   2448   [(set (i32 IntRegs:$Rd),
   2449         (add (mul (i32 IntRegs:$Rs), (i32 IntRegs:$Rt)), u32ImmPred:$u6))],
   2450   "", ALU64_tc_3x_SLOT23>, ImmRegRel {
   2451     bits<5> Rd;
   2452     bits<6> u6;
   2453     bits<5> Rs;
   2454     bits<5> Rt;
   2455 
   2456     let IClass = 0b1101;
   2457 
   2458     let Inst{27-23} = 0b01110;
   2459     let Inst{22-21} = u6{5-4};
   2460     let Inst{20-16} = Rs;
   2461     let Inst{13}    = u6{3};
   2462     let Inst{12-8}  = Rt;
   2463     let Inst{7-5}   = u6{2-0};
   2464     let Inst{4-0}   = Rd;
   2465   }
   2466 
   2467 let hasNewValue = 1 in
   2468 class T_AddMpy <bit MajOp, PatLeaf ImmPred, dag ins>
   2469   : ALU64Inst <(outs IntRegs:$dst), ins,
   2470   "$dst = add($src1, mpyi("#!if(MajOp,"$src3, #$src2))",
   2471                                       "#$src2, $src3))"),
   2472   [(set (i32 IntRegs:$dst),
   2473         (add (i32 IntRegs:$src1), (mul (i32 IntRegs:$src3), ImmPred:$src2)))],
   2474   "", ALU64_tc_3x_SLOT23> {
   2475     bits<5> dst;
   2476     bits<5> src1;
   2477     bits<8> src2;
   2478     bits<5> src3;
   2479 
   2480     let IClass = 0b1101;
   2481 
   2482     bits<6> ImmValue = !if(MajOp, src2{5-0}, src2{7-2});
   2483 
   2484     let Inst{27-24} = 0b1111;
   2485     let Inst{23}    = MajOp;
   2486     let Inst{22-21} = ImmValue{5-4};
   2487     let Inst{20-16} = src3;
   2488     let Inst{13}    = ImmValue{3};
   2489     let Inst{12-8}  = dst;
   2490     let Inst{7-5}   = ImmValue{2-0};
   2491     let Inst{4-0}   = src1;
   2492   }
   2493 
   2494 def M4_mpyri_addr_u2 : T_AddMpy<0b0, u6_2ImmPred,
   2495                        (ins IntRegs:$src1, u6_2Imm:$src2, IntRegs:$src3)>;
   2496 
   2497 let isExtendable = 1, opExtentBits = 6, opExtendable = 3,
   2498     CextOpcode = "ADD_MPY", InputType = "imm" in
   2499 def M4_mpyri_addr : T_AddMpy<0b1, u32ImmPred,
   2500                     (ins IntRegs:$src1, IntRegs:$src3, u6Ext:$src2)>, ImmRegRel;
   2501 
   2502 // Rx=add(Ru,mpyi(Rx,Rs))
   2503 let CextOpcode = "ADD_MPY", InputType = "reg", hasNewValue = 1 in
   2504 def M4_mpyrr_addr: MInst_acc <(outs IntRegs:$Rx),
   2505                               (ins IntRegs:$Ru, IntRegs:$_src_, IntRegs:$Rs),
   2506   "$Rx = add($Ru, mpyi($_src_, $Rs))",
   2507   [(set (i32 IntRegs:$Rx), (add (i32 IntRegs:$Ru),
   2508                            (mul (i32 IntRegs:$_src_), (i32 IntRegs:$Rs))))],
   2509   "$_src_ = $Rx", M_tc_3x_SLOT23>, ImmRegRel {
   2510     bits<5> Rx;
   2511     bits<5> Ru;
   2512     bits<5> Rs;
   2513 
   2514     let IClass = 0b1110;
   2515 
   2516     let Inst{27-21} = 0b0011000;
   2517     let Inst{12-8} = Rx;
   2518     let Inst{4-0} = Ru;
   2519     let Inst{20-16} = Rs;
   2520   }
   2521 
   2522 
   2523 // Vector reduce multiply word by signed half (32x16)
   2524 //Rdd=vrmpyweh(Rss,Rtt)[:<<1]
   2525 def M4_vrmpyeh_s0 : T_M2_vmpy<"vrmpyweh", 0b010, 0b100, 0, 0, 0>;
   2526 def M4_vrmpyeh_s1 : T_M2_vmpy<"vrmpyweh", 0b110, 0b100, 1, 0, 0>;
   2527 
   2528 //Rdd=vrmpywoh(Rss,Rtt)[:<<1]
   2529 def M4_vrmpyoh_s0 : T_M2_vmpy<"vrmpywoh", 0b001, 0b010, 0, 0, 0>;
   2530 def M4_vrmpyoh_s1 : T_M2_vmpy<"vrmpywoh", 0b101, 0b010, 1, 0, 0>;
   2531 
   2532 //Rdd+=vrmpyweh(Rss,Rtt)[:<<1]
   2533 def M4_vrmpyeh_acc_s0: T_M2_vmpy_acc<"vrmpyweh", 0b001, 0b110, 0, 0>;
   2534 def M4_vrmpyeh_acc_s1: T_M2_vmpy_acc<"vrmpyweh", 0b101, 0b110, 1, 0>;
   2535 
   2536 //Rdd=vrmpywoh(Rss,Rtt)[:<<1]
   2537 def M4_vrmpyoh_acc_s0: T_M2_vmpy_acc<"vrmpywoh", 0b011, 0b110, 0, 0>;
   2538 def M4_vrmpyoh_acc_s1: T_M2_vmpy_acc<"vrmpywoh", 0b111, 0b110, 1, 0>;
   2539 
   2540 // Vector multiply halfwords, signed by unsigned
   2541 // Rdd=vmpyhsu(Rs,Rt)[:<<]:sat
   2542 def M2_vmpy2su_s0 : T_XTYPE_mpy64 < "vmpyhsu", 0b000, 0b111, 1, 0, 0>;
   2543 def M2_vmpy2su_s1 : T_XTYPE_mpy64 < "vmpyhsu", 0b100, 0b111, 1, 1, 0>;
   2544 
   2545 // Rxx+=vmpyhsu(Rs,Rt)[:<<1]:sat
   2546 def M2_vmac2su_s0 : T_XTYPE_mpy64_acc < "vmpyhsu", "+", 0b011, 0b101, 1, 0, 0>;
   2547 def M2_vmac2su_s1 : T_XTYPE_mpy64_acc < "vmpyhsu", "+", 0b111, 0b101, 1, 1, 0>;
   2548 
   2549 // Vector polynomial multiply halfwords
   2550 // Rdd=vpmpyh(Rs,Rt)
   2551 def M4_vpmpyh : T_XTYPE_mpy64 < "vpmpyh", 0b110, 0b111, 0, 0, 0>;
   2552 
   2553 // Rxx^=vpmpyh(Rs,Rt)
   2554 def M4_vpmpyh_acc : T_XTYPE_mpy64_acc < "vpmpyh", "^", 0b101, 0b111, 0, 0, 0>;
   2555 
   2556 // Polynomial multiply words
   2557 // Rdd=pmpyw(Rs,Rt)
   2558 def M4_pmpyw : T_XTYPE_mpy64 < "pmpyw", 0b010, 0b111, 0, 0, 0>;
   2559 
   2560 // Rxx^=pmpyw(Rs,Rt)
   2561 def M4_pmpyw_acc  : T_XTYPE_mpy64_acc < "pmpyw", "^", 0b001, 0b111, 0, 0, 0>;
   2562 
   2563 //===----------------------------------------------------------------------===//
   2564 // XTYPE/MPY -
   2565 //===----------------------------------------------------------------------===//
   2566 
   2567 //===----------------------------------------------------------------------===//
   2568 // ALU64/Vector compare
   2569 //===----------------------------------------------------------------------===//
   2570 //===----------------------------------------------------------------------===//
   2571 // Template class for vector compare
   2572 //===----------------------------------------------------------------------===//
   2573 
   2574 let hasSideEffects = 0 in
   2575 class T_vcmpImm <string Str, bits<2> cmpOp, bits<2> minOp, Operand ImmOprnd>
   2576   : ALU64_rr <(outs PredRegs:$Pd),
   2577               (ins DoubleRegs:$Rss, ImmOprnd:$Imm),
   2578   "$Pd = "#Str#"($Rss, #$Imm)",
   2579   [], "", ALU64_tc_2early_SLOT23> {
   2580     bits<2> Pd;
   2581     bits<5> Rss;
   2582     bits<32> Imm;
   2583     bits<8> ImmBits;
   2584     let ImmBits{6-0} = Imm{6-0};
   2585     let ImmBits{7} = !if (!eq(cmpOp,0b10), 0b0, Imm{7}); // 0 for vcmp[bhw].gtu
   2586 
   2587     let IClass = 0b1101;
   2588 
   2589     let Inst{27-24} = 0b1100;
   2590     let Inst{22-21} = cmpOp;
   2591     let Inst{20-16} = Rss;
   2592     let Inst{12-5} = ImmBits;
   2593     let Inst{4-3} = minOp;
   2594     let Inst{1-0} = Pd;
   2595   }
   2596 
   2597 // Vector compare bytes
   2598 def A4_vcmpbgt   : T_vcmp <"vcmpb.gt", 0b1010>;
   2599 def: T_vcmp_pat<A4_vcmpbgt, setgt, v8i8>;
   2600 
   2601 let AsmString = "$Pd = any8(vcmpb.eq($Rss, $Rtt))" in
   2602 def A4_vcmpbeq_any : T_vcmp <"any8(vcmpb.gt", 0b1000>;
   2603 
   2604 def A4_vcmpbeqi  : T_vcmpImm <"vcmpb.eq",  0b00, 0b00, u8Imm>;
   2605 def A4_vcmpbgti  : T_vcmpImm <"vcmpb.gt",  0b01, 0b00, s8Imm>;
   2606 def A4_vcmpbgtui : T_vcmpImm <"vcmpb.gtu", 0b10, 0b00, u7Imm>;
   2607 
   2608 // Vector compare halfwords
   2609 def A4_vcmpheqi  : T_vcmpImm <"vcmph.eq",  0b00, 0b01, s8Imm>;
   2610 def A4_vcmphgti  : T_vcmpImm <"vcmph.gt",  0b01, 0b01, s8Imm>;
   2611 def A4_vcmphgtui : T_vcmpImm <"vcmph.gtu", 0b10, 0b01, u7Imm>;
   2612 
   2613 // Vector compare words
   2614 def A4_vcmpweqi  : T_vcmpImm <"vcmpw.eq",  0b00, 0b10, s8Imm>;
   2615 def A4_vcmpwgti  : T_vcmpImm <"vcmpw.gt",  0b01, 0b10, s8Imm>;
   2616 def A4_vcmpwgtui : T_vcmpImm <"vcmpw.gtu", 0b10, 0b10, u7Imm>;
   2617 
   2618 //===----------------------------------------------------------------------===//
   2619 // XTYPE/SHIFT +
   2620 //===----------------------------------------------------------------------===//
   2621 // Shift by immediate and accumulate/logical.
   2622 // Rx=add(#u8,asl(Rx,#U5))  Rx=add(#u8,lsr(Rx,#U5))
   2623 // Rx=sub(#u8,asl(Rx,#U5))  Rx=sub(#u8,lsr(Rx,#U5))
   2624 // Rx=and(#u8,asl(Rx,#U5))  Rx=and(#u8,lsr(Rx,#U5))
   2625 // Rx=or(#u8,asl(Rx,#U5))   Rx=or(#u8,lsr(Rx,#U5))
   2626 let isExtendable = 1, opExtendable = 1, isExtentSigned = 0, opExtentBits = 8,
   2627     hasNewValue = 1, opNewValue = 0 in
   2628 class T_S4_ShiftOperate<string MnOp, string MnSh, SDNode Op, SDNode Sh,
   2629                         bit asl_lsr, bits<2> MajOp, InstrItinClass Itin>
   2630   : MInst_acc<(outs IntRegs:$Rd), (ins u8Ext:$u8, IntRegs:$Rx, u5Imm:$U5),
   2631       "$Rd = "#MnOp#"(#$u8, "#MnSh#"($Rx, #$U5))",
   2632       [(set (i32 IntRegs:$Rd),
   2633             (Op (Sh I32:$Rx, u5ImmPred:$U5), u32ImmPred:$u8))],
   2634       "$Rd = $Rx", Itin> {
   2635 
   2636   bits<5> Rd;
   2637   bits<8> u8;
   2638   bits<5> Rx;
   2639   bits<5> U5;
   2640 
   2641   let IClass = 0b1101;
   2642   let Inst{27-24} = 0b1110;
   2643   let Inst{23-21} = u8{7-5};
   2644   let Inst{20-16} = Rd;
   2645   let Inst{13} = u8{4};
   2646   let Inst{12-8} = U5;
   2647   let Inst{7-5} = u8{3-1};
   2648   let Inst{4} = asl_lsr;
   2649   let Inst{3} = u8{0};
   2650   let Inst{2-1} = MajOp;
   2651 }
   2652 
   2653 multiclass T_ShiftOperate<string mnemonic, SDNode Op, bits<2> MajOp,
   2654                           InstrItinClass Itin> {
   2655   def _asl_ri : T_S4_ShiftOperate<mnemonic, "asl", Op, shl, 0, MajOp, Itin>;
   2656   def _lsr_ri : T_S4_ShiftOperate<mnemonic, "lsr", Op, srl, 1, MajOp, Itin>;
   2657 }
   2658 
   2659 let AddedComplexity = 200 in {
   2660   defm S4_addi : T_ShiftOperate<"add", add, 0b10, ALU64_tc_2_SLOT23>;
   2661   defm S4_andi : T_ShiftOperate<"and", and, 0b00, ALU64_tc_2_SLOT23>;
   2662 }
   2663 
   2664 let AddedComplexity = 30 in
   2665 defm S4_ori  : T_ShiftOperate<"or",  or,  0b01, ALU64_tc_1_SLOT23>;
   2666 
   2667 defm S4_subi : T_ShiftOperate<"sub", sub, 0b11, ALU64_tc_1_SLOT23>;
   2668 
   2669 let AddedComplexity = 200 in {
   2670   def: Pat<(add addrga:$addr, (shl I32:$src2, u5ImmPred:$src3)),
   2671            (S4_addi_asl_ri addrga:$addr, IntRegs:$src2, u5ImmPred:$src3)>;
   2672   def: Pat<(add addrga:$addr, (srl I32:$src2, u5ImmPred:$src3)),
   2673            (S4_addi_lsr_ri addrga:$addr, IntRegs:$src2, u5ImmPred:$src3)>;
   2674   def: Pat<(sub addrga:$addr, (shl I32:$src2, u5ImmPred:$src3)),
   2675            (S4_subi_asl_ri addrga:$addr, IntRegs:$src2, u5ImmPred:$src3)>;
   2676   def: Pat<(sub addrga:$addr, (srl I32:$src2, u5ImmPred:$src3)),
   2677            (S4_subi_lsr_ri addrga:$addr, IntRegs:$src2, u5ImmPred:$src3)>;
   2678 }
   2679 
   2680 // Vector conditional negate
   2681 // Rdd=vcnegh(Rss,Rt)
   2682 let Defs = [USR_OVF], Itinerary = S_3op_tc_2_SLOT23 in
   2683 def S2_vcnegh   : T_S3op_shiftVect < "vcnegh",   0b11, 0b01>;
   2684 
   2685 // Rd=[cround|round](Rs,Rt)
   2686 let hasNewValue = 1, Itinerary = S_3op_tc_2_SLOT23 in {
   2687   def A4_cround_rr    : T_S3op_3 < "cround", IntRegs, 0b11, 0b00>;
   2688   def A4_round_rr     : T_S3op_3 < "round", IntRegs, 0b11, 0b10>;
   2689 }
   2690 
   2691 // Rd=round(Rs,Rt):sat
   2692 let hasNewValue = 1, Defs = [USR_OVF], Itinerary = S_3op_tc_2_SLOT23 in
   2693 def A4_round_rr_sat : T_S3op_3 < "round", IntRegs, 0b11, 0b11, 1>;
   2694 
   2695 // Rd=[cmpyiwh|cmpyrwh](Rss,Rt):<<1:rnd:sat
   2696 let Defs = [USR_OVF], Itinerary = S_3op_tc_3x_SLOT23 in {
   2697   def M4_cmpyi_wh     : T_S3op_8<"cmpyiwh", 0b100, 1, 1, 1>;
   2698   def M4_cmpyr_wh     : T_S3op_8<"cmpyrwh", 0b110, 1, 1, 1>;
   2699 }
   2700 
   2701 // Rdd=[add|sub](Rss,Rtt,Px):carry
   2702 let isPredicateLate = 1, hasSideEffects = 0 in
   2703 class T_S3op_carry <string mnemonic, bits<3> MajOp>
   2704   : SInst < (outs DoubleRegs:$Rdd, PredRegs:$Px),
   2705             (ins DoubleRegs:$Rss, DoubleRegs:$Rtt, PredRegs:$Pu),
   2706   "$Rdd = "#mnemonic#"($Rss, $Rtt, $Pu):carry",
   2707   [], "$Px = $Pu", S_3op_tc_1_SLOT23 > {
   2708     bits<5> Rdd;
   2709     bits<5> Rss;
   2710     bits<5> Rtt;
   2711     bits<2> Pu;
   2712 
   2713     let IClass = 0b1100;
   2714 
   2715     let Inst{27-24} = 0b0010;
   2716     let Inst{23-21} = MajOp;
   2717     let Inst{20-16} = Rss;
   2718     let Inst{12-8}  = Rtt;
   2719     let Inst{6-5}   = Pu;
   2720     let Inst{4-0}   = Rdd;
   2721   }
   2722 
   2723 def A4_addp_c : T_S3op_carry < "add", 0b110 >;
   2724 def A4_subp_c : T_S3op_carry < "sub", 0b111 >;
   2725 
   2726 let Itinerary = S_3op_tc_3_SLOT23, hasSideEffects = 0 in
   2727 class T_S3op_6 <string mnemonic, bits<3> MinOp, bit isUnsigned>
   2728   : SInst <(outs DoubleRegs:$Rxx),
   2729            (ins DoubleRegs:$dst2, DoubleRegs:$Rss, IntRegs:$Ru),
   2730   "$Rxx = "#mnemonic#"($Rss, $Ru)" ,
   2731   [] , "$dst2 = $Rxx"> {
   2732     bits<5> Rxx;
   2733     bits<5> Rss;
   2734     bits<5> Ru;
   2735 
   2736     let IClass = 0b1100;
   2737 
   2738     let Inst{27-21} = 0b1011001;
   2739     let Inst{20-16} = Rss;
   2740     let Inst{13}    = isUnsigned;
   2741     let Inst{12-8}  = Rxx;
   2742     let Inst{7-5}   = MinOp;
   2743     let Inst{4-0}   = Ru;
   2744   }
   2745 
   2746 // Vector reduce maximum halfwords
   2747 // Rxx=vrmax[u]h(Rss,Ru)
   2748 def A4_vrmaxh  : T_S3op_6 < "vrmaxh",  0b001, 0>;
   2749 def A4_vrmaxuh : T_S3op_6 < "vrmaxuh", 0b001, 1>;
   2750 
   2751 // Vector reduce maximum words
   2752 // Rxx=vrmax[u]w(Rss,Ru)
   2753 def A4_vrmaxw  : T_S3op_6 < "vrmaxw",  0b010, 0>;
   2754 def A4_vrmaxuw : T_S3op_6 < "vrmaxuw", 0b010, 1>;
   2755 
   2756 // Vector reduce minimum halfwords
   2757 // Rxx=vrmin[u]h(Rss,Ru)
   2758 def A4_vrminh  : T_S3op_6 < "vrminh",  0b101, 0>;
   2759 def A4_vrminuh : T_S3op_6 < "vrminuh", 0b101, 1>;
   2760 
   2761 // Vector reduce minimum words
   2762 // Rxx=vrmin[u]w(Rss,Ru)
   2763 def A4_vrminw  : T_S3op_6 < "vrminw",  0b110, 0>;
   2764 def A4_vrminuw : T_S3op_6 < "vrminuw", 0b110, 1>;
   2765 
   2766 // Shift an immediate left by register amount.
   2767 let hasNewValue = 1, hasSideEffects = 0 in
   2768 def S4_lsli: SInst <(outs IntRegs:$Rd), (ins s6Imm:$s6, IntRegs:$Rt),
   2769   "$Rd = lsl(#$s6, $Rt)" ,
   2770   [(set (i32 IntRegs:$Rd), (shl s6ImmPred:$s6,
   2771                                  (i32 IntRegs:$Rt)))],
   2772   "", S_3op_tc_1_SLOT23> {
   2773     bits<5> Rd;
   2774     bits<6> s6;
   2775     bits<5> Rt;
   2776 
   2777     let IClass = 0b1100;
   2778 
   2779     let Inst{27-22} = 0b011010;
   2780     let Inst{20-16} = s6{5-1};
   2781     let Inst{12-8}  = Rt;
   2782     let Inst{7-6}   = 0b11;
   2783     let Inst{4-0}   = Rd;
   2784     let Inst{5}     = s6{0};
   2785   }
   2786 
   2787 //===----------------------------------------------------------------------===//
   2788 // XTYPE/SHIFT -
   2789 //===----------------------------------------------------------------------===//
   2790 
   2791 //===----------------------------------------------------------------------===//
   2792 // MEMOP: Word, Half, Byte
   2793 //===----------------------------------------------------------------------===//
   2794 
   2795 def MEMOPIMM : SDNodeXForm<imm, [{
   2796   // Call the transformation function XformM5ToU5Imm to get the negative
   2797   // immediate's positive counterpart.
   2798   int32_t imm = N->getSExtValue();
   2799   return XformM5ToU5Imm(imm, SDLoc(N));
   2800 }]>;
   2801 
   2802 def MEMOPIMM_HALF : SDNodeXForm<imm, [{
   2803   // -1 .. -31 represented as 65535..65515
   2804   // assigning to a short restores our desired signed value.
   2805   // Call the transformation function XformM5ToU5Imm to get the negative
   2806   // immediate's positive counterpart.
   2807   int16_t imm = N->getSExtValue();
   2808   return XformM5ToU5Imm(imm, SDLoc(N));
   2809 }]>;
   2810 
   2811 def MEMOPIMM_BYTE : SDNodeXForm<imm, [{
   2812   // -1 .. -31 represented as 255..235
   2813   // assigning to a char restores our desired signed value.
   2814   // Call the transformation function XformM5ToU5Imm to get the negative
   2815   // immediate's positive counterpart.
   2816   int8_t imm = N->getSExtValue();
   2817   return XformM5ToU5Imm(imm, SDLoc(N));
   2818 }]>;
   2819 
   2820 def SETMEMIMM : SDNodeXForm<imm, [{
   2821    // Return the bit position we will set [0-31].
   2822    // As an SDNode.
   2823    int32_t imm = N->getSExtValue();
   2824    return XformMskToBitPosU5Imm(imm, SDLoc(N));
   2825 }]>;
   2826 
   2827 def CLRMEMIMM : SDNodeXForm<imm, [{
   2828    // Return the bit position we will clear [0-31].
   2829    // As an SDNode.
   2830    // we bit negate the value first
   2831    int32_t imm = ~(N->getSExtValue());
   2832    return XformMskToBitPosU5Imm(imm, SDLoc(N));
   2833 }]>;
   2834 
   2835 def SETMEMIMM_SHORT : SDNodeXForm<imm, [{
   2836    // Return the bit position we will set [0-15].
   2837    // As an SDNode.
   2838    int16_t imm = N->getSExtValue();
   2839    return XformMskToBitPosU4Imm(imm, SDLoc(N));
   2840 }]>;
   2841 
   2842 def CLRMEMIMM_SHORT : SDNodeXForm<imm, [{
   2843    // Return the bit position we will clear [0-15].
   2844    // As an SDNode.
   2845    // we bit negate the value first
   2846    int16_t imm = ~(N->getSExtValue());
   2847    return XformMskToBitPosU4Imm(imm, SDLoc(N));
   2848 }]>;
   2849 
   2850 def SETMEMIMM_BYTE : SDNodeXForm<imm, [{
   2851    // Return the bit position we will set [0-7].
   2852    // As an SDNode.
   2853    int8_t imm =  N->getSExtValue();
   2854    return XformMskToBitPosU3Imm(imm, SDLoc(N));
   2855 }]>;
   2856 
   2857 def CLRMEMIMM_BYTE : SDNodeXForm<imm, [{
   2858    // Return the bit position we will clear [0-7].
   2859    // As an SDNode.
   2860    // we bit negate the value first
   2861    int8_t imm = ~(N->getSExtValue());
   2862    return XformMskToBitPosU3Imm(imm, SDLoc(N));
   2863 }]>;
   2864 
   2865 //===----------------------------------------------------------------------===//
   2866 // Template class for MemOp instructions with the register value.
   2867 //===----------------------------------------------------------------------===//
   2868 class MemOp_rr_base <string opc, bits<2> opcBits, Operand ImmOp,
   2869                      string memOp, bits<2> memOpBits> :
   2870       MEMInst_V4<(outs),
   2871                  (ins IntRegs:$base, ImmOp:$offset, IntRegs:$delta),
   2872                  opc#"($base+#$offset)"#memOp#"$delta",
   2873                  []>,
   2874                  Requires<[UseMEMOP]> {
   2875 
   2876     bits<5> base;
   2877     bits<5> delta;
   2878     bits<32> offset;
   2879     bits<6> offsetBits; // memb - u6:0 , memh - u6:1, memw - u6:2
   2880 
   2881     let offsetBits = !if (!eq(opcBits, 0b00), offset{5-0},
   2882                      !if (!eq(opcBits, 0b01), offset{6-1},
   2883                      !if (!eq(opcBits, 0b10), offset{7-2},0)));
   2884 
   2885     let opExtentAlign = opcBits;
   2886     let IClass = 0b0011;
   2887     let Inst{27-24} = 0b1110;
   2888     let Inst{22-21} = opcBits;
   2889     let Inst{20-16} = base;
   2890     let Inst{13} = 0b0;
   2891     let Inst{12-7} = offsetBits;
   2892     let Inst{6-5} = memOpBits;
   2893     let Inst{4-0} = delta;
   2894 }
   2895 
   2896 //===----------------------------------------------------------------------===//
   2897 // Template class for MemOp instructions with the immediate value.
   2898 //===----------------------------------------------------------------------===//
   2899 class MemOp_ri_base <string opc, bits<2> opcBits, Operand ImmOp,
   2900                      string memOp, bits<2> memOpBits> :
   2901       MEMInst_V4 <(outs),
   2902                   (ins IntRegs:$base, ImmOp:$offset, u5Imm:$delta),
   2903                   opc#"($base+#$offset)"#memOp#"#$delta"
   2904                   #!if(memOpBits{1},")", ""), // clrbit, setbit - include ')'
   2905                   []>,
   2906                   Requires<[UseMEMOP]> {
   2907 
   2908     bits<5> base;
   2909     bits<5> delta;
   2910     bits<32> offset;
   2911     bits<6> offsetBits; // memb - u6:0 , memh - u6:1, memw - u6:2
   2912 
   2913     let offsetBits = !if (!eq(opcBits, 0b00), offset{5-0},
   2914                      !if (!eq(opcBits, 0b01), offset{6-1},
   2915                      !if (!eq(opcBits, 0b10), offset{7-2},0)));
   2916 
   2917     let opExtentAlign = opcBits;
   2918     let IClass = 0b0011;
   2919     let Inst{27-24} = 0b1111;
   2920     let Inst{22-21} = opcBits;
   2921     let Inst{20-16} = base;
   2922     let Inst{13} = 0b0;
   2923     let Inst{12-7} = offsetBits;
   2924     let Inst{6-5} = memOpBits;
   2925     let Inst{4-0} = delta;
   2926 }
   2927 
   2928 // multiclass to define MemOp instructions with register operand.
   2929 multiclass MemOp_rr<string opc, bits<2> opcBits, Operand ImmOp> {
   2930   def L4_add#NAME : MemOp_rr_base <opc, opcBits, ImmOp, " += ", 0b00>; // add
   2931   def L4_sub#NAME : MemOp_rr_base <opc, opcBits, ImmOp, " -= ", 0b01>; // sub
   2932   def L4_and#NAME : MemOp_rr_base <opc, opcBits, ImmOp, " &= ", 0b10>; // and
   2933   def L4_or#NAME  : MemOp_rr_base <opc, opcBits, ImmOp, " |= ", 0b11>; // or
   2934 }
   2935 
   2936 // multiclass to define MemOp instructions with immediate Operand.
   2937 multiclass MemOp_ri<string opc, bits<2> opcBits, Operand ImmOp> {
   2938   def L4_iadd#NAME : MemOp_ri_base <opc, opcBits, ImmOp, " += ", 0b00 >;
   2939   def L4_isub#NAME : MemOp_ri_base <opc, opcBits, ImmOp, " -= ", 0b01 >;
   2940   def L4_iand#NAME : MemOp_ri_base<opc, opcBits, ImmOp, " = clrbit(", 0b10>;
   2941   def L4_ior#NAME : MemOp_ri_base<opc, opcBits, ImmOp, " = setbit(", 0b11>;
   2942 }
   2943 
   2944 multiclass MemOp_base <string opc, bits<2> opcBits, Operand ImmOp> {
   2945   defm _#NAME : MemOp_rr <opc, opcBits, ImmOp>;
   2946   defm _#NAME : MemOp_ri <opc, opcBits, ImmOp>;
   2947 }
   2948 
   2949 // Define MemOp instructions.
   2950 let isExtendable = 1, opExtendable = 1, isExtentSigned = 0 in {
   2951   let opExtentBits = 6, accessSize = ByteAccess in
   2952   defm memopb_io : MemOp_base <"memb", 0b00, u6_0Ext>;
   2953 
   2954   let opExtentBits = 7, accessSize = HalfWordAccess in
   2955   defm memoph_io : MemOp_base <"memh", 0b01, u6_1Ext>;
   2956 
   2957   let opExtentBits = 8, accessSize = WordAccess in
   2958   defm memopw_io : MemOp_base <"memw", 0b10, u6_2Ext>;
   2959 }
   2960 
   2961 //===----------------------------------------------------------------------===//
   2962 // Multiclass to define 'Def Pats' for ALU operations on the memory
   2963 // Here value used for the ALU operation is an immediate value.
   2964 // mem[bh](Rs+#0) += #U5
   2965 // mem[bh](Rs+#u6) += #U5
   2966 //===----------------------------------------------------------------------===//
   2967 
   2968 multiclass MemOpi_u5Pats <PatFrag ldOp, PatFrag stOp, PatLeaf ImmPred,
   2969                           InstHexagon MI, SDNode OpNode> {
   2970   let AddedComplexity = 180 in
   2971   def: Pat<(stOp (OpNode (ldOp IntRegs:$addr), u5ImmPred:$addend),
   2972                   IntRegs:$addr),
   2973             (MI IntRegs:$addr, 0, u5ImmPred:$addend)>;
   2974 
   2975   let AddedComplexity = 190 in
   2976   def: Pat<(stOp (OpNode (ldOp (add IntRegs:$base, ImmPred:$offset)),
   2977                   u5ImmPred:$addend),
   2978             (add IntRegs:$base, ImmPred:$offset)),
   2979             (MI IntRegs:$base, ImmPred:$offset, u5ImmPred:$addend)>;
   2980 }
   2981 
   2982 multiclass MemOpi_u5ALUOp<PatFrag ldOp, PatFrag stOp, PatLeaf ImmPred,
   2983                           InstHexagon addMI, InstHexagon subMI> {
   2984   defm: MemOpi_u5Pats<ldOp, stOp, ImmPred, addMI, add>;
   2985   defm: MemOpi_u5Pats<ldOp, stOp, ImmPred, subMI, sub>;
   2986 }
   2987 
   2988 multiclass MemOpi_u5ExtType<PatFrag ldOpByte, PatFrag ldOpHalf > {
   2989   // Half Word
   2990   defm: MemOpi_u5ALUOp <ldOpHalf, truncstorei16, u31_1ImmPred,
   2991                         L4_iadd_memoph_io, L4_isub_memoph_io>;
   2992   // Byte
   2993   defm: MemOpi_u5ALUOp <ldOpByte, truncstorei8, u32ImmPred,
   2994                         L4_iadd_memopb_io, L4_isub_memopb_io>;
   2995 }
   2996 
   2997 let Predicates = [UseMEMOP] in {
   2998   defm: MemOpi_u5ExtType<zextloadi8, zextloadi16>; // zero extend
   2999   defm: MemOpi_u5ExtType<sextloadi8, sextloadi16>; // sign extend
   3000   defm: MemOpi_u5ExtType<extloadi8,  extloadi16>;  // any extend
   3001 
   3002   // Word
   3003   defm: MemOpi_u5ALUOp <load, store, u30_2ImmPred, L4_iadd_memopw_io,
   3004                         L4_isub_memopw_io>;
   3005 }
   3006 
   3007 //===----------------------------------------------------------------------===//
   3008 // multiclass to define 'Def Pats' for ALU operations on the memory.
   3009 // Here value used for the ALU operation is a negative value.
   3010 // mem[bh](Rs+#0) += #m5
   3011 // mem[bh](Rs+#u6) += #m5
   3012 //===----------------------------------------------------------------------===//
   3013 
   3014 multiclass MemOpi_m5Pats <PatFrag ldOp, PatFrag stOp, PatLeaf ImmPred,
   3015                           PatLeaf immPred, SDNodeXForm xformFunc,
   3016                           InstHexagon MI> {
   3017   let AddedComplexity = 190 in
   3018   def: Pat<(stOp (add (ldOp IntRegs:$addr), immPred:$subend), IntRegs:$addr),
   3019            (MI IntRegs:$addr, 0, (xformFunc immPred:$subend))>;
   3020 
   3021   let AddedComplexity = 195 in
   3022   def: Pat<(stOp (add (ldOp (add IntRegs:$base, ImmPred:$offset)),
   3023                   immPred:$subend),
   3024            (add IntRegs:$base, ImmPred:$offset)),
   3025            (MI IntRegs:$base, ImmPred:$offset, (xformFunc immPred:$subend))>;
   3026 }
   3027 
   3028 multiclass MemOpi_m5ExtType<PatFrag ldOpByte, PatFrag ldOpHalf > {
   3029   // Half Word
   3030   defm: MemOpi_m5Pats <ldOpHalf, truncstorei16, u31_1ImmPred, m5HImmPred,
   3031                        MEMOPIMM_HALF, L4_isub_memoph_io>;
   3032   // Byte
   3033   defm: MemOpi_m5Pats <ldOpByte, truncstorei8, u32ImmPred, m5BImmPred,
   3034                        MEMOPIMM_BYTE, L4_isub_memopb_io>;
   3035 }
   3036 
   3037 let Predicates = [UseMEMOP] in {
   3038   defm: MemOpi_m5ExtType<zextloadi8, zextloadi16>; // zero extend
   3039   defm: MemOpi_m5ExtType<sextloadi8, sextloadi16>; // sign extend
   3040   defm: MemOpi_m5ExtType<extloadi8,  extloadi16>;  // any extend
   3041 
   3042   // Word
   3043   defm: MemOpi_m5Pats <load, store, u30_2ImmPred, m5ImmPred,
   3044                        MEMOPIMM, L4_isub_memopw_io>;
   3045 }
   3046 
   3047 //===----------------------------------------------------------------------===//
   3048 // Multiclass to define 'def Pats' for bit operations on the memory.
   3049 // mem[bhw](Rs+#0) = [clrbit|setbit](#U5)
   3050 // mem[bhw](Rs+#u6) = [clrbit|setbit](#U5)
   3051 //===----------------------------------------------------------------------===//
   3052 
   3053 multiclass MemOpi_bitPats <PatFrag ldOp, PatFrag stOp, PatLeaf immPred,
   3054                      PatLeaf extPred, SDNodeXForm xformFunc, InstHexagon MI,
   3055                      SDNode OpNode> {
   3056 
   3057   // mem[bhw](Rs+#u6:[012]) = [clrbit|setbit](#U5)
   3058   let AddedComplexity = 250 in
   3059   def: Pat<(stOp (OpNode (ldOp (add IntRegs:$base, extPred:$offset)),
   3060                   immPred:$bitend),
   3061            (add IntRegs:$base, extPred:$offset)),
   3062            (MI IntRegs:$base, extPred:$offset, (xformFunc immPred:$bitend))>;
   3063 
   3064   // mem[bhw](Rs+#0) = [clrbit|setbit](#U5)
   3065   let AddedComplexity = 225 in
   3066   def: Pat<(stOp (OpNode (ldOp IntRegs:$addr), immPred:$bitend), IntRegs:$addr),
   3067            (MI IntRegs:$addr, 0, (xformFunc immPred:$bitend))>;
   3068 }
   3069 
   3070 multiclass MemOpi_bitExtType<PatFrag ldOpByte, PatFrag ldOpHalf> {
   3071   // Byte - clrbit
   3072   defm: MemOpi_bitPats<ldOpByte, truncstorei8, Clr3ImmPred, u32ImmPred,
   3073                        CLRMEMIMM_BYTE, L4_iand_memopb_io, and>;
   3074   // Byte - setbit
   3075   defm: MemOpi_bitPats<ldOpByte, truncstorei8, Set3ImmPred, u32ImmPred,
   3076                        SETMEMIMM_BYTE, L4_ior_memopb_io, or>;
   3077   // Half Word - clrbit
   3078   defm: MemOpi_bitPats<ldOpHalf, truncstorei16, Clr4ImmPred, u31_1ImmPred,
   3079                        CLRMEMIMM_SHORT, L4_iand_memoph_io, and>;
   3080   // Half Word - setbit
   3081   defm: MemOpi_bitPats<ldOpHalf, truncstorei16, Set4ImmPred, u31_1ImmPred,
   3082                        SETMEMIMM_SHORT, L4_ior_memoph_io, or>;
   3083 }
   3084 
   3085 let Predicates = [UseMEMOP] in {
   3086   // mem[bh](Rs+#0) = [clrbit|setbit](#U5)
   3087   // mem[bh](Rs+#u6:[01]) = [clrbit|setbit](#U5)
   3088   defm: MemOpi_bitExtType<zextloadi8, zextloadi16>; // zero extend
   3089   defm: MemOpi_bitExtType<sextloadi8, sextloadi16>; // sign extend
   3090   defm: MemOpi_bitExtType<extloadi8,  extloadi16>;  // any extend
   3091 
   3092   // memw(Rs+#0) = [clrbit|setbit](#U5)
   3093   // memw(Rs+#u6:2) = [clrbit|setbit](#U5)
   3094   defm: MemOpi_bitPats<load, store, Clr5ImmPred, u30_2ImmPred, CLRMEMIMM,
   3095                        L4_iand_memopw_io, and>;
   3096   defm: MemOpi_bitPats<load, store, Set5ImmPred, u30_2ImmPred, SETMEMIMM,
   3097                        L4_ior_memopw_io, or>;
   3098 }
   3099 
   3100 //===----------------------------------------------------------------------===//
   3101 // Multiclass to define 'def Pats' for ALU operations on the memory
   3102 // where addend is a register.
   3103 // mem[bhw](Rs+#0) [+-&|]= Rt
   3104 // mem[bhw](Rs+#U6:[012]) [+-&|]= Rt
   3105 //===----------------------------------------------------------------------===//
   3106 
   3107 multiclass MemOpr_Pats <PatFrag ldOp, PatFrag stOp, PatLeaf extPred,
   3108                         InstHexagon MI, SDNode OpNode> {
   3109   let AddedComplexity = 141 in
   3110   // mem[bhw](Rs+#0) [+-&|]= Rt
   3111   def: Pat<(stOp (OpNode (ldOp IntRegs:$addr), (i32 IntRegs:$addend)),
   3112                  IntRegs:$addr),
   3113            (MI IntRegs:$addr, 0, (i32 IntRegs:$addend))>;
   3114 
   3115   // mem[bhw](Rs+#U6:[012]) [+-&|]= Rt
   3116   let AddedComplexity = 150 in
   3117   def: Pat<(stOp (OpNode (ldOp (add IntRegs:$base, extPred:$offset)),
   3118                   (i32 IntRegs:$orend)),
   3119            (add IntRegs:$base, extPred:$offset)),
   3120            (MI IntRegs:$base, extPred:$offset, (i32 IntRegs:$orend))>;
   3121 }
   3122 
   3123 multiclass MemOPr_ALUOp<PatFrag ldOp, PatFrag stOp, PatLeaf extPred,
   3124                         InstHexagon addMI, InstHexagon subMI,
   3125                         InstHexagon andMI, InstHexagon orMI> {
   3126   defm: MemOpr_Pats <ldOp, stOp, extPred, addMI, add>;
   3127   defm: MemOpr_Pats <ldOp, stOp, extPred, subMI, sub>;
   3128   defm: MemOpr_Pats <ldOp, stOp, extPred, andMI, and>;
   3129   defm: MemOpr_Pats <ldOp, stOp, extPred, orMI,  or>;
   3130 }
   3131 
   3132 multiclass MemOPr_ExtType<PatFrag ldOpByte, PatFrag ldOpHalf > {
   3133   // Half Word
   3134   defm: MemOPr_ALUOp <ldOpHalf, truncstorei16, u31_1ImmPred,
   3135                       L4_add_memoph_io, L4_sub_memoph_io,
   3136                       L4_and_memoph_io, L4_or_memoph_io>;
   3137   // Byte
   3138   defm: MemOPr_ALUOp <ldOpByte, truncstorei8, u32ImmPred,
   3139                       L4_add_memopb_io, L4_sub_memopb_io,
   3140                       L4_and_memopb_io, L4_or_memopb_io>;
   3141 }
   3142 
   3143 // Define 'def Pats' for MemOps with register addend.
   3144 let Predicates = [UseMEMOP] in {
   3145   // Byte, Half Word
   3146   defm: MemOPr_ExtType<zextloadi8, zextloadi16>; // zero extend
   3147   defm: MemOPr_ExtType<sextloadi8, sextloadi16>; // sign extend
   3148   defm: MemOPr_ExtType<extloadi8,  extloadi16>;  // any extend
   3149   // Word
   3150   defm: MemOPr_ALUOp <load, store, u30_2ImmPred, L4_add_memopw_io,
   3151                       L4_sub_memopw_io, L4_and_memopw_io, L4_or_memopw_io>;
   3152 }
   3153 
   3154 //===----------------------------------------------------------------------===//
   3155 // XTYPE/PRED +
   3156 //===----------------------------------------------------------------------===//
   3157 
   3158 // Hexagon V4 only supports these flavors of byte/half compare instructions:
   3159 // EQ/GT/GTU. Other flavors like GE/GEU/LT/LTU/LE/LEU are not supported by
   3160 // hardware. However, compiler can still implement these patterns through
   3161 // appropriate patterns combinations based on current implemented patterns.
   3162 // The implemented patterns are: EQ/GT/GTU.
   3163 // Missing patterns are: GE/GEU/LT/LTU/LE/LEU.
   3164 
   3165 // Following instruction is not being extended as it results into the
   3166 // incorrect code for negative numbers.
   3167 // Pd=cmpb.eq(Rs,#u8)
   3168 
   3169 // p=!cmp.eq(r1,#s10)
   3170 def C4_cmpneqi  : T_CMP <"cmp.eq",  0b00, 1, s10Ext>;
   3171 def C4_cmpltei  : T_CMP <"cmp.gt",  0b01, 1, s10Ext>;
   3172 def C4_cmplteui : T_CMP <"cmp.gtu", 0b10, 1, u9Ext>;
   3173 
   3174 def : T_CMP_pat <C4_cmpneqi,  setne,  s32ImmPred>;
   3175 def : T_CMP_pat <C4_cmpltei,  setle,  s32ImmPred>;
   3176 def : T_CMP_pat <C4_cmplteui, setule, u9ImmPred>;
   3177 
   3178 // rs <= rt -> !(rs > rt).
   3179 /*
   3180 def: Pat<(i1 (setle (i32 IntRegs:$src1), s32ImmPred:$src2)),
   3181          (C2_not (C2_cmpgti IntRegs:$src1, s32ImmPred:$src2))>;
   3182 //         (C4_cmpltei IntRegs:$src1, s32ImmPred:$src2)>;
   3183 */
   3184 // Map cmplt(Rs, Imm) -> !cmpgt(Rs, Imm-1).
   3185 def: Pat<(i1 (setlt (i32 IntRegs:$src1), s32ImmPred:$src2)),
   3186          (C4_cmpltei IntRegs:$src1, (DEC_CONST_SIGNED s32ImmPred:$src2))>;
   3187 
   3188 // rs != rt -> !(rs == rt).
   3189 def: Pat<(i1 (setne (i32 IntRegs:$src1), s32ImmPred:$src2)),
   3190          (C4_cmpneqi IntRegs:$src1, s32ImmPred:$src2)>;
   3191 
   3192 // SDNode for converting immediate C to C-1.
   3193 def DEC_CONST_BYTE : SDNodeXForm<imm, [{
   3194    // Return the byte immediate const-1 as an SDNode.
   3195    int32_t imm = N->getSExtValue();
   3196    return XformU7ToU7M1Imm(imm, SDLoc(N));
   3197 }]>;
   3198 
   3199 // For the sequence
   3200 //   zext( setult ( and(Rs, 255), u8))
   3201 // Use the isdigit transformation below
   3202 
   3203 // Generate code of the form 'C2_muxii(cmpbgtui(Rdd, C-1),0,1)'
   3204 // for C code of the form r = ((c>='0') & (c<='9')) ? 1 : 0;.
   3205 // The isdigit transformation relies on two 'clever' aspects:
   3206 // 1) The data type is unsigned which allows us to eliminate a zero test after
   3207 //    biasing the expression by 48. We are depending on the representation of
   3208 //    the unsigned types, and semantics.
   3209 // 2) The front end has converted <= 9 into < 10 on entry to LLVM
   3210 //
   3211 // For the C code:
   3212 //   retval = ((c>='0') & (c<='9')) ? 1 : 0;
   3213 // The code is transformed upstream of llvm into
   3214 //   retval = (c-48) < 10 ? 1 : 0;
   3215 let AddedComplexity = 139 in
   3216 def: Pat<(i32 (zext (i1 (setult (i32 (and (i32 IntRegs:$src1), 255)),
   3217                          u7StrictPosImmPred:$src2)))),
   3218          (C2_muxii (A4_cmpbgtui IntRegs:$src1,
   3219                     (DEC_CONST_BYTE u7StrictPosImmPred:$src2)),
   3220           0, 1)>;
   3221 
   3222 //===----------------------------------------------------------------------===//
   3223 // XTYPE/PRED -
   3224 //===----------------------------------------------------------------------===//
   3225 
   3226 //===----------------------------------------------------------------------===//
   3227 // Multiclass for DeallocReturn
   3228 //===----------------------------------------------------------------------===//
   3229 class L4_RETURN<string mnemonic, bit isNot, bit isPredNew, bit isTak>
   3230   : LD0Inst<(outs), (ins PredRegs:$src),
   3231   !if(isNot, "if (!$src", "if ($src")#
   3232   !if(isPredNew, ".new) ", ") ")#mnemonic#
   3233   !if(isPredNew, #!if(isTak,":t", ":nt"),""),
   3234   [], "", LD_tc_3or4stall_SLOT0> {
   3235 
   3236     bits<2> src;
   3237     let BaseOpcode = "L4_RETURN";
   3238     let isPredicatedFalse = isNot;
   3239     let isPredicatedNew = isPredNew;
   3240     let isTaken = isTak;
   3241     let IClass = 0b1001;
   3242 
   3243     let Inst{27-16} = 0b011000011110;
   3244 
   3245     let Inst{13} = isNot;
   3246     let Inst{12} = isTak;
   3247     let Inst{11} = isPredNew;
   3248     let Inst{10} = 0b0;
   3249     let Inst{9-8} = src;
   3250     let Inst{4-0} = 0b11110;
   3251   }
   3252 
   3253 // Produce all predicated forms, p, !p, p.new, !p.new, :t, :nt
   3254 multiclass L4_RETURN_PRED<string mnemonic, bit PredNot> {
   3255   let isPredicated = 1 in {
   3256     def _#NAME# : L4_RETURN <mnemonic, PredNot, 0, 1>;
   3257     def _#NAME#new_pnt : L4_RETURN <mnemonic, PredNot, 1, 0>;
   3258     def _#NAME#new_pt : L4_RETURN <mnemonic, PredNot, 1, 1>;
   3259   }
   3260 }
   3261 
   3262 multiclass LD_MISC_L4_RETURN<string mnemonic> {
   3263   let isBarrier = 1, isPredicable = 1 in
   3264     def NAME : LD0Inst <(outs), (ins), mnemonic, [], "",
   3265                         LD_tc_3or4stall_SLOT0> {
   3266       let BaseOpcode = "L4_RETURN";
   3267       let IClass = 0b1001;
   3268       let Inst{27-16} = 0b011000011110;
   3269       let Inst{13-10} = 0b0000;
   3270       let Inst{4-0} = 0b11110;
   3271     }
   3272   defm t : L4_RETURN_PRED<mnemonic, 0 >;
   3273   defm f : L4_RETURN_PRED<mnemonic, 1 >;
   3274 }
   3275 
   3276 let isReturn = 1, isTerminator = 1,
   3277     Defs = [R29, R30, R31, PC], Uses = [R30], hasSideEffects = 0 in
   3278 defm L4_return: LD_MISC_L4_RETURN <"dealloc_return">, PredNewRel;
   3279 
   3280 // Restore registers and dealloc return function call.
   3281 let isCall = 1, isBarrier = 1, isReturn = 1, isTerminator = 1,
   3282     Defs = [R29, R30, R31, PC], isPredicable = 0, isAsmParserOnly = 1 in {
   3283   def RESTORE_DEALLOC_RET_JMP_V4 : T_JMP<"">;
   3284   let isExtended = 1, opExtendable = 0 in
   3285     def RESTORE_DEALLOC_RET_JMP_V4_EXT : T_JMP<"">;
   3286 }
   3287 
   3288 // Restore registers and dealloc frame before a tail call.
   3289 let isCall = 1, Defs = [R29, R30, R31, PC], isAsmParserOnly = 1 in {
   3290   def RESTORE_DEALLOC_BEFORE_TAILCALL_V4 : T_Call<"">, PredRel;
   3291   let isExtended = 1, opExtendable = 0 in
   3292     def RESTORE_DEALLOC_BEFORE_TAILCALL_V4_EXT : T_Call<"">, PredRel;
   3293 }
   3294 
   3295 // Save registers function call.
   3296 let isCall = 1, Uses = [R29, R31], isAsmParserOnly = 1 in {
   3297   def SAVE_REGISTERS_CALL_V4 : T_Call<"">, PredRel;
   3298   let isExtended = 1, opExtendable = 0 in
   3299     def SAVE_REGISTERS_CALL_V4_EXT : T_Call<"">, PredRel;
   3300 }
   3301 
   3302 //===----------------------------------------------------------------------===//
   3303 // Template class for non predicated store instructions with
   3304 // GP-Relative or absolute addressing.
   3305 //===----------------------------------------------------------------------===//
   3306 let hasSideEffects = 0, isPredicable = 1 in
   3307 class T_StoreAbsGP <string mnemonic, RegisterClass RC, Operand ImmOp,
   3308                     bits<2>MajOp, bit isAbs, bit isHalf>
   3309   : STInst<(outs), (ins ImmOp:$addr, RC:$src),
   3310   mnemonic # "(#$addr) = $src"#!if(isHalf, ".h",""),
   3311   [], "", V2LDST_tc_st_SLOT01> {
   3312     bits<19> addr;
   3313     bits<5> src;
   3314     bits<16> offsetBits;
   3315 
   3316     string ImmOpStr = !cast<string>(ImmOp);
   3317     let offsetBits = !if (!eq(ImmOpStr, "u16_3Imm"), addr{18-3},
   3318                      !if (!eq(ImmOpStr, "u16_2Imm"), addr{17-2},
   3319                      !if (!eq(ImmOpStr, "u16_1Imm"), addr{16-1},
   3320                                       /* u16_0Imm */ addr{15-0})));
   3321     // Store upper-half and store doubleword cannot be NV.
   3322     let isNVStorable = !if (!eq(mnemonic, "memd"), 0, !if(isHalf,0,1));
   3323 
   3324     let IClass = 0b0100;
   3325     let Inst{27} = 1;
   3326     let Inst{26-25} = offsetBits{15-14};
   3327     let Inst{24}    = 0b0;
   3328     let Inst{23-22} = MajOp;
   3329     let Inst{21}    = isHalf;
   3330     let Inst{20-16} = offsetBits{13-9};
   3331     let Inst{13}    = offsetBits{8};
   3332     let Inst{12-8}  = src;
   3333     let Inst{7-0}   = offsetBits{7-0};
   3334   }
   3335 
   3336 //===----------------------------------------------------------------------===//
   3337 // Template class for predicated store instructions with
   3338 // GP-Relative or absolute addressing.
   3339 //===----------------------------------------------------------------------===//
   3340 let hasSideEffects = 0, isPredicated = 1, opExtentBits = 6, opExtendable = 1 in
   3341 class T_StoreAbs_Pred <string mnemonic, RegisterClass RC, bits<2> MajOp,
   3342                        bit isHalf, bit isNot, bit isNew>
   3343   : STInst<(outs), (ins PredRegs:$src1, u32MustExt:$absaddr, RC: $src2),
   3344   !if(isNot, "if (!$src1", "if ($src1")#!if(isNew, ".new) ",
   3345   ") ")#mnemonic#"(#$absaddr) = $src2"#!if(isHalf, ".h",""),
   3346   [], "", ST_tc_st_SLOT01>, AddrModeRel {
   3347     bits<2> src1;
   3348     bits<6> absaddr;
   3349     bits<5> src2;
   3350 
   3351     let isPredicatedNew = isNew;
   3352     let isPredicatedFalse = isNot;
   3353     // Store upper-half and store doubleword cannot be NV.
   3354     let isNVStorable = !if (!eq(mnemonic, "memd"), 0, !if(isHalf,0,1));
   3355 
   3356     let IClass = 0b1010;
   3357 
   3358     let Inst{27-24} = 0b1111;
   3359     let Inst{23-22} = MajOp;
   3360     let Inst{21}    = isHalf;
   3361     let Inst{17-16} = absaddr{5-4};
   3362     let Inst{13}    = isNew;
   3363     let Inst{12-8}  = src2;
   3364     let Inst{7}     = 0b1;
   3365     let Inst{6-3}   = absaddr{3-0};
   3366     let Inst{2}     = isNot;
   3367     let Inst{1-0}   = src1;
   3368   }
   3369 
   3370 //===----------------------------------------------------------------------===//
   3371 // Template class for predicated store instructions with absolute addressing.
   3372 //===----------------------------------------------------------------------===//
   3373 class T_StoreAbs <string mnemonic, RegisterClass RC, Operand ImmOp,
   3374                  bits<2> MajOp, bit isHalf>
   3375   : T_StoreAbsGP <mnemonic, RC, u32MustExt, MajOp, 1, isHalf>,
   3376                   AddrModeRel {
   3377   string ImmOpStr = !cast<string>(ImmOp);
   3378   let opExtentBits = !if (!eq(ImmOpStr, "u16_3Imm"), 19,
   3379                      !if (!eq(ImmOpStr, "u16_2Imm"), 18,
   3380                      !if (!eq(ImmOpStr, "u16_1Imm"), 17,
   3381                                       /* u16_0Imm */ 16)));
   3382 
   3383   let opExtentAlign = !if (!eq(ImmOpStr, "u16_3Imm"), 3,
   3384                       !if (!eq(ImmOpStr, "u16_2Imm"), 2,
   3385                       !if (!eq(ImmOpStr, "u16_1Imm"), 1,
   3386                                        /* u16_0Imm */ 0)));
   3387 }
   3388 
   3389 //===----------------------------------------------------------------------===//
   3390 // Multiclass for store instructions with absolute addressing.
   3391 //===----------------------------------------------------------------------===//
   3392 let addrMode = Absolute, isExtended = 1 in
   3393 multiclass ST_Abs<string mnemonic, string CextOp, RegisterClass RC,
   3394                   Operand ImmOp, bits<2> MajOp, bit isHalf = 0> {
   3395   let CextOpcode = CextOp, BaseOpcode = CextOp#_abs in {
   3396     let opExtendable = 0, isPredicable = 1 in
   3397     def S2_#NAME#abs : T_StoreAbs <mnemonic, RC, ImmOp, MajOp, isHalf>;
   3398 
   3399     // Predicated
   3400     def S4_p#NAME#t_abs : T_StoreAbs_Pred<mnemonic, RC, MajOp, isHalf, 0, 0>;
   3401     def S4_p#NAME#f_abs : T_StoreAbs_Pred<mnemonic, RC, MajOp, isHalf, 1, 0>;
   3402 
   3403     // .new Predicated
   3404     def S4_p#NAME#tnew_abs : T_StoreAbs_Pred<mnemonic, RC, MajOp, isHalf, 0, 1>;
   3405     def S4_p#NAME#fnew_abs : T_StoreAbs_Pred<mnemonic, RC, MajOp, isHalf, 1, 1>;
   3406   }
   3407 }
   3408 
   3409 //===----------------------------------------------------------------------===//
   3410 // Template class for non predicated new-value store instructions with
   3411 // GP-Relative or absolute addressing.
   3412 //===----------------------------------------------------------------------===//
   3413 let hasSideEffects = 0, isPredicable = 1, mayStore = 1, isNVStore = 1,
   3414     isNewValue = 1, opNewValue = 1 in
   3415 class T_StoreAbsGP_NV <string mnemonic, Operand ImmOp, bits<2>MajOp, bit isAbs>
   3416   : NVInst_V4<(outs), (ins u32Imm:$addr, IntRegs:$src),
   3417   mnemonic # !if(isAbs, "(##", "(#")#"$addr) = $src.new",
   3418   [], "", V2LDST_tc_st_SLOT0> {
   3419     bits<19> addr;
   3420     bits<3> src;
   3421     bits<16> offsetBits;
   3422 
   3423     string ImmOpStr = !cast<string>(ImmOp);
   3424     let offsetBits = !if (!eq(ImmOpStr, "u16_3Imm"), addr{18-3},
   3425                      !if (!eq(ImmOpStr, "u16_2Imm"), addr{17-2},
   3426                      !if (!eq(ImmOpStr, "u16_1Imm"), addr{16-1},
   3427                                       /* u16_0Imm */ addr{15-0})));
   3428     let IClass = 0b0100;
   3429 
   3430     let Inst{27} = 1;
   3431     let Inst{26-25} = offsetBits{15-14};
   3432     let Inst{24-21} = 0b0101;
   3433     let Inst{20-16} = offsetBits{13-9};
   3434     let Inst{13}    = offsetBits{8};
   3435     let Inst{12-11} = MajOp;
   3436     let Inst{10-8}  = src;
   3437     let Inst{7-0}   = offsetBits{7-0};
   3438   }
   3439 
   3440 //===----------------------------------------------------------------------===//
   3441 // Template class for predicated new-value store instructions with
   3442 // absolute addressing.
   3443 //===----------------------------------------------------------------------===//
   3444 let hasSideEffects = 0, isPredicated = 1, mayStore = 1, isNVStore = 1,
   3445     isNewValue = 1, opNewValue = 2, opExtentBits = 6, opExtendable = 1 in
   3446 class T_StoreAbs_NV_Pred <string mnemonic, bits<2> MajOp, bit isNot, bit isNew>
   3447   : NVInst_V4<(outs), (ins PredRegs:$src1, u6Ext:$absaddr, IntRegs:$src2),
   3448   !if(isNot, "if (!$src1", "if ($src1")#!if(isNew, ".new) ",
   3449   ") ")#mnemonic#"(#$absaddr) = $src2.new",
   3450   [], "", ST_tc_st_SLOT0>, AddrModeRel {
   3451     bits<2> src1;
   3452     bits<6> absaddr;
   3453     bits<3> src2;
   3454 
   3455     let isPredicatedNew = isNew;
   3456     let isPredicatedFalse = isNot;
   3457 
   3458     let IClass = 0b1010;
   3459 
   3460     let Inst{27-24} = 0b1111;
   3461     let Inst{23-21} = 0b101;
   3462     let Inst{17-16} = absaddr{5-4};
   3463     let Inst{13}    = isNew;
   3464     let Inst{12-11} = MajOp;
   3465     let Inst{10-8}  = src2;
   3466     let Inst{7}     = 0b1;
   3467     let Inst{6-3}   = absaddr{3-0};
   3468     let Inst{2}     = isNot;
   3469     let Inst{1-0}   = src1;
   3470 }
   3471 
   3472 //===----------------------------------------------------------------------===//
   3473 // Template class for non-predicated new-value store instructions with
   3474 // absolute addressing.
   3475 //===----------------------------------------------------------------------===//
   3476 class T_StoreAbs_NV <string mnemonic, Operand ImmOp, bits<2> MajOp>
   3477   : T_StoreAbsGP_NV <mnemonic, ImmOp, MajOp, 1>, AddrModeRel {
   3478 
   3479   string ImmOpStr = !cast<string>(ImmOp);
   3480   let opExtentBits = !if (!eq(ImmOpStr, "u16_3Imm"), 19,
   3481                      !if (!eq(ImmOpStr, "u16_2Imm"), 18,
   3482                      !if (!eq(ImmOpStr, "u16_1Imm"), 17,
   3483                                       /* u16_0Imm */ 16)));
   3484 
   3485   let opExtentAlign = !if (!eq(ImmOpStr, "u16_3Imm"), 3,
   3486                       !if (!eq(ImmOpStr, "u16_2Imm"), 2,
   3487                       !if (!eq(ImmOpStr, "u16_1Imm"), 1,
   3488                                        /* u16_0Imm */ 0)));
   3489 }
   3490 
   3491 //===----------------------------------------------------------------------===//
   3492 // Multiclass for new-value store instructions with absolute addressing.
   3493 //===----------------------------------------------------------------------===//
   3494 let addrMode = Absolute, isExtended = 1  in
   3495 multiclass ST_Abs_NV <string mnemonic, string CextOp, Operand ImmOp,
   3496                    bits<2> MajOp> {
   3497   let CextOpcode = CextOp, BaseOpcode = CextOp#_abs in {
   3498     let opExtendable = 0, isPredicable = 1 in
   3499     def S2_#NAME#newabs : T_StoreAbs_NV <mnemonic, ImmOp, MajOp>;
   3500 
   3501     // Predicated
   3502     def S4_p#NAME#newt_abs  : T_StoreAbs_NV_Pred <mnemonic, MajOp, 0, 0>;
   3503     def S4_p#NAME#newf_abs  : T_StoreAbs_NV_Pred <mnemonic, MajOp, 1, 0>;
   3504 
   3505     // .new Predicated
   3506     def S4_p#NAME#newtnew_abs : T_StoreAbs_NV_Pred <mnemonic, MajOp, 0, 1>;
   3507     def S4_p#NAME#newfnew_abs : T_StoreAbs_NV_Pred <mnemonic, MajOp, 1, 1>;
   3508   }
   3509 }
   3510 
   3511 //===----------------------------------------------------------------------===//
   3512 // Stores with absolute addressing
   3513 //===----------------------------------------------------------------------===//
   3514 let accessSize = ByteAccess in
   3515 defm storerb : ST_Abs    <"memb", "STrib", IntRegs, u16_0Imm, 0b00>,
   3516                ST_Abs_NV <"memb", "STrib", u16_0Imm, 0b00>;
   3517 
   3518 let accessSize = HalfWordAccess in
   3519 defm storerh : ST_Abs    <"memh", "STrih", IntRegs, u16_1Imm, 0b01>,
   3520                ST_Abs_NV <"memh", "STrih", u16_1Imm, 0b01>;
   3521 
   3522 let accessSize = WordAccess in
   3523 defm storeri : ST_Abs    <"memw", "STriw", IntRegs, u16_2Imm, 0b10>,
   3524                ST_Abs_NV <"memw", "STriw", u16_2Imm, 0b10>;
   3525 
   3526 let isNVStorable = 0, accessSize = DoubleWordAccess in
   3527 defm storerd : ST_Abs <"memd", "STrid", DoubleRegs, u16_3Imm, 0b11>;
   3528 
   3529 let isNVStorable = 0, accessSize = HalfWordAccess in
   3530 defm storerf : ST_Abs <"memh", "STrif", IntRegs, u16_1Imm, 0b01, 1>;
   3531 
   3532 //===----------------------------------------------------------------------===//
   3533 // GP-relative stores.
   3534 // mem[bhwd](#global)=Rt
   3535 // Once predicated, these instructions map to absolute addressing mode.
   3536 // if ([!]Pv[.new]) mem[bhwd](##global)=Rt
   3537 //===----------------------------------------------------------------------===//
   3538 
   3539 let isAsmParserOnly = 1 in
   3540 class T_StoreGP <string mnemonic, string BaseOp, RegisterClass RC,
   3541                  Operand ImmOp, bits<2> MajOp, bit isHalf = 0>
   3542   : T_StoreAbsGP <mnemonic, RC, ImmOp, MajOp, 0, isHalf> {
   3543     // Set BaseOpcode same as absolute addressing instructions so that
   3544     // non-predicated GP-Rel instructions can have relate with predicated
   3545     // Absolute instruction.
   3546     let BaseOpcode = BaseOp#_abs;
   3547   }
   3548 
   3549 let isAsmParserOnly = 1 in
   3550 multiclass ST_GP <string mnemonic, string BaseOp, Operand ImmOp,
   3551                   bits<2> MajOp, bit isHalf = 0> {
   3552   // Set BaseOpcode same as absolute addressing instructions so that
   3553   // non-predicated GP-Rel instructions can have relate with predicated
   3554   // Absolute instruction.
   3555   let BaseOpcode = BaseOp#_abs in {
   3556     def NAME#gp : T_StoreAbsGP <mnemonic, IntRegs, ImmOp, MajOp,
   3557                                 0, isHalf>;
   3558     // New-value store
   3559     def NAME#newgp : T_StoreAbsGP_NV <mnemonic, ImmOp, MajOp, 0> ;
   3560   }
   3561 }
   3562 
   3563 let accessSize = ByteAccess in
   3564 defm S2_storerb : ST_GP<"memb", "STrib", u16_0Imm, 0b00>, NewValueRel;
   3565 
   3566 let accessSize = HalfWordAccess in
   3567 defm S2_storerh : ST_GP<"memh", "STrih", u16_1Imm, 0b01>, NewValueRel;
   3568 
   3569 let accessSize = WordAccess in
   3570 defm S2_storeri : ST_GP<"memw", "STriw", u16_2Imm, 0b10>, NewValueRel;
   3571 
   3572 let isNVStorable = 0, accessSize = DoubleWordAccess in
   3573 def S2_storerdgp : T_StoreGP <"memd", "STrid", DoubleRegs,
   3574                               u16_3Imm, 0b11>, PredNewRel;
   3575 
   3576 let isNVStorable = 0, accessSize = HalfWordAccess in
   3577 def S2_storerfgp : T_StoreGP <"memh", "STrif", IntRegs,
   3578                               u16_1Imm, 0b01, 1>, PredNewRel;
   3579 
   3580 class Loada_pat<PatFrag Load, ValueType VT, PatFrag Addr, InstHexagon MI>
   3581   : Pat<(VT (Load Addr:$addr)), (MI Addr:$addr)>;
   3582 
   3583 class Loadam_pat<PatFrag Load, ValueType VT, PatFrag Addr, PatFrag ValueMod,
   3584                  InstHexagon MI>
   3585   : Pat<(VT (Load Addr:$addr)), (ValueMod (MI Addr:$addr))>;
   3586 
   3587 class Storea_pat<PatFrag Store, PatFrag Value, PatFrag Addr, InstHexagon MI>
   3588   : Pat<(Store Value:$val, Addr:$addr), (MI Addr:$addr, Value:$val)>;
   3589 
   3590 class Stoream_pat<PatFrag Store, PatFrag Value, PatFrag Addr, PatFrag ValueMod,
   3591                   InstHexagon MI>
   3592   : Pat<(Store Value:$val, Addr:$addr),
   3593         (MI Addr:$addr, (ValueMod Value:$val))>;
   3594 
   3595 def: Storea_pat<SwapSt<atomic_store_8>,  I32, addrgp, S2_storerbgp>;
   3596 def: Storea_pat<SwapSt<atomic_store_16>, I32, addrgp, S2_storerhgp>;
   3597 def: Storea_pat<SwapSt<atomic_store_32>, I32, addrgp, S2_storerigp>;
   3598 def: Storea_pat<SwapSt<atomic_store_64>, I64, addrgp, S2_storerdgp>;
   3599 
   3600 let AddedComplexity = 100 in {
   3601   def: Storea_pat<truncstorei8,  I32, addrgp, S2_storerbgp>;
   3602   def: Storea_pat<truncstorei16, I32, addrgp, S2_storerhgp>;
   3603   def: Storea_pat<store,         I32, addrgp, S2_storerigp>;
   3604   def: Storea_pat<store,         I64, addrgp, S2_storerdgp>;
   3605 
   3606   // Map from "i1 = constant<-1>; memw(CONST32(#foo)) = i1"
   3607   //       to "r0 = 1; memw(#foo) = r0"
   3608   let AddedComplexity = 100 in
   3609   def: Pat<(store (i1 -1), (HexagonCONST32_GP tglobaladdr:$global)),
   3610            (S2_storerbgp tglobaladdr:$global, (A2_tfrsi 1))>;
   3611 }
   3612 
   3613 //===----------------------------------------------------------------------===//
   3614 // Template class for non predicated load instructions with
   3615 // absolute addressing mode.
   3616 //===----------------------------------------------------------------------===//
   3617 let isPredicable = 1, hasSideEffects = 0 in
   3618 class T_LoadAbsGP <string mnemonic, RegisterClass RC, Operand ImmOp,
   3619                    bits<3> MajOp>
   3620   : LDInst <(outs RC:$dst), (ins ImmOp:$addr),
   3621   "$dst = "#mnemonic# "(#$addr)",
   3622   [], "", V2LDST_tc_ld_SLOT01> {
   3623     bits<5> dst;
   3624     bits<19> addr;
   3625     bits<16> offsetBits;
   3626 
   3627     string ImmOpStr = !cast<string>(ImmOp);
   3628     let offsetBits = !if (!eq(ImmOpStr, "u16_3Imm"), addr{18-3},
   3629                      !if (!eq(ImmOpStr, "u16_2Imm"), addr{17-2},
   3630                      !if (!eq(ImmOpStr, "u16_1Imm"), addr{16-1},
   3631                                       /* u16_0Imm */ addr{15-0})));
   3632 
   3633     let IClass = 0b0100;
   3634 
   3635     let Inst{27}    = 0b1;
   3636     let Inst{26-25} = offsetBits{15-14};
   3637     let Inst{24}    = 0b1;
   3638     let Inst{23-21} = MajOp;
   3639     let Inst{20-16} = offsetBits{13-9};
   3640     let Inst{13-5}  = offsetBits{8-0};
   3641     let Inst{4-0}   = dst;
   3642   }
   3643 
   3644 class T_LoadAbs <string mnemonic, RegisterClass RC, Operand ImmOp,
   3645                  bits<3> MajOp>
   3646   : T_LoadAbsGP <mnemonic, RC, u32MustExt, MajOp>, AddrModeRel {
   3647 
   3648     string ImmOpStr = !cast<string>(ImmOp);
   3649     let opExtentBits = !if (!eq(ImmOpStr, "u16_3Imm"), 19,
   3650                        !if (!eq(ImmOpStr, "u16_2Imm"), 18,
   3651                        !if (!eq(ImmOpStr, "u16_1Imm"), 17,
   3652                                         /* u16_0Imm */ 16)));
   3653 
   3654     let opExtentAlign = !if (!eq(ImmOpStr, "u16_3Imm"), 3,
   3655                         !if (!eq(ImmOpStr, "u16_2Imm"), 2,
   3656                         !if (!eq(ImmOpStr, "u16_1Imm"), 1,
   3657                                         /* u16_0Imm */ 0)));
   3658   }
   3659 
   3660 //===----------------------------------------------------------------------===//
   3661 // Template class for predicated load instructions with
   3662 // absolute addressing mode.
   3663 //===----------------------------------------------------------------------===//
   3664 let isPredicated = 1, hasSideEffects = 0, hasNewValue = 1, opExtentBits = 6,
   3665     opExtendable = 2 in
   3666 class T_LoadAbs_Pred <string mnemonic, RegisterClass RC, bits<3> MajOp,
   3667                       bit isPredNot, bit isPredNew>
   3668   : LDInst <(outs RC:$dst), (ins PredRegs:$src1, u32MustExt:$absaddr),
   3669   !if(isPredNot, "if (!$src1", "if ($src1")#!if(isPredNew, ".new) ",
   3670   ") ")#"$dst = "#mnemonic#"(#$absaddr)">, AddrModeRel {
   3671     bits<5> dst;
   3672     bits<2> src1;
   3673     bits<6> absaddr;
   3674 
   3675     let isPredicatedNew = isPredNew;
   3676     let isPredicatedFalse = isPredNot;
   3677     let hasNewValue = !if (!eq(!cast<string>(RC), "DoubleRegs"), 0, 1);
   3678 
   3679     let IClass = 0b1001;
   3680 
   3681     let Inst{27-24} = 0b1111;
   3682     let Inst{23-21} = MajOp;
   3683     let Inst{20-16} = absaddr{5-1};
   3684     let Inst{13} = 0b1;
   3685     let Inst{12} = isPredNew;
   3686     let Inst{11} = isPredNot;
   3687     let Inst{10-9} = src1;
   3688     let Inst{8} = absaddr{0};
   3689     let Inst{7} = 0b1;
   3690     let Inst{4-0} = dst;
   3691   }
   3692 
   3693 //===----------------------------------------------------------------------===//
   3694 // Multiclass for the load instructions with absolute addressing mode.
   3695 //===----------------------------------------------------------------------===//
   3696 multiclass LD_Abs_Pred<string mnemonic, RegisterClass RC, bits<3> MajOp,
   3697                        bit PredNot> {
   3698   def _abs : T_LoadAbs_Pred <mnemonic, RC, MajOp, PredNot, 0>;
   3699   // Predicate new
   3700   def new_abs : T_LoadAbs_Pred <mnemonic, RC, MajOp, PredNot, 1>;
   3701 }
   3702 
   3703 let addrMode = Absolute, isExtended = 1 in
   3704 multiclass LD_Abs<string mnemonic, string CextOp, RegisterClass RC,
   3705                   Operand ImmOp, bits<3> MajOp> {
   3706   let CextOpcode = CextOp, BaseOpcode = CextOp#_abs in {
   3707     let opExtendable = 1, isPredicable = 1 in
   3708     def L4_#NAME#_abs: T_LoadAbs <mnemonic, RC, ImmOp, MajOp>;
   3709 
   3710     // Predicated
   3711     defm L4_p#NAME#t : LD_Abs_Pred<mnemonic, RC, MajOp, 0>;
   3712     defm L4_p#NAME#f : LD_Abs_Pred<mnemonic, RC, MajOp, 1>;
   3713   }
   3714 }
   3715 
   3716 let accessSize = ByteAccess, hasNewValue = 1 in {
   3717   defm loadrb  : LD_Abs<"memb",  "LDrib",  IntRegs, u16_0Imm, 0b000>;
   3718   defm loadrub : LD_Abs<"memub", "LDriub", IntRegs, u16_0Imm, 0b001>;
   3719 }
   3720 
   3721 let accessSize = HalfWordAccess, hasNewValue = 1 in {
   3722   defm loadrh  : LD_Abs<"memh",  "LDrih",  IntRegs, u16_1Imm, 0b010>;
   3723   defm loadruh : LD_Abs<"memuh", "LDriuh", IntRegs, u16_1Imm, 0b011>;
   3724 }
   3725 
   3726 let accessSize = WordAccess, hasNewValue = 1 in
   3727 defm loadri  : LD_Abs<"memw",  "LDriw",  IntRegs, u16_2Imm, 0b100>;
   3728 
   3729 let accessSize = DoubleWordAccess in
   3730 defm loadrd  : LD_Abs<"memd",  "LDrid", DoubleRegs, u16_3Imm, 0b110>;
   3731 
   3732 //===----------------------------------------------------------------------===//
   3733 // multiclass for load instructions with GP-relative addressing mode.
   3734 // Rx=mem[bhwd](##global)
   3735 // Once predicated, these instructions map to absolute addressing mode.
   3736 // if ([!]Pv[.new]) Rx=mem[bhwd](##global)
   3737 //===----------------------------------------------------------------------===//
   3738 
   3739 let isAsmParserOnly = 1 in
   3740 class T_LoadGP <string mnemonic, string BaseOp, RegisterClass RC, Operand ImmOp,
   3741                 bits<3> MajOp>
   3742   : T_LoadAbsGP <mnemonic, RC, ImmOp, MajOp>, PredNewRel {
   3743     let BaseOpcode = BaseOp#_abs;
   3744   }
   3745 
   3746 let accessSize = ByteAccess, hasNewValue = 1 in {
   3747   def L2_loadrbgp  : T_LoadGP<"memb",  "LDrib",  IntRegs, u16_0Imm, 0b000>;
   3748   def L2_loadrubgp : T_LoadGP<"memub", "LDriub", IntRegs, u16_0Imm, 0b001>;
   3749 }
   3750 
   3751 let accessSize = HalfWordAccess, hasNewValue = 1 in {
   3752   def L2_loadrhgp  : T_LoadGP<"memh",  "LDrih",  IntRegs, u16_1Imm, 0b010>;
   3753   def L2_loadruhgp : T_LoadGP<"memuh", "LDriuh", IntRegs, u16_1Imm, 0b011>;
   3754 }
   3755 
   3756 let accessSize = WordAccess, hasNewValue = 1 in
   3757 def L2_loadrigp  : T_LoadGP<"memw",  "LDriw",  IntRegs, u16_2Imm, 0b100>;
   3758 
   3759 let accessSize = DoubleWordAccess in
   3760 def L2_loadrdgp  : T_LoadGP<"memd", "LDrid", DoubleRegs, u16_3Imm, 0b110>;
   3761 
   3762 def: Loada_pat<atomic_load_8,  i32, addrgp, L2_loadrubgp>;
   3763 def: Loada_pat<atomic_load_16, i32, addrgp, L2_loadruhgp>;
   3764 def: Loada_pat<atomic_load_32, i32, addrgp, L2_loadrigp>;
   3765 def: Loada_pat<atomic_load_64, i64, addrgp, L2_loadrdgp>;
   3766 
   3767 // Map from Pd = load(globaladdress) -> Rd = memb(globaladdress), Pd = Rd
   3768 def: Loadam_pat<load, i1, addrga, I32toI1, L4_loadrub_abs>;
   3769 def: Loadam_pat<load, i1, addrgp, I32toI1, L2_loadrubgp>;
   3770 
   3771 def: Stoream_pat<store, I1, addrga, I1toI32, S2_storerbabs>;
   3772 def: Stoream_pat<store, I1, addrgp, I1toI32, S2_storerbgp>;
   3773 
   3774 // Map from load(globaladdress) -> mem[u][bhwd](#foo)
   3775 class LoadGP_pats <PatFrag ldOp, InstHexagon MI, ValueType VT = i32>
   3776   : Pat <(VT (ldOp (HexagonCONST32_GP tglobaladdr:$global))),
   3777          (VT (MI tglobaladdr:$global))>;
   3778 
   3779 let AddedComplexity = 100 in {
   3780   def: LoadGP_pats <extloadi8, L2_loadrbgp>;
   3781   def: LoadGP_pats <sextloadi8, L2_loadrbgp>;
   3782   def: LoadGP_pats <zextloadi8, L2_loadrubgp>;
   3783   def: LoadGP_pats <extloadi16, L2_loadrhgp>;
   3784   def: LoadGP_pats <sextloadi16, L2_loadrhgp>;
   3785   def: LoadGP_pats <zextloadi16, L2_loadruhgp>;
   3786   def: LoadGP_pats <load, L2_loadrigp>;
   3787   def: LoadGP_pats <load, L2_loadrdgp, i64>;
   3788 }
   3789 
   3790 // When the Interprocedural Global Variable optimizer realizes that a certain
   3791 // global variable takes only two constant values, it shrinks the global to
   3792 // a boolean. Catch those loads here in the following 3 patterns.
   3793 let AddedComplexity = 100 in {
   3794   def: LoadGP_pats <extloadi1, L2_loadrubgp>;
   3795   def: LoadGP_pats <zextloadi1, L2_loadrubgp>;
   3796 }
   3797 
   3798 // Transfer global address into a register
   3799 def: Pat<(HexagonCONST32 tglobaladdr:$Rs),      (A2_tfrsi s16Ext:$Rs)>;
   3800 def: Pat<(HexagonCONST32_GP tblockaddress:$Rs), (A2_tfrsi s16Ext:$Rs)>;
   3801 def: Pat<(HexagonCONST32_GP tglobaladdr:$Rs),   (A2_tfrsi s16Ext:$Rs)>;
   3802 
   3803 let AddedComplexity  = 30 in {
   3804   def: Storea_pat<truncstorei8,  I32, u32ImmPred, S2_storerbabs>;
   3805   def: Storea_pat<truncstorei16, I32, u32ImmPred, S2_storerhabs>;
   3806   def: Storea_pat<store,         I32, u32ImmPred, S2_storeriabs>;
   3807 }
   3808 
   3809 let AddedComplexity  = 30 in {
   3810   def: Loada_pat<load,        i32, u32ImmPred, L4_loadri_abs>;
   3811   def: Loada_pat<sextloadi8,  i32, u32ImmPred, L4_loadrb_abs>;
   3812   def: Loada_pat<zextloadi8,  i32, u32ImmPred, L4_loadrub_abs>;
   3813   def: Loada_pat<sextloadi16, i32, u32ImmPred, L4_loadrh_abs>;
   3814   def: Loada_pat<zextloadi16, i32, u32ImmPred, L4_loadruh_abs>;
   3815 }
   3816 
   3817 // Indexed store word - global address.
   3818 // memw(Rs+#u6:2)=#S8
   3819 let AddedComplexity = 100 in
   3820 def: Storex_add_pat<store, addrga, u6_2ImmPred, S4_storeiri_io>;
   3821 
   3822 // Load from a global address that has only one use in the current basic block.
   3823 let AddedComplexity = 100 in {
   3824   def: Loada_pat<extloadi8,   i32, addrga, L4_loadrub_abs>;
   3825   def: Loada_pat<sextloadi8,  i32, addrga, L4_loadrb_abs>;
   3826   def: Loada_pat<zextloadi8,  i32, addrga, L4_loadrub_abs>;
   3827 
   3828   def: Loada_pat<extloadi16,  i32, addrga, L4_loadruh_abs>;
   3829   def: Loada_pat<sextloadi16, i32, addrga, L4_loadrh_abs>;
   3830   def: Loada_pat<zextloadi16, i32, addrga, L4_loadruh_abs>;
   3831 
   3832   def: Loada_pat<load,        i32, addrga, L4_loadri_abs>;
   3833   def: Loada_pat<load,        i64, addrga, L4_loadrd_abs>;
   3834 }
   3835 
   3836 // Store to a global address that has only one use in the current basic block.
   3837 let AddedComplexity = 100 in {
   3838   def: Storea_pat<truncstorei8,  I32, addrga, S2_storerbabs>;
   3839   def: Storea_pat<truncstorei16, I32, addrga, S2_storerhabs>;
   3840   def: Storea_pat<store,         I32, addrga, S2_storeriabs>;
   3841   def: Storea_pat<store,         I64, addrga, S2_storerdabs>;
   3842 
   3843   def: Stoream_pat<truncstorei32, I64, addrga, LoReg, S2_storeriabs>;
   3844 }
   3845 
   3846 // i8/i16/i32 -> i64 loads
   3847 // We need a complexity of 120 here to override preceding handling of
   3848 // zextload.
   3849 let AddedComplexity = 120 in {
   3850   def: Loadam_pat<extloadi8,   i64, addrga, Zext64, L4_loadrub_abs>;
   3851   def: Loadam_pat<sextloadi8,  i64, addrga, Sext64, L4_loadrb_abs>;
   3852   def: Loadam_pat<zextloadi8,  i64, addrga, Zext64, L4_loadrub_abs>;
   3853 
   3854   def: Loadam_pat<extloadi16,  i64, addrga, Zext64, L4_loadruh_abs>;
   3855   def: Loadam_pat<sextloadi16, i64, addrga, Sext64, L4_loadrh_abs>;
   3856   def: Loadam_pat<zextloadi16, i64, addrga, Zext64, L4_loadruh_abs>;
   3857 
   3858   def: Loadam_pat<extloadi32,  i64, addrga, Zext64, L4_loadri_abs>;
   3859   def: Loadam_pat<sextloadi32, i64, addrga, Sext64, L4_loadri_abs>;
   3860   def: Loadam_pat<zextloadi32, i64, addrga, Zext64, L4_loadri_abs>;
   3861 }
   3862 
   3863 let AddedComplexity = 100 in {
   3864   def: Loada_pat<extloadi8,   i32, addrgp, L4_loadrub_abs>;
   3865   def: Loada_pat<sextloadi8,  i32, addrgp, L4_loadrb_abs>;
   3866   def: Loada_pat<zextloadi8,  i32, addrgp, L4_loadrub_abs>;
   3867 
   3868   def: Loada_pat<extloadi16,  i32, addrgp, L4_loadruh_abs>;
   3869   def: Loada_pat<sextloadi16, i32, addrgp, L4_loadrh_abs>;
   3870   def: Loada_pat<zextloadi16, i32, addrgp, L4_loadruh_abs>;
   3871 
   3872   def: Loada_pat<load,        i32, addrgp, L4_loadri_abs>;
   3873   def: Loada_pat<load,        i64, addrgp, L4_loadrd_abs>;
   3874 }
   3875 
   3876 let AddedComplexity = 100 in {
   3877   def: Storea_pat<truncstorei8,  I32, addrgp, S2_storerbabs>;
   3878   def: Storea_pat<truncstorei16, I32, addrgp, S2_storerhabs>;
   3879   def: Storea_pat<store,         I32, addrgp, S2_storeriabs>;
   3880   def: Storea_pat<store,         I64, addrgp, S2_storerdabs>;
   3881 }
   3882 
   3883 def: Loada_pat<atomic_load_8,  i32, addrgp, L4_loadrub_abs>;
   3884 def: Loada_pat<atomic_load_16, i32, addrgp, L4_loadruh_abs>;
   3885 def: Loada_pat<atomic_load_32, i32, addrgp, L4_loadri_abs>;
   3886 def: Loada_pat<atomic_load_64, i64, addrgp, L4_loadrd_abs>;
   3887 
   3888 def: Storea_pat<SwapSt<atomic_store_8>,  I32, addrgp, S2_storerbabs>;
   3889 def: Storea_pat<SwapSt<atomic_store_16>, I32, addrgp, S2_storerhabs>;
   3890 def: Storea_pat<SwapSt<atomic_store_32>, I32, addrgp, S2_storeriabs>;
   3891 def: Storea_pat<SwapSt<atomic_store_64>, I64, addrgp, S2_storerdabs>;
   3892 
   3893 let Constraints = "@earlyclobber $dst" in
   3894 def Insert4 : PseudoM<(outs DoubleRegs:$dst), (ins IntRegs:$a, IntRegs:$b,
   3895                                                    IntRegs:$c, IntRegs:$d),
   3896   ".error \"Should never try to emit Insert4\"",
   3897   [(set (i64 DoubleRegs:$dst),
   3898         (or (or (or (shl (i64 (zext (i32 (and (i32 IntRegs:$b), (i32 65535))))),
   3899                          (i32 16)),
   3900                     (i64 (zext (i32 (and (i32 IntRegs:$a), (i32 65535)))))),
   3901                 (shl (i64 (anyext (i32 (and (i32 IntRegs:$c), (i32 65535))))),
   3902                      (i32 32))),
   3903             (shl (i64 (anyext (i32 IntRegs:$d))), (i32 48))))]>;
   3904 
   3905 //===----------------------------------------------------------------------===//
   3906 // :raw for of boundscheck:hi:lo insns
   3907 //===----------------------------------------------------------------------===//
   3908 
   3909 // A4_boundscheck_lo: Detect if a register is within bounds.
   3910 let hasSideEffects = 0 in
   3911 def A4_boundscheck_lo: ALU64Inst <
   3912   (outs PredRegs:$Pd),
   3913   (ins DoubleRegs:$Rss, DoubleRegs:$Rtt),
   3914   "$Pd = boundscheck($Rss, $Rtt):raw:lo"> {
   3915     bits<2> Pd;
   3916     bits<5> Rss;
   3917     bits<5> Rtt;
   3918 
   3919     let IClass = 0b1101;
   3920 
   3921     let Inst{27-23} = 0b00100;
   3922     let Inst{13} = 0b1;
   3923     let Inst{7-5} = 0b100;
   3924     let Inst{1-0} = Pd;
   3925     let Inst{20-16} = Rss;
   3926     let Inst{12-8} = Rtt;
   3927   }
   3928 
   3929 // A4_boundscheck_hi: Detect if a register is within bounds.
   3930 let hasSideEffects = 0 in
   3931 def A4_boundscheck_hi: ALU64Inst <
   3932   (outs PredRegs:$Pd),
   3933   (ins DoubleRegs:$Rss, DoubleRegs:$Rtt),
   3934   "$Pd = boundscheck($Rss, $Rtt):raw:hi"> {
   3935     bits<2> Pd;
   3936     bits<5> Rss;
   3937     bits<5> Rtt;
   3938 
   3939     let IClass = 0b1101;
   3940 
   3941     let Inst{27-23} = 0b00100;
   3942     let Inst{13} = 0b1;
   3943     let Inst{7-5} = 0b101;
   3944     let Inst{1-0} = Pd;
   3945     let Inst{20-16} = Rss;
   3946     let Inst{12-8} = Rtt;
   3947   }
   3948 
   3949 let hasSideEffects = 0, isAsmParserOnly = 1 in
   3950 def A4_boundscheck : MInst <
   3951   (outs PredRegs:$Pd), (ins IntRegs:$Rs, DoubleRegs:$Rtt),
   3952   "$Pd=boundscheck($Rs,$Rtt)">;
   3953 
   3954 // A4_tlbmatch: Detect if a VA/ASID matches a TLB entry.
   3955 let isPredicateLate = 1, hasSideEffects = 0 in
   3956 def A4_tlbmatch : ALU64Inst<(outs PredRegs:$Pd),
   3957   (ins DoubleRegs:$Rs, IntRegs:$Rt),
   3958   "$Pd = tlbmatch($Rs, $Rt)",
   3959   [], "", ALU64_tc_2early_SLOT23> {
   3960     bits<2> Pd;
   3961     bits<5> Rs;
   3962     bits<5> Rt;
   3963 
   3964     let IClass = 0b1101;
   3965     let Inst{27-23} = 0b00100;
   3966     let Inst{20-16} = Rs;
   3967     let Inst{13} = 0b1;
   3968     let Inst{12-8} = Rt;
   3969     let Inst{7-5} = 0b011;
   3970     let Inst{1-0} = Pd;
   3971   }
   3972 
   3973 // We need custom lowering of ISD::PREFETCH into HexagonISD::DCFETCH
   3974 // because the SDNode ISD::PREFETCH has properties MayLoad and MayStore.
   3975 // We don't really want either one here.
   3976 def SDTHexagonDCFETCH : SDTypeProfile<0, 2, [SDTCisPtrTy<0>,SDTCisInt<1>]>;
   3977 def HexagonDCFETCH : SDNode<"HexagonISD::DCFETCH", SDTHexagonDCFETCH,
   3978                             [SDNPHasChain]>;
   3979 
   3980 // Use LD0Inst for dcfetch, but set "mayLoad" to 0 because this doesn't
   3981 // really do a load.
   3982 let hasSideEffects = 1, mayLoad = 0 in
   3983 def Y2_dcfetchbo : LD0Inst<(outs), (ins IntRegs:$Rs, u11_3Imm:$u11_3),
   3984       "dcfetch($Rs + #$u11_3)",
   3985       [(HexagonDCFETCH IntRegs:$Rs, u11_3ImmPred:$u11_3)],
   3986       "", LD_tc_ld_SLOT0> {
   3987   bits<5> Rs;
   3988   bits<14> u11_3;
   3989 
   3990   let IClass = 0b1001;
   3991   let Inst{27-21} = 0b0100000;
   3992   let Inst{20-16} = Rs;
   3993   let Inst{13} = 0b0;
   3994   let Inst{10-0} = u11_3{13-3};
   3995 }
   3996 
   3997 //===----------------------------------------------------------------------===//
   3998 // Compound instructions
   3999 //===----------------------------------------------------------------------===//
   4000 
   4001 let isBranch = 1, hasSideEffects = 0, isExtentSigned = 1,
   4002     isPredicated = 1, isPredicatedNew = 1, isExtendable = 1,
   4003     opExtentBits = 11, opExtentAlign = 2, opExtendable = 1,
   4004     isTerminator = 1 in
   4005 class CJInst_tstbit_R0<string px, bit np, string tnt>
   4006   : InstHexagon<(outs), (ins IntRegs:$Rs, brtarget:$r9_2),
   4007   ""#px#" = tstbit($Rs, #0); if ("
   4008     #!if(np, "!","")#""#px#".new) jump:"#tnt#" $r9_2",
   4009   [], "", COMPOUND, TypeCOMPOUND>, OpcodeHexagon {
   4010   bits<4> Rs;
   4011   bits<11> r9_2;
   4012 
   4013   // np: !p[01]
   4014   let isPredicatedFalse = np;
   4015   // tnt: Taken/Not Taken
   4016   let isBrTaken = !if (!eq(tnt, "t"), "true", "false");
   4017   let isTaken   = !if (!eq(tnt, "t"), 1, 0);
   4018 
   4019   let IClass = 0b0001;
   4020   let Inst{27-26} = 0b00;
   4021   let Inst{25} = !if (!eq(px, "!p1"), 1,
   4022                  !if (!eq(px,  "p1"), 1, 0));
   4023   let Inst{24-23} = 0b11;
   4024   let Inst{22} = np;
   4025   let Inst{21-20} = r9_2{10-9};
   4026   let Inst{19-16} = Rs;
   4027   let Inst{13} = !if (!eq(tnt, "t"), 1, 0);
   4028   let Inst{9-8} = 0b11;
   4029   let Inst{7-1} = r9_2{8-2};
   4030 }
   4031 
   4032 let Defs = [PC, P0], Uses = [P0] in {
   4033   def J4_tstbit0_tp0_jump_nt : CJInst_tstbit_R0<"p0", 0, "nt">;
   4034   def J4_tstbit0_tp0_jump_t : CJInst_tstbit_R0<"p0", 0, "t">;
   4035   def J4_tstbit0_fp0_jump_nt : CJInst_tstbit_R0<"p0", 1, "nt">;
   4036   def J4_tstbit0_fp0_jump_t : CJInst_tstbit_R0<"p0", 1, "t">;
   4037 }
   4038 
   4039 let Defs = [PC, P1], Uses = [P1] in {
   4040   def J4_tstbit0_tp1_jump_nt : CJInst_tstbit_R0<"p1", 0, "nt">;
   4041   def J4_tstbit0_tp1_jump_t : CJInst_tstbit_R0<"p1", 0, "t">;
   4042   def J4_tstbit0_fp1_jump_nt : CJInst_tstbit_R0<"p1", 1, "nt">;
   4043   def J4_tstbit0_fp1_jump_t : CJInst_tstbit_R0<"p1", 1, "t">;
   4044 }
   4045 
   4046 
   4047 let isBranch = 1, hasSideEffects = 0,
   4048     isExtentSigned = 1, isPredicated = 1, isPredicatedNew = 1,
   4049     isExtendable = 1, opExtentBits = 11, opExtentAlign = 2,
   4050     opExtendable = 2, isTerminator = 1 in
   4051 class CJInst_RR<string px, string op, bit np, string tnt>
   4052   : InstHexagon<(outs), (ins IntRegs:$Rs, IntRegs:$Rt, brtarget:$r9_2),
   4053   ""#px#" = cmp."#op#"($Rs, $Rt); if ("
   4054    #!if(np, "!","")#""#px#".new) jump:"#tnt#" $r9_2",
   4055   [], "", COMPOUND, TypeCOMPOUND>, OpcodeHexagon {
   4056   bits<4> Rs;
   4057   bits<4> Rt;
   4058   bits<11> r9_2;
   4059 
   4060   // np: !p[01]
   4061   let isPredicatedFalse = np;
   4062   // tnt: Taken/Not Taken
   4063   let isBrTaken = !if (!eq(tnt, "t"), "true", "false");
   4064   let isTaken   = !if (!eq(tnt, "t"), 1, 0);
   4065 
   4066   let IClass = 0b0001;
   4067   let Inst{27-23} = !if (!eq(op, "eq"),  0b01000,
   4068                     !if (!eq(op, "gt"),  0b01001,
   4069                     !if (!eq(op, "gtu"), 0b01010, 0)));
   4070   let Inst{22} = np;
   4071   let Inst{21-20} = r9_2{10-9};
   4072   let Inst{19-16} = Rs;
   4073   let Inst{13} = !if (!eq(tnt, "t"), 1, 0);
   4074   // px: Predicate reg 0/1
   4075   let Inst{12} = !if (!eq(px, "!p1"), 1,
   4076                  !if (!eq(px,  "p1"), 1, 0));
   4077   let Inst{11-8} = Rt;
   4078   let Inst{7-1} = r9_2{8-2};
   4079 }
   4080 
   4081 // P[10] taken/not taken.
   4082 multiclass T_tnt_CJInst_RR<string op, bit np> {
   4083   let Defs = [PC, P0], Uses = [P0] in {
   4084     def NAME#p0_jump_nt : CJInst_RR<"p0", op, np, "nt">;
   4085     def NAME#p0_jump_t : CJInst_RR<"p0", op, np, "t">;
   4086   }
   4087   let Defs = [PC, P1], Uses = [P1] in {
   4088     def NAME#p1_jump_nt : CJInst_RR<"p1", op, np, "nt">;
   4089     def NAME#p1_jump_t : CJInst_RR<"p1", op, np, "t">;
   4090   }
   4091 }
   4092 // Predicate / !Predicate
   4093 multiclass T_pnp_CJInst_RR<string op>{
   4094   defm J4_cmp#NAME#_t : T_tnt_CJInst_RR<op, 0>;
   4095   defm J4_cmp#NAME#_f : T_tnt_CJInst_RR<op, 1>;
   4096 }
   4097 // TypeCJ Instructions compare RR and jump
   4098 defm eq : T_pnp_CJInst_RR<"eq">;
   4099 defm gt : T_pnp_CJInst_RR<"gt">;
   4100 defm gtu : T_pnp_CJInst_RR<"gtu">;
   4101 
   4102 let isBranch = 1, hasSideEffects = 0, isExtentSigned = 1,
   4103     isPredicated = 1, isPredicatedNew = 1, isExtendable = 1, opExtentBits = 11,
   4104     opExtentAlign = 2, opExtendable = 2, isTerminator = 1 in
   4105 class CJInst_RU5<string px, string op, bit np, string tnt>
   4106   : InstHexagon<(outs), (ins IntRegs:$Rs, u5Imm:$U5, brtarget:$r9_2),
   4107   ""#px#" = cmp."#op#"($Rs, #$U5); if ("
   4108     #!if(np, "!","")#""#px#".new) jump:"#tnt#" $r9_2",
   4109   [], "", COMPOUND, TypeCOMPOUND>, OpcodeHexagon {
   4110   bits<4> Rs;
   4111   bits<5> U5;
   4112   bits<11> r9_2;
   4113 
   4114   // np: !p[01]
   4115   let isPredicatedFalse = np;
   4116   // tnt: Taken/Not Taken
   4117   let isBrTaken = !if (!eq(tnt, "t"), "true", "false");
   4118   let isTaken   = !if (!eq(tnt, "t"), 1, 0);
   4119 
   4120   let IClass = 0b0001;
   4121   let Inst{27-26} = 0b00;
   4122   // px: Predicate reg 0/1
   4123   let Inst{25} = !if (!eq(px, "!p1"), 1,
   4124                  !if (!eq(px,  "p1"), 1, 0));
   4125   let Inst{24-23} = !if (!eq(op, "eq"),  0b00,
   4126                     !if (!eq(op, "gt"),  0b01,
   4127                     !if (!eq(op, "gtu"), 0b10, 0)));
   4128   let Inst{22} = np;
   4129   let Inst{21-20} = r9_2{10-9};
   4130   let Inst{19-16} = Rs;
   4131   let Inst{13} = !if (!eq(tnt, "t"), 1, 0);
   4132   let Inst{12-8} = U5;
   4133   let Inst{7-1} = r9_2{8-2};
   4134 }
   4135 // P[10] taken/not taken.
   4136 multiclass T_tnt_CJInst_RU5<string op, bit np> {
   4137   let Defs = [PC, P0], Uses = [P0] in {
   4138     def NAME#p0_jump_nt : CJInst_RU5<"p0", op, np, "nt">;
   4139     def NAME#p0_jump_t : CJInst_RU5<"p0", op, np, "t">;
   4140   }
   4141   let Defs = [PC, P1], Uses = [P1] in {
   4142     def NAME#p1_jump_nt : CJInst_RU5<"p1", op, np, "nt">;
   4143     def NAME#p1_jump_t : CJInst_RU5<"p1", op, np, "t">;
   4144   }
   4145 }
   4146 // Predicate / !Predicate
   4147 multiclass T_pnp_CJInst_RU5<string op>{
   4148   defm J4_cmp#NAME#i_t : T_tnt_CJInst_RU5<op, 0>;
   4149   defm J4_cmp#NAME#i_f : T_tnt_CJInst_RU5<op, 1>;
   4150 }
   4151 // TypeCJ Instructions compare RI and jump
   4152 defm eq : T_pnp_CJInst_RU5<"eq">;
   4153 defm gt : T_pnp_CJInst_RU5<"gt">;
   4154 defm gtu : T_pnp_CJInst_RU5<"gtu">;
   4155 
   4156 let isBranch = 1, hasSideEffects = 0, isExtentSigned = 1,
   4157     isPredicated = 1, isPredicatedFalse = 1, isPredicatedNew = 1,
   4158     isExtendable = 1, opExtentBits = 11, opExtentAlign = 2, opExtendable = 1,
   4159     isTerminator = 1 in
   4160 class CJInst_Rn1<string px, string op, bit np, string tnt>
   4161   : InstHexagon<(outs), (ins IntRegs:$Rs, brtarget:$r9_2),
   4162   ""#px#" = cmp."#op#"($Rs,#-1); if ("
   4163   #!if(np, "!","")#""#px#".new) jump:"#tnt#" $r9_2",
   4164   [], "", COMPOUND, TypeCOMPOUND>, OpcodeHexagon {
   4165   bits<4> Rs;
   4166   bits<11> r9_2;
   4167 
   4168   // np: !p[01]
   4169   let isPredicatedFalse = np;
   4170   // tnt: Taken/Not Taken
   4171   let isBrTaken = !if (!eq(tnt, "t"), "true", "false");
   4172   let isTaken   = !if (!eq(tnt, "t"), 1, 0);
   4173 
   4174   let IClass = 0b0001;
   4175   let Inst{27-26} = 0b00;
   4176   let Inst{25} = !if (!eq(px, "!p1"), 1,
   4177                  !if (!eq(px,  "p1"), 1, 0));
   4178 
   4179   let Inst{24-23} = 0b11;
   4180   let Inst{22} = np;
   4181   let Inst{21-20} = r9_2{10-9};
   4182   let Inst{19-16} = Rs;
   4183   let Inst{13} = !if (!eq(tnt, "t"), 1, 0);
   4184   let Inst{9-8} = !if (!eq(op, "eq"),  0b00,
   4185                   !if (!eq(op, "gt"),  0b01, 0));
   4186   let Inst{7-1} = r9_2{8-2};
   4187 }
   4188 
   4189 // P[10] taken/not taken.
   4190 multiclass T_tnt_CJInst_Rn1<string op, bit np> {
   4191   let Defs = [PC, P0], Uses = [P0] in {
   4192     def NAME#p0_jump_nt : CJInst_Rn1<"p0", op, np, "nt">;
   4193     def NAME#p0_jump_t : CJInst_Rn1<"p0", op, np, "t">;
   4194   }
   4195   let Defs = [PC, P1], Uses = [P1] in {
   4196     def NAME#p1_jump_nt : CJInst_Rn1<"p1", op, np, "nt">;
   4197     def NAME#p1_jump_t : CJInst_Rn1<"p1", op, np, "t">;
   4198   }
   4199 }
   4200 // Predicate / !Predicate
   4201 multiclass T_pnp_CJInst_Rn1<string op>{
   4202   defm J4_cmp#NAME#n1_t : T_tnt_CJInst_Rn1<op, 0>;
   4203   defm J4_cmp#NAME#n1_f : T_tnt_CJInst_Rn1<op, 1>;
   4204 }
   4205 // TypeCJ Instructions compare -1 and jump
   4206 defm eq : T_pnp_CJInst_Rn1<"eq">;
   4207 defm gt : T_pnp_CJInst_Rn1<"gt">;
   4208 
   4209 // J4_jumpseti: Direct unconditional jump and set register to immediate.
   4210 let Defs = [PC], isBranch = 1, hasSideEffects = 0, hasNewValue = 1,
   4211     isExtentSigned = 1, opNewValue = 0, isExtendable = 1, opExtentBits = 11,
   4212     opExtentAlign = 2, opExtendable = 2 in
   4213 def J4_jumpseti: CJInst <
   4214   (outs IntRegs:$Rd),
   4215   (ins u6Imm:$U6, brtarget:$r9_2),
   4216   "$Rd = #$U6 ; jump $r9_2"> {
   4217     bits<4> Rd;
   4218     bits<6> U6;
   4219     bits<11> r9_2;
   4220 
   4221     let IClass = 0b0001;
   4222     let Inst{27-24} = 0b0110;
   4223     let Inst{21-20} = r9_2{10-9};
   4224     let Inst{19-16} = Rd;
   4225     let Inst{13-8} = U6;
   4226     let Inst{7-1} = r9_2{8-2};
   4227   }
   4228 
   4229 // J4_jumpsetr: Direct unconditional jump and transfer register.
   4230 let Defs = [PC], isBranch = 1, hasSideEffects = 0, hasNewValue = 1,
   4231     isExtentSigned = 1, opNewValue = 0, isExtendable = 1, opExtentBits = 11,
   4232     opExtentAlign = 2, opExtendable = 2 in
   4233 def J4_jumpsetr: CJInst <
   4234   (outs IntRegs:$Rd),
   4235   (ins IntRegs:$Rs, brtarget:$r9_2),
   4236   "$Rd = $Rs ; jump $r9_2"> {
   4237     bits<4> Rd;
   4238     bits<4> Rs;
   4239     bits<11> r9_2;
   4240 
   4241     let IClass = 0b0001;
   4242     let Inst{27-24} = 0b0111;
   4243     let Inst{21-20} = r9_2{10-9};
   4244     let Inst{11-8} = Rd;
   4245     let Inst{19-16} = Rs;
   4246     let Inst{7-1} = r9_2{8-2};
   4247   }
   4248 
   4249 // Duplex instructions
   4250 //===----------------------------------------------------------------------===//
   4251 include "HexagonIsetDx.td"
   4252