[Hexagon] Renaming old multiclass for removal. Adding post-increment store classes...
[oota-llvm.git] / lib / Target / Hexagon / HexagonInstrInfo.td
1 //==- HexagonInstrInfo.td - Target Description for Hexagon -*- 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 instructions in TableGen format.
11 //
12 //===----------------------------------------------------------------------===//
13
14 include "HexagonInstrFormats.td"
15 include "HexagonOperands.td"
16
17 // Pattern fragment that combines the value type and the register class
18 // into a single parameter.
19 // The pat frags in the definitions below need to have a named register,
20 // otherwise i32 will be assumed regardless of the register class. The
21 // name of the register does not matter.
22 def I1  : PatLeaf<(i1 PredRegs:$R)>;
23 def I32 : PatLeaf<(i32 IntRegs:$R)>;
24 def I64 : PatLeaf<(i64 DoubleRegs:$R)>;
25 def F32 : PatLeaf<(f32 IntRegs:$R)>;
26 def F64 : PatLeaf<(f64 DoubleRegs:$R)>;
27
28 // Pattern fragments to extract the low and high subregisters from a
29 // 64-bit value.
30 def LoReg: OutPatFrag<(ops node:$Rs),
31                       (EXTRACT_SUBREG (i64 $Rs), subreg_loreg)>;
32
33 //===----------------------------------------------------------------------===//
34
35 //===----------------------------------------------------------------------===//
36 // Compare
37 //===----------------------------------------------------------------------===//
38 let hasSideEffects = 0, isCompare = 1, InputType = "imm", isExtendable = 1,
39     opExtendable = 2 in
40 class T_CMP <string mnemonic, bits<2> MajOp, bit isNot, Operand ImmOp>
41   : ALU32Inst <(outs PredRegs:$dst),
42                (ins IntRegs:$src1, ImmOp:$src2),
43   "$dst = "#!if(isNot, "!","")#mnemonic#"($src1, #$src2)",
44   [], "",ALU32_2op_tc_2early_SLOT0123 >, ImmRegRel {
45     bits<2> dst;
46     bits<5> src1;
47     bits<10> src2;
48     let CextOpcode = mnemonic;
49     let opExtentBits  = !if(!eq(mnemonic, "cmp.gtu"), 9, 10);
50     let isExtentSigned = !if(!eq(mnemonic, "cmp.gtu"), 0, 1);
51
52     let IClass = 0b0111;
53
54     let Inst{27-24} = 0b0101;
55     let Inst{23-22} = MajOp;
56     let Inst{21}    = !if(!eq(mnemonic, "cmp.gtu"), 0, src2{9});
57     let Inst{20-16} = src1;
58     let Inst{13-5}  = src2{8-0};
59     let Inst{4}     = isNot;
60     let Inst{3-2}   = 0b00;
61     let Inst{1-0}   = dst;
62   }
63
64 def C2_cmpeqi   : T_CMP <"cmp.eq",  0b00, 0, s10Ext>;
65 def C2_cmpgti   : T_CMP <"cmp.gt",  0b01, 0, s10Ext>;
66 def C2_cmpgtui  : T_CMP <"cmp.gtu", 0b10, 0, u9Ext>;
67
68 class T_CMP_pat <InstHexagon MI, PatFrag OpNode, PatLeaf ImmPred>
69   : Pat<(i1 (OpNode (i32 IntRegs:$src1), ImmPred:$src2)),
70         (MI IntRegs:$src1, ImmPred:$src2)>;
71
72 def : T_CMP_pat <C2_cmpeqi,  seteq,  s10ImmPred>;
73 def : T_CMP_pat <C2_cmpgti,  setgt,  s10ImmPred>;
74 def : T_CMP_pat <C2_cmpgtui, setugt, u9ImmPred>;
75
76 //===----------------------------------------------------------------------===//
77 // ALU32/ALU +
78 //===----------------------------------------------------------------------===//
79 def SDTHexagonI64I32I32 : SDTypeProfile<1, 2,
80   [SDTCisVT<0, i64>, SDTCisVT<1, i32>, SDTCisSameAs<1, 2>]>;
81
82 def HexagonCOMBINE : SDNode<"HexagonISD::COMBINE", SDTHexagonI64I32I32>;
83
84 let hasSideEffects = 0, hasNewValue = 1, InputType = "reg" in
85 class T_ALU32_3op<string mnemonic, bits<3> MajOp, bits<3> MinOp, bit OpsRev,
86                   bit IsComm>
87   : ALU32_rr<(outs IntRegs:$Rd), (ins IntRegs:$Rs, IntRegs:$Rt),
88              "$Rd = "#mnemonic#"($Rs, $Rt)",
89              [], "", ALU32_3op_tc_1_SLOT0123>, ImmRegRel, PredRel {
90   let isCommutable = IsComm;
91   let BaseOpcode = mnemonic#_rr;
92   let CextOpcode = mnemonic;
93
94   bits<5> Rs;
95   bits<5> Rt;
96   bits<5> Rd;
97
98   let IClass = 0b1111;
99   let Inst{27} = 0b0;
100   let Inst{26-24} = MajOp;
101   let Inst{23-21} = MinOp;
102   let Inst{20-16} = !if(OpsRev,Rt,Rs);
103   let Inst{12-8} = !if(OpsRev,Rs,Rt);
104   let Inst{4-0} = Rd;
105 }
106
107 let hasSideEffects = 0, hasNewValue = 1 in
108 class T_ALU32_3op_pred<string mnemonic, bits<3> MajOp, bits<3> MinOp,
109                        bit OpsRev, bit PredNot, bit PredNew>
110   : ALU32_rr<(outs IntRegs:$Rd), (ins PredRegs:$Pu, IntRegs:$Rs, IntRegs:$Rt),
111              "if ("#!if(PredNot,"!","")#"$Pu"#!if(PredNew,".new","")#") "#
112              "$Rd = "#mnemonic#"($Rs, $Rt)",
113              [], "", ALU32_3op_tc_1_SLOT0123>, ImmRegRel, PredNewRel {
114   let isPredicated = 1;
115   let isPredicatedFalse = PredNot;
116   let isPredicatedNew = PredNew;
117   let BaseOpcode = mnemonic#_rr;
118   let CextOpcode = mnemonic;
119
120   bits<2> Pu;
121   bits<5> Rs;
122   bits<5> Rt;
123   bits<5> Rd;
124
125   let IClass = 0b1111;
126   let Inst{27} = 0b1;
127   let Inst{26-24} = MajOp;
128   let Inst{23-21} = MinOp;
129   let Inst{20-16} = !if(OpsRev,Rt,Rs);
130   let Inst{13} = PredNew;
131   let Inst{12-8} = !if(OpsRev,Rs,Rt);
132   let Inst{7} = PredNot;
133   let Inst{6-5} = Pu;
134   let Inst{4-0} = Rd;
135 }
136
137 class T_ALU32_combineh<string Op1, string Op2, bits<3> MajOp, bits<3> MinOp,
138                       bit OpsRev>
139   : T_ALU32_3op<"", MajOp, MinOp, OpsRev, 0> {
140   let AsmString = "$Rd = combine($Rs"#Op1#", $Rt"#Op2#")";
141 }
142
143 let isCodeGenOnly = 0 in {
144 def A2_combine_hh : T_ALU32_combineh<".h", ".h", 0b011, 0b100, 1>;
145 def A2_combine_hl : T_ALU32_combineh<".h", ".l", 0b011, 0b101, 1>;
146 def A2_combine_lh : T_ALU32_combineh<".l", ".h", 0b011, 0b110, 1>;
147 def A2_combine_ll : T_ALU32_combineh<".l", ".l", 0b011, 0b111, 1>;
148 }
149
150 class T_ALU32_3op_sfx<string mnemonic, string suffix, bits<3> MajOp,
151                       bits<3> MinOp, bit OpsRev, bit IsComm>
152   : T_ALU32_3op<"", MajOp, MinOp, OpsRev, IsComm> {
153   let AsmString = "$Rd = "#mnemonic#"($Rs, $Rt)"#suffix;
154 }
155
156 let Defs = [USR_OVF], Itinerary = ALU32_3op_tc_2_SLOT0123, 
157     isCodeGenOnly = 0 in {
158   def A2_addsat   : T_ALU32_3op_sfx<"add",    ":sat", 0b110, 0b010, 0, 1>;
159   def A2_subsat   : T_ALU32_3op_sfx<"sub",    ":sat", 0b110, 0b110, 1, 0>;
160 }
161
162 multiclass T_ALU32_3op_p<string mnemonic, bits<3> MajOp, bits<3> MinOp,
163                          bit OpsRev> {
164   def t    : T_ALU32_3op_pred<mnemonic, MajOp, MinOp, OpsRev, 0, 0>;
165   def f    : T_ALU32_3op_pred<mnemonic, MajOp, MinOp, OpsRev, 1, 0>;
166   def tnew : T_ALU32_3op_pred<mnemonic, MajOp, MinOp, OpsRev, 0, 1>;
167   def fnew : T_ALU32_3op_pred<mnemonic, MajOp, MinOp, OpsRev, 1, 1>;
168 }
169
170 multiclass T_ALU32_3op_A2<string mnemonic, bits<3> MajOp, bits<3> MinOp,
171                           bit OpsRev, bit IsComm> {
172   let isPredicable = 1 in
173   def  A2_#NAME  : T_ALU32_3op  <mnemonic, MajOp, MinOp, OpsRev, IsComm>;
174   defm A2_p#NAME : T_ALU32_3op_p<mnemonic, MajOp, MinOp, OpsRev>;
175 }
176
177 let isCodeGenOnly = 0 in {
178 defm add : T_ALU32_3op_A2<"add", 0b011, 0b000, 0, 1>;
179 defm and : T_ALU32_3op_A2<"and", 0b001, 0b000, 0, 1>;
180 defm or  : T_ALU32_3op_A2<"or",  0b001, 0b001, 0, 1>;
181 defm sub : T_ALU32_3op_A2<"sub", 0b011, 0b001, 1, 0>;
182 defm xor : T_ALU32_3op_A2<"xor", 0b001, 0b011, 0, 1>;
183 }
184
185 // Pats for instruction selection.
186 class BinOp32_pat<SDNode Op, InstHexagon MI, ValueType ResT>
187   : Pat<(ResT (Op (i32 IntRegs:$Rs), (i32 IntRegs:$Rt))),
188         (ResT (MI IntRegs:$Rs, IntRegs:$Rt))>;
189
190 def: BinOp32_pat<add, A2_add, i32>;
191 def: BinOp32_pat<and, A2_and, i32>;
192 def: BinOp32_pat<or,  A2_or,  i32>;
193 def: BinOp32_pat<sub, A2_sub, i32>;
194 def: BinOp32_pat<xor, A2_xor, i32>;
195
196 // A few special cases producing register pairs:
197 let OutOperandList = (outs DoubleRegs:$Rd), hasNewValue = 0,
198     isCodeGenOnly = 0 in {
199   def S2_packhl    : T_ALU32_3op  <"packhl",  0b101, 0b100, 0, 0>;
200
201   let isPredicable = 1 in
202     def A2_combinew  : T_ALU32_3op  <"combine", 0b101, 0b000, 0, 0>;
203
204   // Conditional combinew uses "newt/f" instead of "t/fnew".
205   def C2_ccombinewt    : T_ALU32_3op_pred<"combine", 0b101, 0b000, 0, 0, 0>;
206   def C2_ccombinewf    : T_ALU32_3op_pred<"combine", 0b101, 0b000, 0, 1, 0>;
207   def C2_ccombinewnewt : T_ALU32_3op_pred<"combine", 0b101, 0b000, 0, 0, 1>;
208   def C2_ccombinewnewf : T_ALU32_3op_pred<"combine", 0b101, 0b000, 0, 1, 1>;
209 }
210
211 let hasSideEffects = 0, hasNewValue = 1, isCompare = 1, InputType = "reg"  in
212 class T_ALU32_3op_cmp<string mnemonic, bits<2> MinOp, bit IsNeg, bit IsComm>
213   : ALU32_rr<(outs PredRegs:$Pd), (ins IntRegs:$Rs, IntRegs:$Rt),
214              "$Pd = "#mnemonic#"($Rs, $Rt)",
215              [], "", ALU32_3op_tc_1_SLOT0123>, ImmRegRel {
216   let CextOpcode = mnemonic;
217   let isCommutable = IsComm;
218   bits<5> Rs;
219   bits<5> Rt;
220   bits<2> Pd;
221
222   let IClass = 0b1111;
223   let Inst{27-24} = 0b0010;
224   let Inst{22-21} = MinOp;
225   let Inst{20-16} = Rs;
226   let Inst{12-8} = Rt;
227   let Inst{4} = IsNeg;
228   let Inst{3-2} = 0b00;
229   let Inst{1-0} = Pd;
230 }
231
232 let Itinerary = ALU32_3op_tc_2early_SLOT0123, isCodeGenOnly = 0 in {
233   def C2_cmpeq   : T_ALU32_3op_cmp< "cmp.eq",  0b00, 0, 1>;
234   def C2_cmpgt   : T_ALU32_3op_cmp< "cmp.gt",  0b10, 0, 0>;
235   def C2_cmpgtu  : T_ALU32_3op_cmp< "cmp.gtu", 0b11, 0, 0>;
236 }
237
238 // Patfrag to convert the usual comparison patfrags (e.g. setlt) to ones
239 // that reverse the order of the operands.
240 class RevCmp<PatFrag F> : PatFrag<(ops node:$rhs, node:$lhs), F.Fragment>;
241
242 // Pats for compares. They use PatFrags as operands, not SDNodes,
243 // since seteq/setgt/etc. are defined as ParFrags.
244 class T_cmp32_rr_pat<InstHexagon MI, PatFrag Op, ValueType VT>
245   : Pat<(VT (Op (i32 IntRegs:$Rs), (i32 IntRegs:$Rt))),
246         (VT (MI IntRegs:$Rs, IntRegs:$Rt))>;
247
248 def: T_cmp32_rr_pat<C2_cmpeq,  seteq, i1>;
249 def: T_cmp32_rr_pat<C2_cmpgt,  setgt, i1>;
250 def: T_cmp32_rr_pat<C2_cmpgtu, setugt, i1>;
251
252 def: T_cmp32_rr_pat<C2_cmpgt,  RevCmp<setlt>,  i1>;
253 def: T_cmp32_rr_pat<C2_cmpgtu, RevCmp<setult>, i1>;
254
255 let CextOpcode = "MUX", InputType = "reg", hasNewValue = 1,
256   isCodeGenOnly = 0 in
257 def C2_mux: ALU32_rr<(outs IntRegs:$Rd),
258                      (ins PredRegs:$Pu, IntRegs:$Rs, IntRegs:$Rt),
259       "$Rd = mux($Pu, $Rs, $Rt)", [], "", ALU32_3op_tc_1_SLOT0123>, ImmRegRel {
260   bits<5> Rd;
261   bits<2> Pu;
262   bits<5> Rs;
263   bits<5> Rt;
264
265   let CextOpcode = "mux";
266   let InputType = "reg";
267   let hasSideEffects = 0;
268   let IClass = 0b1111;
269
270   let Inst{27-24} = 0b0100;
271   let Inst{20-16} = Rs;
272   let Inst{12-8} = Rt;
273   let Inst{6-5} = Pu;
274   let Inst{4-0} = Rd;
275 }
276
277 def: Pat<(i32 (select (i1 PredRegs:$Pu), (i32 IntRegs:$Rs), (i32 IntRegs:$Rt))),
278          (C2_mux PredRegs:$Pu, IntRegs:$Rs, IntRegs:$Rt)>;
279
280 // Combines the two immediates into a double register.
281 // Increase complexity to make it greater than any complexity of a combine
282 // that involves a register.
283
284 let isReMaterializable = 1, isMoveImm = 1, isAsCheapAsAMove = 1,
285     isExtentSigned = 1, isExtendable = 1, opExtentBits = 8, opExtendable = 1,
286     AddedComplexity = 75, isCodeGenOnly = 0 in
287 def A2_combineii: ALU32Inst <(outs DoubleRegs:$Rdd), (ins s8Ext:$s8, s8Imm:$S8),
288   "$Rdd = combine(#$s8, #$S8)",
289   [(set (i64 DoubleRegs:$Rdd),
290         (i64 (HexagonCOMBINE(i32 s8ExtPred:$s8), (i32 s8ImmPred:$S8))))]> {
291     bits<5> Rdd;
292     bits<8> s8;
293     bits<8> S8;
294
295     let IClass = 0b0111;
296     let Inst{27-23} = 0b11000;
297     let Inst{22-16} = S8{7-1};
298     let Inst{13}    = S8{0};
299     let Inst{12-5}  = s8;
300     let Inst{4-0}   = Rdd;
301   }
302
303 //===----------------------------------------------------------------------===//
304 // Template class for predicated ADD of a reg and an Immediate value.
305 //===----------------------------------------------------------------------===//
306 let hasNewValue = 1 in
307 class T_Addri_Pred <bit PredNot, bit PredNew>
308   : ALU32_ri <(outs IntRegs:$Rd),
309               (ins PredRegs:$Pu, IntRegs:$Rs, s8Ext:$s8),
310   !if(PredNot, "if (!$Pu", "if ($Pu")#!if(PredNew,".new) $Rd = ",
311   ") $Rd = ")#"add($Rs, #$s8)"> {
312     bits<5> Rd;
313     bits<2> Pu;
314     bits<5> Rs;
315     bits<8> s8;
316
317     let isPredicatedNew = PredNew;
318     let IClass = 0b0111;
319
320     let Inst{27-24} = 0b0100;
321     let Inst{23}    = PredNot;
322     let Inst{22-21} = Pu;
323     let Inst{20-16} = Rs;
324     let Inst{13}    = PredNew;
325     let Inst{12-5}  = s8;
326     let Inst{4-0}   = Rd;
327   }
328
329 //===----------------------------------------------------------------------===//
330 // A2_addi: Add a signed immediate to a register.
331 //===----------------------------------------------------------------------===//
332 let hasNewValue = 1 in
333 class T_Addri <Operand immOp, list<dag> pattern = [] >
334   : ALU32_ri <(outs IntRegs:$Rd),
335               (ins IntRegs:$Rs, immOp:$s16),
336   "$Rd = add($Rs, #$s16)", pattern,
337   //[(set (i32 IntRegs:$Rd), (add (i32 IntRegs:$Rs), (s16ExtPred:$s16)))],
338   "", ALU32_ADDI_tc_1_SLOT0123> {
339     bits<5> Rd;
340     bits<5> Rs;
341     bits<16> s16;
342
343     let IClass = 0b1011;
344
345     let Inst{27-21} = s16{15-9};
346     let Inst{20-16} = Rs;
347     let Inst{13-5}  = s16{8-0};
348     let Inst{4-0}   = Rd;
349   }
350
351 //===----------------------------------------------------------------------===//
352 // Multiclass for ADD of a register and an immediate value.
353 //===----------------------------------------------------------------------===//
354 multiclass Addri_Pred<string mnemonic, bit PredNot> {
355   let isPredicatedFalse = PredNot in {
356     def _c#NAME : T_Addri_Pred<PredNot, 0>;
357     // Predicate new
358     def _cdn#NAME : T_Addri_Pred<PredNot, 1>;
359   }
360 }
361
362 let isExtendable = 1, InputType = "imm" in
363 multiclass Addri_base<string mnemonic, SDNode OpNode> {
364   let CextOpcode = mnemonic, BaseOpcode = mnemonic#_ri in {
365     let opExtendable = 2, isExtentSigned = 1, opExtentBits = 16,
366     isPredicable = 1 in
367     def NAME : T_Addri< s16Ext, // Rd=add(Rs,#s16)
368                         [(set (i32 IntRegs:$Rd),
369                               (add IntRegs:$Rs, s16ExtPred:$s16))]>;
370
371     let opExtendable = 3, isExtentSigned = 1, opExtentBits = 8,
372     hasSideEffects = 0, isPredicated = 1 in {
373       defm Pt : Addri_Pred<mnemonic, 0>;
374       defm NotPt : Addri_Pred<mnemonic, 1>;
375     }
376   }
377 }
378
379 let isCodeGenOnly = 0 in
380 defm ADD_ri : Addri_base<"add", add>, ImmRegRel, PredNewRel;
381
382 //===----------------------------------------------------------------------===//
383 // Template class used for the following ALU32 instructions.
384 // Rd=and(Rs,#s10)
385 // Rd=or(Rs,#s10)
386 //===----------------------------------------------------------------------===//
387 let isExtendable = 1, opExtendable = 2, isExtentSigned = 1, opExtentBits = 10,
388 InputType = "imm", hasNewValue = 1 in
389 class T_ALU32ri_logical <string mnemonic, SDNode OpNode, bits<2> MinOp>
390   : ALU32_ri <(outs IntRegs:$Rd),
391               (ins IntRegs:$Rs, s10Ext:$s10),
392   "$Rd = "#mnemonic#"($Rs, #$s10)" ,
393   [(set (i32 IntRegs:$Rd), (OpNode (i32 IntRegs:$Rs), s10ExtPred:$s10))]> {
394     bits<5> Rd;
395     bits<5> Rs;
396     bits<10> s10;
397     let CextOpcode = mnemonic;
398
399     let IClass = 0b0111;
400
401     let Inst{27-24} = 0b0110;
402     let Inst{23-22} = MinOp;
403     let Inst{21}    = s10{9};
404     let Inst{20-16} = Rs;
405     let Inst{13-5}  = s10{8-0};
406     let Inst{4-0}   = Rd;
407   }
408
409 let isCodeGenOnly = 0 in {
410 def OR_ri  : T_ALU32ri_logical<"or", or, 0b10>, ImmRegRel;
411 def AND_ri : T_ALU32ri_logical<"and", and, 0b00>, ImmRegRel;
412 }
413
414 // Subtract register from immediate
415 // Rd32=sub(#s10,Rs32)
416 let isExtendable = 1, opExtendable = 1, isExtentSigned = 1, opExtentBits = 10,
417 CextOpcode = "sub", InputType = "imm", hasNewValue = 1, isCodeGenOnly = 0 in
418 def SUB_ri: ALU32_ri <(outs IntRegs:$Rd), (ins s10Ext:$s10, IntRegs:$Rs),
419   "$Rd = sub(#$s10, $Rs)" ,
420   [(set IntRegs:$Rd, (sub s10ExtPred:$s10, IntRegs:$Rs))] > ,
421   ImmRegRel {
422     bits<5> Rd;
423     bits<10> s10;
424     bits<5> Rs;
425
426     let IClass = 0b0111;
427
428     let Inst{27-22} = 0b011001;
429     let Inst{21}    = s10{9};
430     let Inst{20-16} = Rs;
431     let Inst{13-5}  = s10{8-0};
432     let Inst{4-0}   = Rd;
433   }
434
435 // Nop.
436 let hasSideEffects = 0, isCodeGenOnly = 0 in
437 def A2_nop: ALU32Inst <(outs), (ins), "nop" > {
438   let IClass = 0b0111;
439   let Inst{27-24} = 0b1111;
440 }
441 // Rd = not(Rs) gets mapped to Rd=sub(#-1, Rs).
442 def : Pat<(not (i32 IntRegs:$src1)),
443           (SUB_ri -1, (i32 IntRegs:$src1))>;
444
445 let hasSideEffects = 0, hasNewValue = 1 in
446 class T_tfr16<bit isHi>
447   : ALU32Inst <(outs IntRegs:$Rx), (ins IntRegs:$src1, u16Imm:$u16),
448   "$Rx"#!if(isHi, ".h", ".l")#" = #$u16",
449   [], "$src1 = $Rx" > {
450     bits<5> Rx;
451     bits<16> u16;
452
453     let IClass = 0b0111;
454     let Inst{27-26} = 0b00;
455     let Inst{25-24} = !if(isHi, 0b10, 0b01);
456     let Inst{23-22} = u16{15-14};
457     let Inst{21}    = 0b1;
458     let Inst{20-16} = Rx;
459     let Inst{13-0}  = u16{13-0};
460   }
461
462 let isCodeGenOnly = 0 in {
463 def A2_tfril: T_tfr16<0>;
464 def A2_tfrih: T_tfr16<1>;
465 }
466
467 // Conditional transfer is an alias to conditional "Rd = add(Rs, #0)".
468 let isPredicated = 1, hasNewValue = 1, opNewValue = 0 in
469 class T_tfr_pred<bit isPredNot, bit isPredNew>
470   : ALU32Inst<(outs IntRegs:$dst),
471               (ins PredRegs:$src1, IntRegs:$src2),
472               "if ("#!if(isPredNot, "!", "")#
473               "$src1"#!if(isPredNew, ".new", "")#
474               ") $dst = $src2"> {
475     bits<5> dst;
476     bits<2> src1;
477     bits<5> src2;
478
479     let isPredicatedFalse = isPredNot;
480     let isPredicatedNew = isPredNew;
481     let IClass = 0b0111;
482
483     let Inst{27-24} = 0b0100;
484     let Inst{23} = isPredNot;
485     let Inst{13} = isPredNew;
486     let Inst{12-5} = 0;
487     let Inst{4-0} = dst;
488     let Inst{22-21} = src1;
489     let Inst{20-16} = src2;
490   }
491
492 let isPredicable = 1 in
493 class T_tfr : ALU32Inst<(outs IntRegs:$dst), (ins IntRegs:$src),
494               "$dst = $src"> {
495     bits<5> dst;
496     bits<5> src;
497
498     let IClass = 0b0111;
499
500     let Inst{27-21} = 0b0000011;
501     let Inst{20-16} = src;
502     let Inst{13}    = 0b0;
503     let Inst{4-0}   = dst;
504   }
505
506 let InputType = "reg", hasNewValue = 1, hasSideEffects = 0 in
507 multiclass tfr_base<string CextOp> {
508   let CextOpcode = CextOp, BaseOpcode = CextOp in {
509     def NAME : T_tfr;
510
511     // Predicate
512     def t : T_tfr_pred<0, 0>;
513     def f : T_tfr_pred<1, 0>;
514     // Predicate new
515     def tnew : T_tfr_pred<0, 1>;
516     def fnew : T_tfr_pred<1, 1>;
517   }
518 }
519
520 // Assembler mapped to C2_ccombinew[t|f|newt|newf].
521 // Please don't add bits to this instruction as it'll be converted into
522 // 'combine' before object code emission.
523 let isPredicated = 1 in
524 class T_tfrp_pred<bit PredNot, bit PredNew>
525   : ALU32_rr <(outs DoubleRegs:$dst),
526               (ins PredRegs:$src1, DoubleRegs:$src2),
527   "if ("#!if(PredNot, "!", "")#"$src1"
528         #!if(PredNew, ".new", "")#") $dst = $src2" > {
529     let isPredicatedFalse = PredNot;
530     let isPredicatedNew = PredNew;
531   }
532
533 // Assembler mapped to A2_combinew.
534 // Please don't add bits to this instruction as it'll be converted into
535 // 'combine' before object code emission.
536 class T_tfrp : ALU32Inst <(outs DoubleRegs:$dst),
537                (ins DoubleRegs:$src),
538     "$dst = $src">;
539
540 let hasSideEffects = 0 in
541 multiclass TFR64_base<string BaseName> {
542   let BaseOpcode = BaseName in {
543     let isPredicable = 1 in
544     def NAME : T_tfrp;
545     // Predicate
546     def t : T_tfrp_pred <0, 0>;
547     def f : T_tfrp_pred <1, 0>;
548     // Predicate new
549     def tnew : T_tfrp_pred <0, 1>;
550     def fnew : T_tfrp_pred <1, 1>;
551   }
552 }
553
554 let InputType = "imm", isExtendable = 1, isExtentSigned = 1, opExtentBits = 12,
555     isMoveImm = 1, opExtendable = 2, BaseOpcode = "TFRI", CextOpcode = "TFR",
556     hasSideEffects = 0, isPredicated = 1, hasNewValue = 1 in
557 class T_TFRI_Pred<bit PredNot, bit PredNew>
558   : ALU32_ri<(outs IntRegs:$Rd), (ins PredRegs:$Pu, s12Ext:$s12),
559     "if ("#!if(PredNot,"!","")#"$Pu"#!if(PredNew,".new","")#") $Rd = #$s12",
560     [], "", ALU32_2op_tc_1_SLOT0123>, ImmRegRel, PredNewRel {
561   let isPredicatedFalse = PredNot;
562   let isPredicatedNew = PredNew;
563
564   bits<5> Rd;
565   bits<2> Pu;
566   bits<12> s12;
567
568   let IClass = 0b0111;
569   let Inst{27-24} = 0b1110;
570   let Inst{23} = PredNot;
571   let Inst{22-21} = Pu;
572   let Inst{20} = 0b0;
573   let Inst{19-16,12-5} = s12;
574   let Inst{13} = PredNew;
575   let Inst{4-0} = Rd;
576 }
577
578 let isCodeGenOnly = 0 in {
579 def C2_cmoveit    : T_TFRI_Pred<0, 0>;
580 def C2_cmoveif    : T_TFRI_Pred<1, 0>;
581 def C2_cmovenewit : T_TFRI_Pred<0, 1>;
582 def C2_cmovenewif : T_TFRI_Pred<1, 1>;
583 }
584
585 let InputType = "imm", isExtendable = 1, isExtentSigned = 1,
586     CextOpcode = "TFR", BaseOpcode = "TFRI", hasNewValue = 1, opNewValue = 0,
587     isAsCheapAsAMove = 1 , opExtendable = 1, opExtentBits = 16, isMoveImm = 1,
588     isPredicated = 0, isPredicable = 1, isReMaterializable = 1,
589     isCodeGenOnly = 0 in
590 def A2_tfrsi : ALU32Inst<(outs IntRegs:$Rd), (ins s16Ext:$s16), "$Rd = #$s16",
591     [(set (i32 IntRegs:$Rd), s16ExtPred:$s16)], "", ALU32_2op_tc_1_SLOT0123>,
592     ImmRegRel, PredRel {
593   bits<5> Rd;
594   bits<16> s16;
595
596   let IClass = 0b0111;
597   let Inst{27-24} = 0b1000;
598   let Inst{23-22,20-16,13-5} = s16;
599   let Inst{4-0} = Rd;
600 }
601
602 let isCodeGenOnly = 0 in
603 defm A2_tfr  : tfr_base<"TFR">, ImmRegRel, PredNewRel;
604 defm A2_tfrp : TFR64_base<"TFR64">, PredNewRel;
605
606 // Assembler mapped
607 let isReMaterializable = 1, isMoveImm = 1, isAsCheapAsAMove = 1 in
608 def A2_tfrpi : ALU64_rr<(outs DoubleRegs:$dst), (ins s8Imm64:$src1),
609                       "$dst = #$src1",
610                       [(set (i64 DoubleRegs:$dst), s8Imm64Pred:$src1)]>;
611
612 // TODO: see if this instruction can be deleted..
613 let isExtendable = 1, opExtendable = 1, opExtentBits = 6 in
614 def TFRI64_V4 : ALU64_rr<(outs DoubleRegs:$dst), (ins u6Ext:$src1),
615                          "$dst = #$src1">;
616
617 //===----------------------------------------------------------------------===//
618 // ALU32/ALU -
619 //===----------------------------------------------------------------------===//
620
621
622 //===----------------------------------------------------------------------===//
623 // ALU32/PERM +
624 //===----------------------------------------------------------------------===//
625 // Scalar mux register immediate.
626 let hasSideEffects = 0, isExtentSigned = 1, CextOpcode = "MUX",
627     InputType = "imm", hasNewValue = 1, isExtendable = 1, opExtentBits = 8 in
628 class T_MUX1 <bit MajOp, dag ins, string AsmStr>
629       : ALU32Inst <(outs IntRegs:$Rd), ins, AsmStr>, ImmRegRel {
630   bits<5> Rd;
631   bits<2> Pu;
632   bits<8> s8;
633   bits<5> Rs;
634
635   let IClass = 0b0111;
636   let Inst{27-24} = 0b0011;
637   let Inst{23} = MajOp;
638   let Inst{22-21} = Pu;
639   let Inst{20-16} = Rs;
640   let Inst{13}    = 0b0;
641   let Inst{12-5}  = s8;
642   let Inst{4-0}   = Rd;
643 }
644
645 let opExtendable = 2, isCodeGenOnly = 0 in
646 def C2_muxri : T_MUX1<0b1, (ins PredRegs:$Pu, s8Ext:$s8, IntRegs:$Rs),
647                            "$Rd = mux($Pu, #$s8, $Rs)">;
648
649 let opExtendable = 3, isCodeGenOnly = 0 in
650 def C2_muxir : T_MUX1<0b0, (ins PredRegs:$Pu, IntRegs:$Rs, s8Ext:$s8),
651                            "$Rd = mux($Pu, $Rs, #$s8)">;
652
653 def : Pat<(i32 (select I1:$Pu, s8ExtPred:$s8, I32:$Rs)),
654           (C2_muxri I1:$Pu, s8ExtPred:$s8, I32:$Rs)>;
655
656 def : Pat<(i32 (select I1:$Pu, I32:$Rs, s8ExtPred:$s8)),
657           (C2_muxir I1:$Pu, I32:$Rs, s8ExtPred:$s8)>;
658
659 // C2_muxii: Scalar mux immediates.
660 let isExtentSigned = 1, hasNewValue = 1, isExtendable = 1,
661     opExtentBits = 8, opExtendable = 2, isCodeGenOnly = 0 in
662 def C2_muxii: ALU32Inst <(outs IntRegs:$Rd),
663                          (ins PredRegs:$Pu, s8Ext:$s8, s8Imm:$S8),
664   "$Rd = mux($Pu, #$s8, #$S8)" ,
665   [(set (i32 IntRegs:$Rd),
666         (i32 (select I1:$Pu, s8ExtPred:$s8, s8ImmPred:$S8)))] > {
667     bits<5> Rd;
668     bits<2> Pu;
669     bits<8> s8;
670     bits<8> S8;
671
672     let IClass = 0b0111;
673
674     let Inst{27-25} = 0b101;
675     let Inst{24-23} = Pu;
676     let Inst{22-16} = S8{7-1};
677     let Inst{13}    = S8{0};
678     let Inst{12-5}  = s8;
679     let Inst{4-0}   = Rd;
680   }
681
682 //===----------------------------------------------------------------------===//
683 // template class for non-predicated alu32_2op instructions
684 // - aslh, asrh, sxtb, sxth, zxth
685 //===----------------------------------------------------------------------===//
686 let hasNewValue = 1, opNewValue = 0 in
687 class T_ALU32_2op <string mnemonic, bits<3> minOp> :
688     ALU32Inst < (outs IntRegs:$Rd), (ins IntRegs:$Rs),
689     "$Rd = "#mnemonic#"($Rs)", [] > {
690   bits<5> Rd;
691   bits<5> Rs;
692
693   let IClass = 0b0111;
694
695   let Inst{27-24} = 0b0000;
696   let Inst{23-21} = minOp;
697   let Inst{13} = 0b0;
698   let Inst{4-0} = Rd;
699   let Inst{20-16} = Rs;
700 }
701
702 //===----------------------------------------------------------------------===//
703 // template class for predicated alu32_2op instructions
704 // - aslh, asrh, sxtb, sxth, zxtb, zxth
705 //===----------------------------------------------------------------------===//
706 let hasSideEffects = 0, validSubTargets = HasV4SubT,
707     hasNewValue = 1, opNewValue = 0 in
708 class T_ALU32_2op_Pred <string mnemonic, bits<3> minOp, bit isPredNot, 
709     bit isPredNew > :
710     ALU32Inst <(outs IntRegs:$Rd), (ins PredRegs:$Pu, IntRegs:$Rs),
711     !if(isPredNot, "if (!$Pu", "if ($Pu")
712     #!if(isPredNew, ".new) ",") ")#"$Rd = "#mnemonic#"($Rs)"> {
713   bits<5> Rd;
714   bits<2> Pu;
715   bits<5> Rs;
716
717   let IClass = 0b0111;
718
719   let Inst{27-24} = 0b0000;
720   let Inst{23-21} = minOp;
721   let Inst{13} = 0b1;
722   let Inst{11} = isPredNot;
723   let Inst{10} = isPredNew;
724   let Inst{4-0} = Rd;
725   let Inst{9-8} = Pu;
726   let Inst{20-16} = Rs;
727 }
728
729 multiclass ALU32_2op_Pred<string mnemonic, bits<3> minOp, bit PredNot> {
730   let isPredicatedFalse = PredNot in {
731     def NAME : T_ALU32_2op_Pred<mnemonic, minOp, PredNot, 0>;
732
733     // Predicate new
734     let isPredicatedNew = 1 in
735     def NAME#new : T_ALU32_2op_Pred<mnemonic, minOp, PredNot, 1>;
736   }
737 }
738
739 multiclass ALU32_2op_base<string mnemonic, bits<3> minOp> {
740   let BaseOpcode = mnemonic in {
741     let isPredicable = 1, hasSideEffects = 0 in
742     def A2_#NAME : T_ALU32_2op<mnemonic, minOp>;
743
744     let validSubTargets = HasV4SubT, isPredicated = 1, hasSideEffects = 0 in {
745       defm A4_p#NAME#t : ALU32_2op_Pred<mnemonic, minOp, 0>;
746       defm A4_p#NAME#f : ALU32_2op_Pred<mnemonic, minOp, 1>;
747     }
748   }
749 }
750
751 let isCodeGenOnly = 0 in {
752 defm aslh : ALU32_2op_base<"aslh", 0b000>, PredNewRel;
753 defm asrh : ALU32_2op_base<"asrh", 0b001>, PredNewRel;
754 defm sxtb : ALU32_2op_base<"sxtb", 0b101>, PredNewRel;
755 defm sxth : ALU32_2op_base<"sxth", 0b111>, PredNewRel;
756 defm zxth : ALU32_2op_base<"zxth", 0b110>, PredNewRel;
757 }
758
759 // Rd=zxtb(Rs): assembler mapped to Rd=and(Rs,#255).
760 // Compiler would want to generate 'zxtb' instead of 'and' becuase 'zxtb' has
761 // predicated forms while 'and' doesn't. Since integrated assembler can't
762 // handle 'mapped' instructions, we need to encode 'zxtb' same as 'and' where
763 // immediate operand is set to '255'.
764
765 let hasNewValue = 1, opNewValue = 0 in
766 class T_ZXTB: ALU32Inst < (outs IntRegs:$Rd), (ins IntRegs:$Rs),
767   "$Rd = zxtb($Rs)", [] > { // Rd = and(Rs,255)
768     bits<5> Rd;
769     bits<5> Rs;
770     bits<10> s10 = 255;
771
772     let IClass = 0b0111;
773
774     let Inst{27-22} = 0b011000;
775     let Inst{4-0} = Rd;
776     let Inst{20-16} = Rs;
777     let Inst{21} = s10{9};
778     let Inst{13-5} = s10{8-0};
779 }
780
781 //Rd=zxtb(Rs): assembler mapped to "Rd=and(Rs,#255)
782 multiclass ZXTB_base <string mnemonic, bits<3> minOp> {
783   let BaseOpcode = mnemonic in {
784     let isPredicable = 1, hasSideEffects = 0 in
785     def A2_#NAME : T_ZXTB;
786
787     let validSubTargets = HasV4SubT, isPredicated = 1, hasSideEffects = 0 in {
788       defm A4_p#NAME#t : ALU32_2op_Pred<mnemonic, minOp, 0>;
789       defm A4_p#NAME#f : ALU32_2op_Pred<mnemonic, minOp, 1>;
790     }
791   }
792 }
793
794 let isCodeGenOnly=0 in
795 defm zxtb : ZXTB_base<"zxtb",0b100>, PredNewRel;
796
797 def: Pat<(shl I32:$src1, (i32 16)),   (A2_aslh I32:$src1)>;
798 def: Pat<(sra I32:$src1, (i32 16)),   (A2_asrh I32:$src1)>;
799 def: Pat<(sext_inreg I32:$src1, i8),  (A2_sxtb I32:$src1)>;
800 def: Pat<(sext_inreg I32:$src1, i16), (A2_sxth I32:$src1)>;
801
802 // Mux.
803 def VMUX_prr64 : ALU64_rr<(outs DoubleRegs:$dst), (ins PredRegs:$src1,
804                                                    DoubleRegs:$src2,
805                                                    DoubleRegs:$src3),
806             "$dst = vmux($src1, $src2, $src3)",
807             []>;
808
809
810 //===----------------------------------------------------------------------===//
811 // ALU32/PERM -
812 //===----------------------------------------------------------------------===//
813
814
815 //===----------------------------------------------------------------------===//
816 // ALU32/PRED +
817 //===----------------------------------------------------------------------===//
818
819 // SDNode for converting immediate C to C-1.
820 def DEC_CONST_SIGNED : SDNodeXForm<imm, [{
821    // Return the byte immediate const-1 as an SDNode.
822    int32_t imm = N->getSExtValue();
823    return XformSToSM1Imm(imm);
824 }]>;
825
826 // SDNode for converting immediate C to C-1.
827 def DEC_CONST_UNSIGNED : SDNodeXForm<imm, [{
828    // Return the byte immediate const-1 as an SDNode.
829    uint32_t imm = N->getZExtValue();
830    return XformUToUM1Imm(imm);
831 }]>;
832
833 def CTLZ64_rr : SInst<(outs IntRegs:$dst), (ins DoubleRegs:$src1),
834     "$dst = cl0($src1)",
835     [(set (i32 IntRegs:$dst), (i32 (trunc (ctlz (i64 DoubleRegs:$src1)))))]>;
836
837 def CTTZ64_rr : SInst<(outs IntRegs:$dst), (ins DoubleRegs:$src1),
838     "$dst = ct0($src1)",
839     [(set (i32 IntRegs:$dst), (i32 (trunc (cttz (i64 DoubleRegs:$src1)))))]>;
840
841 //===----------------------------------------------------------------------===//
842 // ALU32/PRED -
843 //===----------------------------------------------------------------------===//
844
845
846 //===----------------------------------------------------------------------===//
847 // ALU64/ALU +
848 //===----------------------------------------------------------------------===//// Add.
849 //===----------------------------------------------------------------------===//
850 // Template Class
851 // Add/Subtract halfword
852 // Rd=add(Rt.L,Rs.[HL])[:sat]
853 // Rd=sub(Rt.L,Rs.[HL])[:sat]
854 // Rd=add(Rt.[LH],Rs.[HL])[:sat][:<16]
855 // Rd=sub(Rt.[LH],Rs.[HL])[:sat][:<16]
856 //===----------------------------------------------------------------------===//
857
858 let  hasNewValue = 1, opNewValue = 0 in
859 class T_XTYPE_ADD_SUB <bits<2> LHbits, bit isSat, bit hasShift, bit isSub>
860   : ALU64Inst <(outs IntRegs:$Rd), (ins IntRegs:$Rt, IntRegs:$Rs),
861   "$Rd = "#!if(isSub,"sub","add")#"($Rt."
862           #!if(hasShift, !if(LHbits{1},"h","l"),"l") #", $Rs."
863           #!if(hasShift, !if(LHbits{0},"h)","l)"), !if(LHbits{1},"h)","l)"))
864           #!if(isSat,":sat","")
865           #!if(hasShift,":<<16",""), [], "", ALU64_tc_1_SLOT23> {
866     bits<5> Rd;
867     bits<5> Rt;
868     bits<5> Rs;
869     let IClass = 0b1101;
870
871     let Inst{27-23} = 0b01010;
872     let Inst{22} = hasShift;
873     let Inst{21} = isSub;
874     let Inst{7} = isSat;
875     let Inst{6-5} = LHbits;
876     let Inst{4-0} = Rd;
877     let Inst{12-8} = Rt;
878     let Inst{20-16} = Rs;
879   }
880
881 //Rd=sub(Rt.L,Rs.[LH])
882 let isCodeGenOnly = 0 in {
883 def A2_subh_l16_ll : T_XTYPE_ADD_SUB <0b00, 0, 0, 1>;
884 def A2_subh_l16_hl : T_XTYPE_ADD_SUB <0b10, 0, 0, 1>;
885 }
886
887 let isCodeGenOnly = 0 in {
888 //Rd=add(Rt.L,Rs.[LH])
889 def A2_addh_l16_ll : T_XTYPE_ADD_SUB <0b00, 0, 0, 0>;
890 def A2_addh_l16_hl : T_XTYPE_ADD_SUB <0b10, 0, 0, 0>;
891 }
892
893 let Itinerary = ALU64_tc_2_SLOT23, Defs = [USR_OVF], isCodeGenOnly = 0 in {
894   //Rd=sub(Rt.L,Rs.[LH]):sat
895   def A2_subh_l16_sat_ll : T_XTYPE_ADD_SUB <0b00, 1, 0, 1>;
896   def A2_subh_l16_sat_hl : T_XTYPE_ADD_SUB <0b10, 1, 0, 1>;
897
898   //Rd=add(Rt.L,Rs.[LH]):sat
899   def A2_addh_l16_sat_ll : T_XTYPE_ADD_SUB <0b00, 1, 0, 0>;
900   def A2_addh_l16_sat_hl : T_XTYPE_ADD_SUB <0b10, 1, 0, 0>;
901 }
902
903 //Rd=sub(Rt.[LH],Rs.[LH]):<<16
904 let isCodeGenOnly = 0 in {
905 def A2_subh_h16_ll : T_XTYPE_ADD_SUB <0b00, 0, 1, 1>;
906 def A2_subh_h16_lh : T_XTYPE_ADD_SUB <0b01, 0, 1, 1>;
907 def A2_subh_h16_hl : T_XTYPE_ADD_SUB <0b10, 0, 1, 1>;
908 def A2_subh_h16_hh : T_XTYPE_ADD_SUB <0b11, 0, 1, 1>;
909 }
910
911 //Rd=add(Rt.[LH],Rs.[LH]):<<16
912 let isCodeGenOnly = 0 in {
913 def A2_addh_h16_ll : T_XTYPE_ADD_SUB <0b00, 0, 1, 0>;
914 def A2_addh_h16_lh : T_XTYPE_ADD_SUB <0b01, 0, 1, 0>;
915 def A2_addh_h16_hl : T_XTYPE_ADD_SUB <0b10, 0, 1, 0>;
916 def A2_addh_h16_hh : T_XTYPE_ADD_SUB <0b11, 0, 1, 0>;
917 }
918
919 let Itinerary = ALU64_tc_2_SLOT23, Defs = [USR_OVF], isCodeGenOnly = 0 in {
920   //Rd=sub(Rt.[LH],Rs.[LH]):sat:<<16
921   def A2_subh_h16_sat_ll : T_XTYPE_ADD_SUB <0b00, 1, 1, 1>;
922   def A2_subh_h16_sat_lh : T_XTYPE_ADD_SUB <0b01, 1, 1, 1>;
923   def A2_subh_h16_sat_hl : T_XTYPE_ADD_SUB <0b10, 1, 1, 1>;
924   def A2_subh_h16_sat_hh : T_XTYPE_ADD_SUB <0b11, 1, 1, 1>;
925
926   //Rd=add(Rt.[LH],Rs.[LH]):sat:<<16
927   def A2_addh_h16_sat_ll : T_XTYPE_ADD_SUB <0b00, 1, 1, 0>;
928   def A2_addh_h16_sat_lh : T_XTYPE_ADD_SUB <0b01, 1, 1, 0>;
929   def A2_addh_h16_sat_hl : T_XTYPE_ADD_SUB <0b10, 1, 1, 0>;
930   def A2_addh_h16_sat_hh : T_XTYPE_ADD_SUB <0b11, 1, 1, 0>;
931 }
932
933 // Add halfword.
934 def: Pat<(sext_inreg (add I32:$src1, I32:$src2), i16),
935          (A2_addh_l16_ll I32:$src1, I32:$src2)>;
936
937 def: Pat<(sra (add (shl I32:$src1, (i32 16)), I32:$src2), (i32 16)),
938          (A2_addh_l16_hl I32:$src1, I32:$src2)>;
939
940 def: Pat<(shl (add I32:$src1, I32:$src2), (i32 16)),
941          (A2_addh_h16_ll I32:$src1, I32:$src2)>;
942
943 // Subtract halfword.
944 def: Pat<(sext_inreg (sub I32:$src1, I32:$src2), i16),
945          (A2_subh_l16_ll I32:$src1, I32:$src2)>;
946
947 def: Pat<(shl (sub I32:$src1, I32:$src2), (i32 16)),
948          (A2_subh_h16_ll I32:$src1, I32:$src2)>;
949
950 let hasSideEffects = 0, hasNewValue = 1, isCodeGenOnly = 0 in
951 def S2_parityp: ALU64Inst<(outs IntRegs:$Rd),
952       (ins DoubleRegs:$Rs, DoubleRegs:$Rt),
953       "$Rd = parity($Rs, $Rt)", [], "", ALU64_tc_2_SLOT23> {
954   bits<5> Rd;
955   bits<5> Rs;
956   bits<5> Rt;
957
958   let IClass = 0b1101;
959   let Inst{27-24} = 0b0000;
960   let Inst{20-16} = Rs;
961   let Inst{12-8} = Rt;
962   let Inst{4-0} = Rd;
963 }
964
965 let hasNewValue = 1, opNewValue = 0, hasSideEffects = 0 in
966 class T_XTYPE_MIN_MAX < bit isMax, bit isUnsigned >
967   : ALU64Inst < (outs IntRegs:$Rd), (ins IntRegs:$Rt, IntRegs:$Rs),
968   "$Rd = "#!if(isMax,"max","min")#!if(isUnsigned,"u","")
969           #"($Rt, $Rs)", [], "", ALU64_tc_2_SLOT23> {
970     bits<5> Rd;
971     bits<5> Rt;
972     bits<5> Rs;
973
974     let IClass = 0b1101;
975
976     let Inst{27-23} = 0b01011;
977     let Inst{22-21} = !if(isMax, 0b10, 0b01);
978     let Inst{7} = isUnsigned;
979     let Inst{4-0} = Rd;
980     let Inst{12-8} = !if(isMax, Rs, Rt);
981     let Inst{20-16} = !if(isMax, Rt, Rs);
982   }
983
984 let isCodeGenOnly = 0 in {
985 def A2_min  : T_XTYPE_MIN_MAX < 0, 0 >;
986 def A2_minu : T_XTYPE_MIN_MAX < 0, 1 >;
987 def A2_max  : T_XTYPE_MIN_MAX < 1, 0 >;
988 def A2_maxu : T_XTYPE_MIN_MAX < 1, 1 >;
989 }
990
991 // Here, depending on  the operand being selected, we'll either generate a
992 // min or max instruction.
993 // Ex:
994 // (a>b)?a:b --> max(a,b) => Here check performed is '>' and the value selected
995 // is the larger of two. So, the corresponding HexagonInst is passed in 'Inst'.
996 // (a>b)?b:a --> min(a,b) => Here check performed is '>' but the smaller value
997 // is selected and the corresponding HexagonInst is passed in 'SwapInst'.
998
999 multiclass T_MinMax_pats <PatFrag Op, RegisterClass RC, ValueType VT,
1000                           InstHexagon Inst, InstHexagon SwapInst> {
1001   def: Pat<(select (i1 (Op (VT RC:$src1), (VT RC:$src2))),
1002                    (VT RC:$src1), (VT RC:$src2)),
1003            (Inst RC:$src1, RC:$src2)>;
1004   def: Pat<(select (i1 (Op (VT RC:$src1), (VT RC:$src2))),
1005                    (VT RC:$src2), (VT RC:$src1)),
1006            (SwapInst RC:$src1, RC:$src2)>;
1007 }
1008
1009
1010 multiclass MinMax_pats <PatFrag Op, InstHexagon Inst, InstHexagon SwapInst> {
1011   defm: T_MinMax_pats<Op, IntRegs, i32, Inst, SwapInst>;
1012
1013   def: Pat<(sext_inreg (i32 (select (i1 (Op (i32 PositiveHalfWord:$src1),
1014                                             (i32 PositiveHalfWord:$src2))),
1015                                     (i32 PositiveHalfWord:$src1),
1016                                     (i32 PositiveHalfWord:$src2))), i16),
1017            (Inst IntRegs:$src1, IntRegs:$src2)>;
1018
1019   def: Pat<(sext_inreg (i32 (select (i1 (Op (i32 PositiveHalfWord:$src1),
1020                                             (i32 PositiveHalfWord:$src2))),
1021                                     (i32 PositiveHalfWord:$src2),
1022                                     (i32 PositiveHalfWord:$src1))), i16),
1023            (SwapInst IntRegs:$src1, IntRegs:$src2)>;
1024 }
1025
1026 let AddedComplexity = 200 in {
1027   defm: MinMax_pats<setge,  A2_max,  A2_min>;
1028   defm: MinMax_pats<setgt,  A2_max,  A2_min>;
1029   defm: MinMax_pats<setle,  A2_min,  A2_max>;
1030   defm: MinMax_pats<setlt,  A2_min,  A2_max>;
1031   defm: MinMax_pats<setuge, A2_maxu, A2_minu>;
1032   defm: MinMax_pats<setugt, A2_maxu, A2_minu>;
1033   defm: MinMax_pats<setule, A2_minu, A2_maxu>;
1034   defm: MinMax_pats<setult, A2_minu, A2_maxu>;
1035 }
1036
1037 class T_cmp64_rr<string mnemonic, bits<3> MinOp, bit IsComm>
1038   : ALU64_rr<(outs PredRegs:$Pd), (ins DoubleRegs:$Rs, DoubleRegs:$Rt),
1039              "$Pd = "#mnemonic#"($Rs, $Rt)", [], "", ALU64_tc_2early_SLOT23> {
1040   let isCompare = 1;
1041   let isCommutable = IsComm;
1042   let hasSideEffects = 0;
1043
1044   bits<2> Pd;
1045   bits<5> Rs;
1046   bits<5> Rt;
1047
1048   let IClass = 0b1101;
1049   let Inst{27-21} = 0b0010100;
1050   let Inst{20-16} = Rs;
1051   let Inst{12-8} = Rt;
1052   let Inst{7-5} = MinOp;
1053   let Inst{1-0} = Pd;
1054 }
1055
1056 let isCodeGenOnly = 0 in {
1057 def C2_cmpeqp  : T_cmp64_rr<"cmp.eq",  0b000, 1>;
1058 def C2_cmpgtp  : T_cmp64_rr<"cmp.gt",  0b010, 0>;
1059 def C2_cmpgtup : T_cmp64_rr<"cmp.gtu", 0b100, 0>;
1060 }
1061
1062 class T_cmp64_rr_pat<InstHexagon MI, PatFrag CmpOp>
1063   : Pat<(i1 (CmpOp (i64 DoubleRegs:$Rs), (i64 DoubleRegs:$Rt))),
1064         (i1 (MI DoubleRegs:$Rs, DoubleRegs:$Rt))>;
1065
1066 def: T_cmp64_rr_pat<C2_cmpeqp,  seteq>;
1067 def: T_cmp64_rr_pat<C2_cmpgtp,  setgt>;
1068 def: T_cmp64_rr_pat<C2_cmpgtup, setugt>;
1069 def: T_cmp64_rr_pat<C2_cmpgtp,  RevCmp<setlt>>;
1070 def: T_cmp64_rr_pat<C2_cmpgtup, RevCmp<setult>>;
1071
1072 class T_ALU64_rr<string mnemonic, string suffix, bits<4> RegType,
1073                  bits<3> MajOp, bits<3> MinOp, bit OpsRev, bit IsComm,
1074                  string Op2Pfx>
1075   : ALU64_rr<(outs DoubleRegs:$Rd), (ins DoubleRegs:$Rs, DoubleRegs:$Rt),
1076              "$Rd = " #mnemonic# "($Rs, " #Op2Pfx# "$Rt)" #suffix, [],
1077              "", ALU64_tc_1_SLOT23> {
1078   let hasSideEffects = 0;
1079   let isCommutable = IsComm;
1080
1081   bits<5> Rs;
1082   bits<5> Rt;
1083   bits<5> Rd;
1084
1085   let IClass = 0b1101;
1086   let Inst{27-24} = RegType;
1087   let Inst{23-21} = MajOp;
1088   let Inst{20-16} = !if (OpsRev,Rt,Rs);
1089   let Inst{12-8} = !if (OpsRev,Rs,Rt);
1090   let Inst{7-5} = MinOp;
1091   let Inst{4-0} = Rd;
1092 }
1093
1094 class T_ALU64_arith<string mnemonic, bits<3> MajOp, bits<3> MinOp, bit IsSat,
1095                     bit OpsRev, bit IsComm>
1096   : T_ALU64_rr<mnemonic, !if(IsSat,":sat",""), 0b0011, MajOp, MinOp, OpsRev,
1097                IsComm, "">;
1098
1099 let isCodeGenOnly = 0 in {
1100 def A2_addp : T_ALU64_arith<"add", 0b000, 0b111, 0, 0, 1>;
1101 def A2_subp : T_ALU64_arith<"sub", 0b001, 0b111, 0, 1, 0>;
1102 }
1103
1104 def: Pat<(i64 (add I64:$Rs, I64:$Rt)), (A2_addp I64:$Rs, I64:$Rt)>;
1105 def: Pat<(i64 (sub I64:$Rs, I64:$Rt)), (A2_subp I64:$Rs, I64:$Rt)>;
1106
1107 class T_ALU64_logical<string mnemonic, bits<3> MinOp, bit OpsRev, bit IsComm,
1108                       bit IsNeg>
1109   : T_ALU64_rr<mnemonic, "", 0b0011, 0b111, MinOp, OpsRev, IsComm,
1110                !if(IsNeg,"~","")>;
1111
1112 let isCodeGenOnly = 0 in {
1113 def A2_andp : T_ALU64_logical<"and", 0b000, 0, 1, 0>;
1114 def A2_orp  : T_ALU64_logical<"or",  0b010, 0, 1, 0>;
1115 def A2_xorp : T_ALU64_logical<"xor", 0b100, 0, 1, 0>;
1116 }
1117
1118 def: Pat<(i64 (and I64:$Rs, I64:$Rt)), (A2_andp I64:$Rs, I64:$Rt)>;
1119 def: Pat<(i64 (or  I64:$Rs, I64:$Rt)), (A2_orp  I64:$Rs, I64:$Rt)>;
1120 def: Pat<(i64 (xor I64:$Rs, I64:$Rt)), (A2_xorp I64:$Rs, I64:$Rt)>;
1121
1122 //===----------------------------------------------------------------------===//
1123 // ALU64/ALU -
1124 //===----------------------------------------------------------------------===//
1125
1126 //===----------------------------------------------------------------------===//
1127 // ALU64/BIT +
1128 //===----------------------------------------------------------------------===//
1129 //
1130 //===----------------------------------------------------------------------===//
1131 // ALU64/BIT -
1132 //===----------------------------------------------------------------------===//
1133
1134 //===----------------------------------------------------------------------===//
1135 // ALU64/PERM +
1136 //===----------------------------------------------------------------------===//
1137 //
1138 //===----------------------------------------------------------------------===//
1139 // ALU64/PERM -
1140 //===----------------------------------------------------------------------===//
1141
1142 //===----------------------------------------------------------------------===//
1143 // CR +
1144 //===----------------------------------------------------------------------===//
1145 // Logical reductions on predicates.
1146
1147 // Looping instructions.
1148
1149 // Pipelined looping instructions.
1150
1151 // Logical operations on predicates.
1152 let hasSideEffects = 0 in
1153 class T_LOGICAL_1OP<string MnOp, bits<2> OpBits>
1154     : CRInst<(outs PredRegs:$Pd), (ins PredRegs:$Ps),
1155              "$Pd = " # MnOp # "($Ps)", [], "", CR_tc_2early_SLOT23> {
1156   bits<2> Pd;
1157   bits<2> Ps;
1158
1159   let IClass = 0b0110;
1160   let Inst{27-23} = 0b10111;
1161   let Inst{22-21} = OpBits;
1162   let Inst{20} = 0b0;
1163   let Inst{17-16} = Ps;
1164   let Inst{13} = 0b0;
1165   let Inst{1-0} = Pd;
1166 }
1167
1168 let isCodeGenOnly = 0 in {
1169 def C2_any8 : T_LOGICAL_1OP<"any8", 0b00>;
1170 def C2_all8 : T_LOGICAL_1OP<"all8", 0b01>;
1171 def C2_not  : T_LOGICAL_1OP<"not",  0b10>;
1172 }
1173
1174 def: Pat<(i1 (not (i1 PredRegs:$Ps))),
1175          (C2_not PredRegs:$Ps)>;
1176
1177 let hasSideEffects = 0 in
1178 class T_LOGICAL_2OP<string MnOp, bits<3> OpBits, bit IsNeg, bit Rev>
1179     : CRInst<(outs PredRegs:$Pd), (ins PredRegs:$Ps, PredRegs:$Pt),
1180              "$Pd = " # MnOp # "($Ps, " # !if (IsNeg,"!","") # "$Pt)",
1181              [], "", CR_tc_2early_SLOT23> {
1182   bits<2> Pd;
1183   bits<2> Ps;
1184   bits<2> Pt;
1185
1186   let IClass = 0b0110;
1187   let Inst{27-24} = 0b1011;
1188   let Inst{23-21} = OpBits;
1189   let Inst{20} = 0b0;
1190   let Inst{17-16} = !if(Rev,Pt,Ps);  // Rs and Rt are reversed for some
1191   let Inst{13} = 0b0;                // instructions.
1192   let Inst{9-8} = !if(Rev,Ps,Pt);
1193   let Inst{1-0} = Pd;
1194 }
1195
1196 let isCodeGenOnly = 0 in {
1197 def C2_and  : T_LOGICAL_2OP<"and", 0b000, 0, 1>;
1198 def C2_or   : T_LOGICAL_2OP<"or",  0b001, 0, 1>;
1199 def C2_xor  : T_LOGICAL_2OP<"xor", 0b010, 0, 0>;
1200 def C2_andn : T_LOGICAL_2OP<"and", 0b011, 1, 1>;
1201 def C2_orn  : T_LOGICAL_2OP<"or",  0b111, 1, 1>;
1202 }
1203
1204 def: Pat<(i1 (and I1:$Ps, I1:$Pt)),       (C2_and  I1:$Ps, I1:$Pt)>;
1205 def: Pat<(i1 (or  I1:$Ps, I1:$Pt)),       (C2_or   I1:$Ps, I1:$Pt)>;
1206 def: Pat<(i1 (xor I1:$Ps, I1:$Pt)),       (C2_xor  I1:$Ps, I1:$Pt)>;
1207 def: Pat<(i1 (and I1:$Ps, (not I1:$Pt))), (C2_andn I1:$Ps, I1:$Pt)>;
1208 def: Pat<(i1 (or  I1:$Ps, (not I1:$Pt))), (C2_orn  I1:$Ps, I1:$Pt)>;
1209
1210 let hasSideEffects = 0, hasNewValue = 1, isCodeGenOnly = 0 in
1211 def C2_vitpack : SInst<(outs IntRegs:$Rd), (ins PredRegs:$Ps, PredRegs:$Pt),
1212       "$Rd = vitpack($Ps, $Pt)", [], "", S_2op_tc_1_SLOT23> {
1213   bits<5> Rd;
1214   bits<2> Ps;
1215   bits<2> Pt;
1216
1217   let IClass = 0b1000;
1218   let Inst{27-24} = 0b1001;
1219   let Inst{22-21} = 0b00;
1220   let Inst{17-16} = Ps;
1221   let Inst{9-8} = Pt;
1222   let Inst{4-0} = Rd;
1223 }
1224
1225 let hasSideEffects = 0, isCodeGenOnly = 0 in
1226 def C2_mask : SInst<(outs DoubleRegs:$Rd), (ins PredRegs:$Pt),
1227       "$Rd = mask($Pt)", [], "", S_2op_tc_1_SLOT23> {
1228   bits<5> Rd;
1229   bits<2> Pt;
1230
1231   let IClass = 0b1000;
1232   let Inst{27-24} = 0b0110;
1233   let Inst{9-8} = Pt;
1234   let Inst{4-0} = Rd;
1235 }
1236
1237 def VALIGN_rrp : SInst<(outs DoubleRegs:$dst), (ins DoubleRegs:$src1,
1238                                                     DoubleRegs:$src2,
1239                                                     PredRegs:$src3),
1240              "$dst = valignb($src1, $src2, $src3)",
1241              []>;
1242
1243 def VSPLICE_rrp : SInst<(outs DoubleRegs:$dst), (ins DoubleRegs:$src1,
1244                                                      DoubleRegs:$src2,
1245                                                      PredRegs:$src3),
1246              "$dst = vspliceb($src1, $src2, $src3)",
1247              []>;
1248
1249 // User control register transfer.
1250 //===----------------------------------------------------------------------===//
1251 // CR -
1252 //===----------------------------------------------------------------------===//
1253
1254 //===----------------------------------------------------------------------===//
1255 // JR +
1256 //===----------------------------------------------------------------------===//
1257
1258 def retflag : SDNode<"HexagonISD::RET_FLAG", SDTNone,
1259                                [SDNPHasChain, SDNPOptInGlue, SDNPVariadic]>;
1260 def eh_return: SDNode<"HexagonISD::EH_RETURN", SDTNone, [SDNPHasChain]>;
1261
1262 def SDHexagonBR_JT: SDTypeProfile<0, 1, [SDTCisVT<0, i32>]>;
1263 def HexagonBR_JT: SDNode<"HexagonISD::BR_JT", SDHexagonBR_JT, [SDNPHasChain]>;
1264
1265 class CondStr<string CReg, bit True, bit New> {
1266   string S = "if (" # !if(True,"","!") # CReg # !if(New,".new","") # ") ";
1267 }
1268 class JumpOpcStr<string Mnemonic, bit New, bit Taken> {
1269   string S = Mnemonic # !if(New, !if(Taken,":t",":nt"), "");
1270 }
1271
1272 let isBranch = 1, isBarrier = 1, Defs = [PC], hasSideEffects = 0,
1273     isPredicable = 1,
1274     isExtendable = 1, opExtendable = 0, isExtentSigned = 1,
1275     opExtentBits = 24, opExtentAlign = 2, InputType = "imm" in
1276 class T_JMP<string ExtStr>
1277   : JInst<(outs), (ins brtarget:$dst),
1278       "jump " # ExtStr # "$dst",
1279       [], "", J_tc_2early_SLOT23> {
1280     bits<24> dst;
1281     let IClass = 0b0101;
1282
1283     let Inst{27-25} = 0b100;
1284     let Inst{24-16} = dst{23-15};
1285     let Inst{13-1} = dst{14-2};
1286 }
1287
1288 let isBranch = 1, Defs = [PC], hasSideEffects = 0, isPredicated = 1,
1289     isExtendable = 1, opExtendable = 1, isExtentSigned = 1,
1290     opExtentBits = 17, opExtentAlign = 2, InputType = "imm" in
1291 class T_JMP_c<bit PredNot, bit isPredNew, bit isTak, string ExtStr>
1292   : JInst<(outs), (ins PredRegs:$src, brtarget:$dst),
1293       CondStr<"$src", !if(PredNot,0,1), isPredNew>.S #
1294         JumpOpcStr<"jump", isPredNew, isTak>.S # " " #
1295         ExtStr # "$dst",
1296       [], "", J_tc_2early_SLOT23>, ImmRegRel {
1297     let isTaken = isTak;
1298     let isPredicatedFalse = PredNot;
1299     let isPredicatedNew = isPredNew;
1300     bits<2> src;
1301     bits<17> dst;
1302
1303     let IClass = 0b0101;
1304
1305     let Inst{27-24} = 0b1100;
1306     let Inst{21} = PredNot;
1307     let Inst{12} = !if(isPredNew, isTak, zero);
1308     let Inst{11} = isPredNew;
1309     let Inst{9-8} = src;
1310     let Inst{23-22} = dst{16-15};
1311     let Inst{20-16} = dst{14-10};
1312     let Inst{13} = dst{9};
1313     let Inst{7-1} = dst{8-2};
1314   }
1315
1316 multiclass JMP_Pred<bit PredNot, string ExtStr> {
1317   def NAME : T_JMP_c<PredNot, 0, 0, ExtStr>;
1318   // Predicate new
1319   def NAME#newpt : T_JMP_c<PredNot, 1, 1, ExtStr>; // taken
1320   def NAME#new   : T_JMP_c<PredNot, 1, 0, ExtStr>; // not taken
1321 }
1322
1323 multiclass JMP_base<string BaseOp, string ExtStr> {
1324   let BaseOpcode = BaseOp in {
1325     def NAME : T_JMP<ExtStr>;
1326     defm t : JMP_Pred<0, ExtStr>;
1327     defm f : JMP_Pred<1, ExtStr>;
1328   }
1329 }
1330
1331 // Jumps to address stored in a register, JUMPR_MISC
1332 // if ([[!]P[.new]]) jumpr[:t/nt] Rs
1333 let isBranch = 1, isIndirectBranch = 1, isBarrier = 1, Defs = [PC],
1334     isPredicable = 1, hasSideEffects = 0, InputType = "reg" in
1335 class T_JMPr
1336   : JRInst<(outs), (ins IntRegs:$dst),
1337       "jumpr $dst", [], "", J_tc_2early_SLOT2> {
1338     bits<5> dst;
1339
1340     let IClass = 0b0101;
1341     let Inst{27-21} = 0b0010100;
1342     let Inst{20-16} = dst;
1343 }
1344
1345 let isBranch = 1, isIndirectBranch = 1, Defs = [PC], isPredicated = 1,
1346     hasSideEffects = 0, InputType = "reg" in
1347 class T_JMPr_c <bit PredNot, bit isPredNew, bit isTak>
1348   : JRInst <(outs), (ins PredRegs:$src, IntRegs:$dst),
1349       CondStr<"$src", !if(PredNot,0,1), isPredNew>.S #
1350         JumpOpcStr<"jumpr", isPredNew, isTak>.S # " $dst", [],
1351       "", J_tc_2early_SLOT2> {
1352
1353     let isTaken = isTak;
1354     let isPredicatedFalse = PredNot;
1355     let isPredicatedNew = isPredNew;
1356     bits<2> src;
1357     bits<5> dst;
1358
1359     let IClass = 0b0101;
1360
1361     let Inst{27-22} = 0b001101;
1362     let Inst{21} = PredNot;
1363     let Inst{20-16} = dst;
1364     let Inst{12} = !if(isPredNew, isTak, zero);
1365     let Inst{11} = isPredNew;
1366     let Inst{9-8} = src;
1367 }
1368
1369 multiclass JMPR_Pred<bit PredNot> {
1370   def NAME: T_JMPr_c<PredNot, 0, 0>;
1371   // Predicate new
1372   def NAME#newpt  : T_JMPr_c<PredNot, 1, 1>; // taken
1373   def NAME#new    : T_JMPr_c<PredNot, 1, 0>; // not taken
1374 }
1375
1376 multiclass JMPR_base<string BaseOp> {
1377   let BaseOpcode = BaseOp in {
1378     def NAME : T_JMPr;
1379     defm t : JMPR_Pred<0>;
1380     defm f : JMPR_Pred<1>;
1381   }
1382 }
1383
1384 let isCall = 1, hasSideEffects = 1 in
1385 class JUMPR_MISC_CALLR<bit isPred, bit isPredNot,
1386                dag InputDag = (ins IntRegs:$Rs)>
1387   : JRInst<(outs), InputDag,
1388       !if(isPred, !if(isPredNot, "if (!$Pu) callr $Rs",
1389                                  "if ($Pu) callr $Rs"),
1390                                  "callr $Rs"),
1391       [], "", J_tc_2early_SLOT2> {
1392     bits<5> Rs;
1393     bits<2> Pu;
1394     let isPredicated = isPred;
1395     let isPredicatedFalse = isPredNot;
1396
1397     let IClass = 0b0101;
1398     let Inst{27-25} = 0b000;
1399     let Inst{24-23} = !if (isPred, 0b10, 0b01);
1400     let Inst{22} = 0;
1401     let Inst{21} = isPredNot;
1402     let Inst{9-8} = !if (isPred, Pu, 0b00);
1403     let Inst{20-16} = Rs;
1404
1405   }
1406
1407 let Defs = VolatileV3.Regs, isCodeGenOnly = 0 in {
1408   def J2_callrt : JUMPR_MISC_CALLR<1, 0, (ins PredRegs:$Pu, IntRegs:$Rs)>;
1409   def J2_callrf : JUMPR_MISC_CALLR<1, 1, (ins PredRegs:$Pu, IntRegs:$Rs)>;
1410 }
1411
1412 let isTerminator = 1, hasSideEffects = 0, isCodeGenOnly = 0 in {
1413   defm J2_jump : JMP_base<"JMP", "">, PredNewRel;
1414
1415   // Deal with explicit assembly
1416   //  - never extened a jump #,  always extend a jump ##
1417   let isAsmParserOnly = 1 in {
1418     defm J2_jump_ext   : JMP_base<"JMP", "##">;
1419     defm J2_jump_noext : JMP_base<"JMP", "#">;
1420   }
1421
1422   defm J2_jumpr : JMPR_base<"JMPr">, PredNewRel;
1423
1424   let isReturn = 1, isCodeGenOnly = 1 in
1425   defm JMPret : JMPR_base<"JMPret">, PredNewRel;
1426 }
1427
1428 def: Pat<(br bb:$dst),
1429          (J2_jump brtarget:$dst)>;
1430 def: Pat<(retflag),
1431          (JMPret (i32 R31))>;
1432 def: Pat<(brcond (i1 PredRegs:$src1), bb:$offset),
1433          (J2_jumpt PredRegs:$src1, bb:$offset)>;
1434
1435 // A return through builtin_eh_return.
1436 let isReturn = 1, isTerminator = 1, isBarrier = 1, hasSideEffects = 0,
1437     isCodeGenOnly = 1, Defs = [PC], Uses = [R28], isPredicable = 0 in
1438 def EH_RETURN_JMPR : T_JMPr;
1439
1440 def: Pat<(eh_return),
1441          (EH_RETURN_JMPR (i32 R31))>;
1442 def: Pat<(HexagonBR_JT (i32 IntRegs:$dst)),
1443          (J2_jumpr IntRegs:$dst)>;
1444 def: Pat<(brind (i32 IntRegs:$dst)),
1445          (J2_jumpr IntRegs:$dst)>;
1446
1447 //===----------------------------------------------------------------------===//
1448 // JR -
1449 //===----------------------------------------------------------------------===//
1450
1451 //===----------------------------------------------------------------------===//
1452 // LD +
1453 //===----------------------------------------------------------------------===//
1454 let isExtendable = 1, opExtendable = 2, isExtentSigned = 1, AddedComplexity = 20 in
1455 class T_load_io <string mnemonic, RegisterClass RC, bits<4> MajOp,
1456                  Operand ImmOp>
1457   : LDInst<(outs RC:$dst), (ins IntRegs:$src1, ImmOp:$offset),
1458   "$dst = "#mnemonic#"($src1 + #$offset)", []>, AddrModeRel {
1459     bits<4> name;
1460     bits<5> dst;
1461     bits<5> src1;
1462     bits<14> offset;
1463     bits<11> offsetBits;
1464
1465     string ImmOpStr = !cast<string>(ImmOp);
1466     let offsetBits = !if (!eq(ImmOpStr, "s11_3Ext"), offset{13-3},
1467                      !if (!eq(ImmOpStr, "s11_2Ext"), offset{12-2},
1468                      !if (!eq(ImmOpStr, "s11_1Ext"), offset{11-1},
1469                                       /* s11_0Ext */ offset{10-0})));
1470     let opExtentBits = !if (!eq(ImmOpStr, "s11_3Ext"), 14,
1471                        !if (!eq(ImmOpStr, "s11_2Ext"), 13,
1472                        !if (!eq(ImmOpStr, "s11_1Ext"), 12,
1473                                         /* s11_0Ext */ 11)));
1474     let hasNewValue = !if (!eq(ImmOpStr, "s11_3Ext"), 0, 1);
1475
1476     let IClass = 0b1001;
1477
1478     let Inst{27}    = 0b0;
1479     let Inst{26-25} = offsetBits{10-9};
1480     let Inst{24-21} = MajOp;
1481     let Inst{20-16} = src1;
1482     let Inst{13-5}  = offsetBits{8-0};
1483     let Inst{4-0}   = dst;
1484   }
1485
1486 let opExtendable = 3, isExtentSigned = 0, isPredicated = 1 in
1487 class T_pload_io <string mnemonic, RegisterClass RC, bits<4>MajOp,
1488                   Operand ImmOp, bit isNot, bit isPredNew>
1489   : LDInst<(outs RC:$dst),
1490            (ins PredRegs:$src1, IntRegs:$src2, ImmOp:$offset),
1491   "if ("#!if(isNot, "!$src1", "$src1")
1492        #!if(isPredNew, ".new", "")
1493        #") $dst = "#mnemonic#"($src2 + #$offset)",
1494   [],"", V2LDST_tc_ld_SLOT01> , AddrModeRel {
1495     bits<5> dst;
1496     bits<2> src1;
1497     bits<5> src2;
1498     bits<9> offset;
1499     bits<6> offsetBits;
1500     string ImmOpStr = !cast<string>(ImmOp);
1501
1502     let offsetBits = !if (!eq(ImmOpStr, "u6_3Ext"), offset{8-3},
1503                      !if (!eq(ImmOpStr, "u6_2Ext"), offset{7-2},
1504                      !if (!eq(ImmOpStr, "u6_1Ext"), offset{6-1},
1505                                       /* u6_0Ext */ offset{5-0})));
1506     let opExtentBits = !if (!eq(ImmOpStr, "u6_3Ext"), 9,
1507                        !if (!eq(ImmOpStr, "u6_2Ext"), 8,
1508                        !if (!eq(ImmOpStr, "u6_1Ext"), 7,
1509                                         /* u6_0Ext */ 6)));
1510     let hasNewValue = !if (!eq(ImmOpStr, "u6_3Ext"), 0, 1);
1511     let isPredicatedNew = isPredNew;
1512     let isPredicatedFalse = isNot;
1513
1514     let IClass = 0b0100;
1515
1516     let Inst{27}    = 0b0;
1517     let Inst{27}    = 0b0;
1518     let Inst{26}    = isNot;
1519     let Inst{25}    = isPredNew;
1520     let Inst{24-21} = MajOp;
1521     let Inst{20-16} = src2;
1522     let Inst{13}    = 0b0;
1523     let Inst{12-11} = src1;
1524     let Inst{10-5}  = offsetBits;
1525     let Inst{4-0}   = dst;
1526   }
1527
1528 let isExtendable = 1, hasSideEffects = 0, addrMode = BaseImmOffset in
1529 multiclass LD_Idxd<string mnemonic, string CextOp, RegisterClass RC,
1530                    Operand ImmOp, Operand predImmOp, bits<4>MajOp> {
1531   let CextOpcode = CextOp, BaseOpcode = CextOp#_indexed in {
1532     let isPredicable = 1 in
1533     def L2_#NAME#_io : T_load_io <mnemonic, RC, MajOp, ImmOp>;
1534
1535     // Predicated
1536     def L2_p#NAME#t_io : T_pload_io <mnemonic, RC, MajOp, predImmOp, 0, 0>;
1537     def L2_p#NAME#f_io : T_pload_io <mnemonic, RC, MajOp, predImmOp, 1, 0>;
1538
1539     // Predicated new
1540     def L2_p#NAME#tnew_io : T_pload_io <mnemonic, RC, MajOp, predImmOp, 0, 1>;
1541     def L2_p#NAME#fnew_io : T_pload_io <mnemonic, RC, MajOp, predImmOp, 1, 1>;
1542   }
1543 }
1544
1545 let accessSize = ByteAccess, isCodeGenOnly = 0 in {
1546   defm loadrb:  LD_Idxd <"memb", "LDrib", IntRegs, s11_0Ext, u6_0Ext, 0b1000>;
1547   defm loadrub: LD_Idxd <"memub", "LDriub", IntRegs, s11_0Ext, u6_0Ext, 0b1001>;
1548 }
1549
1550 let accessSize = HalfWordAccess, opExtentAlign = 1, isCodeGenOnly = 0 in {
1551   defm loadrh:  LD_Idxd <"memh", "LDrih", IntRegs, s11_1Ext, u6_1Ext, 0b1010>;
1552   defm loadruh: LD_Idxd <"memuh", "LDriuh", IntRegs, s11_1Ext, u6_1Ext, 0b1011>;
1553 }
1554
1555 let accessSize = WordAccess, opExtentAlign = 2, isCodeGenOnly = 0 in
1556 defm loadri: LD_Idxd <"memw", "LDriw", IntRegs, s11_2Ext, u6_2Ext, 0b1100>;
1557
1558 let accessSize = DoubleWordAccess, opExtentAlign = 3, isCodeGenOnly = 0 in
1559 defm loadrd: LD_Idxd <"memd", "LDrid", DoubleRegs, s11_3Ext, u6_3Ext, 0b1110>;
1560
1561 def : Pat < (i32 (sextloadi8 ADDRriS11_0:$addr)),
1562             (L2_loadrb_io AddrFI:$addr, 0) >;
1563
1564 def : Pat < (i32 (zextloadi8 ADDRriS11_0:$addr)),
1565             (L2_loadrub_io AddrFI:$addr, 0) >;
1566
1567 def : Pat < (i32 (sextloadi16 ADDRriS11_1:$addr)),
1568             (L2_loadrh_io AddrFI:$addr, 0) >;
1569
1570 def : Pat < (i32 (zextloadi16 ADDRriS11_1:$addr)),
1571             (L2_loadruh_io AddrFI:$addr, 0) >;
1572
1573 def : Pat < (i32 (load ADDRriS11_2:$addr)),
1574             (L2_loadri_io AddrFI:$addr, 0) >;
1575
1576 def : Pat < (i64 (load ADDRriS11_3:$addr)),
1577             (L2_loadrd_io AddrFI:$addr, 0) >;
1578
1579 let AddedComplexity = 20 in {
1580 def : Pat < (i32 (sextloadi8 (add IntRegs:$src1, s11_0ExtPred:$offset))),
1581             (L2_loadrb_io IntRegs:$src1, s11_0ExtPred:$offset) >;
1582
1583 def : Pat < (i32 (zextloadi8 (add IntRegs:$src1, s11_0ExtPred:$offset))),
1584             (L2_loadrub_io IntRegs:$src1, s11_0ExtPred:$offset) >;
1585
1586 def : Pat < (i32 (sextloadi16 (add IntRegs:$src1, s11_1ExtPred:$offset))),
1587             (L2_loadrh_io IntRegs:$src1, s11_1ExtPred:$offset) >;
1588
1589 def : Pat < (i32 (zextloadi16 (add IntRegs:$src1, s11_1ExtPred:$offset))),
1590             (L2_loadruh_io IntRegs:$src1, s11_1ExtPred:$offset) >;
1591
1592 def : Pat < (i32 (load (add IntRegs:$src1, s11_2ExtPred:$offset))),
1593             (L2_loadri_io IntRegs:$src1, s11_2ExtPred:$offset) >;
1594
1595 def : Pat < (i64 (load (add IntRegs:$src1, s11_3ExtPred:$offset))),
1596             (L2_loadrd_io IntRegs:$src1, s11_3ExtPred:$offset) >;
1597 }
1598
1599 //===----------------------------------------------------------------------===//
1600 // Post increment load
1601 //===----------------------------------------------------------------------===//
1602 //===----------------------------------------------------------------------===//
1603 // Template class for non-predicated post increment loads with immediate offset.
1604 //===----------------------------------------------------------------------===//
1605 let hasSideEffects = 0, addrMode = PostInc in
1606 class T_load_pi <string mnemonic, RegisterClass RC, Operand ImmOp,
1607                      bits<4> MajOp >
1608   : LDInstPI <(outs RC:$dst, IntRegs:$dst2),
1609   (ins IntRegs:$src1, ImmOp:$offset),
1610   "$dst = "#mnemonic#"($src1++#$offset)" ,
1611   [],
1612   "$src1 = $dst2" > ,
1613   PredNewRel {
1614     bits<5> dst;
1615     bits<5> src1;
1616     bits<7> offset;
1617     bits<4> offsetBits;
1618
1619     string ImmOpStr = !cast<string>(ImmOp);
1620     let offsetBits = !if (!eq(ImmOpStr, "s4_3Imm"), offset{6-3},
1621                      !if (!eq(ImmOpStr, "s4_2Imm"), offset{5-2},
1622                      !if (!eq(ImmOpStr, "s4_1Imm"), offset{4-1},
1623                                       /* s4_0Imm */ offset{3-0})));
1624     let hasNewValue = !if (!eq(ImmOpStr, "s4_3Imm"), 0, 1);
1625
1626     let IClass = 0b1001;
1627
1628     let Inst{27-25} = 0b101;
1629     let Inst{24-21} = MajOp;
1630     let Inst{20-16} = src1;
1631     let Inst{13-12} = 0b00;
1632     let Inst{8-5} = offsetBits;
1633     let Inst{4-0}   = dst;
1634   }
1635
1636 //===----------------------------------------------------------------------===//
1637 // Template class for predicated post increment loads with immediate offset.
1638 //===----------------------------------------------------------------------===//
1639 let isPredicated = 1, hasSideEffects = 0, addrMode = PostInc in
1640 class T_pload_pi <string mnemonic, RegisterClass RC, Operand ImmOp,
1641                           bits<4> MajOp, bit isPredNot, bit isPredNew >
1642   : LDInst <(outs RC:$dst, IntRegs:$dst2),
1643             (ins PredRegs:$src1, IntRegs:$src2, ImmOp:$offset),
1644   !if(isPredNot, "if (!$src1", "if ($src1")#!if(isPredNew, ".new) ",
1645   ") ")#"$dst = "#mnemonic#"($src2++#$offset)",
1646   [] ,
1647   "$src2 = $dst2" > ,
1648   PredNewRel {
1649     bits<5> dst;
1650     bits<2> src1;
1651     bits<5> src2;
1652     bits<7> offset;
1653     bits<4> offsetBits;
1654
1655     let isPredicatedNew = isPredNew;
1656     let isPredicatedFalse = isPredNot;
1657
1658     string ImmOpStr = !cast<string>(ImmOp);
1659     let offsetBits = !if (!eq(ImmOpStr, "s4_3Imm"), offset{6-3},
1660                      !if (!eq(ImmOpStr, "s4_2Imm"), offset{5-2},
1661                      !if (!eq(ImmOpStr, "s4_1Imm"), offset{4-1},
1662                                       /* s4_0Imm */ offset{3-0})));
1663     let hasNewValue = !if (!eq(ImmOpStr, "s4_3Imm"), 0, 1);
1664
1665     let IClass = 0b1001;
1666
1667     let Inst{27-25} = 0b101;
1668     let Inst{24-21} = MajOp;
1669     let Inst{20-16} = src2;
1670     let Inst{13} = 0b1;
1671     let Inst{12} = isPredNew;
1672     let Inst{11} = isPredNot;
1673     let Inst{10-9} = src1;
1674     let Inst{8-5}  = offsetBits;
1675     let Inst{4-0}  = dst;
1676   }
1677
1678 //===----------------------------------------------------------------------===//
1679 // Multiclass for post increment loads with immediate offset.
1680 //===----------------------------------------------------------------------===//
1681
1682 multiclass LD_PostInc <string mnemonic, string BaseOp, RegisterClass RC,
1683                        Operand ImmOp, bits<4> MajOp> {
1684   let BaseOpcode = "POST_"#BaseOp in {
1685     let isPredicable = 1 in
1686     def L2_#NAME#_pi : T_load_pi < mnemonic, RC, ImmOp, MajOp>;
1687
1688     // Predicated
1689     def L2_p#NAME#t_pi : T_pload_pi < mnemonic, RC, ImmOp, MajOp, 0, 0>;
1690     def L2_p#NAME#f_pi : T_pload_pi < mnemonic, RC, ImmOp, MajOp, 1, 0>;
1691
1692     // Predicated new
1693     def L2_p#NAME#tnew_pi : T_pload_pi < mnemonic, RC, ImmOp, MajOp, 0, 1>;
1694     def L2_p#NAME#fnew_pi : T_pload_pi < mnemonic, RC, ImmOp, MajOp, 1, 1>;
1695   }
1696 }
1697
1698 // post increment byte loads with immediate offset
1699 let accessSize = ByteAccess, isCodeGenOnly = 0 in {
1700   defm loadrb  : LD_PostInc <"memb",  "LDrib", IntRegs, s4_0Imm, 0b1000>;
1701   defm loadrub : LD_PostInc <"memub", "LDriub", IntRegs, s4_0Imm, 0b1001>;
1702 }
1703
1704 // post increment halfword loads with immediate offset
1705 let accessSize = HalfWordAccess, opExtentAlign = 1, isCodeGenOnly = 0 in {
1706   defm loadrh  : LD_PostInc <"memh",  "LDrih", IntRegs, s4_1Imm, 0b1010>;
1707   defm loadruh : LD_PostInc <"memuh", "LDriuh", IntRegs, s4_1Imm, 0b1011>;
1708 }
1709
1710 // post increment word loads with immediate offset
1711 let accessSize = WordAccess, opExtentAlign = 2, isCodeGenOnly = 0 in
1712 defm loadri : LD_PostInc <"memw", "LDriw", IntRegs, s4_2Imm, 0b1100>;
1713
1714 // post increment doubleword loads with immediate offset
1715 let accessSize = DoubleWordAccess, opExtentAlign = 3, isCodeGenOnly = 0 in
1716 defm loadrd : LD_PostInc <"memd", "LDrid", DoubleRegs, s4_3Imm, 0b1110>;
1717
1718 def : Pat< (i32 (extloadi1 ADDRriS11_0:$addr)),
1719            (i32 (L2_loadrb_io AddrFI:$addr, 0)) >;
1720
1721 // Load byte any-extend.
1722 def : Pat < (i32 (extloadi8 ADDRriS11_0:$addr)),
1723             (i32 (L2_loadrb_io AddrFI:$addr, 0)) >;
1724
1725 // Indexed load byte any-extend.
1726 let AddedComplexity = 20 in
1727 def : Pat < (i32 (extloadi8 (add IntRegs:$src1, s11_0ImmPred:$offset))),
1728             (i32 (L2_loadrb_io IntRegs:$src1, s11_0ImmPred:$offset)) >;
1729
1730 def : Pat < (i32 (extloadi16 ADDRriS11_1:$addr)),
1731             (i32 (L2_loadrh_io AddrFI:$addr, 0))>;
1732
1733 let AddedComplexity = 20 in
1734 def : Pat < (i32 (extloadi16 (add IntRegs:$src1, s11_1ImmPred:$offset))),
1735             (i32 (L2_loadrh_io IntRegs:$src1, s11_1ImmPred:$offset)) >;
1736
1737 let AddedComplexity = 10 in
1738 def : Pat < (i32 (zextloadi1 ADDRriS11_0:$addr)),
1739             (i32 (L2_loadrub_io AddrFI:$addr, 0))>;
1740
1741 let AddedComplexity = 20 in
1742 def : Pat < (i32 (zextloadi1 (add IntRegs:$src1, s11_0ImmPred:$offset))),
1743             (i32 (L2_loadrub_io IntRegs:$src1, s11_0ImmPred:$offset))>;
1744
1745 //===----------------------------------------------------------------------===//
1746 // Template class for post increment loads with register offset.
1747 //===----------------------------------------------------------------------===//
1748 let hasSideEffects = 0, addrMode = PostInc in
1749 class T_load_pr <string mnemonic, RegisterClass RC, bits<4> MajOp,
1750                        MemAccessSize AccessSz>
1751   : LDInstPI <(outs RC:$dst, IntRegs:$_dst_),
1752               (ins IntRegs:$src1, ModRegs:$src2),
1753   "$dst = "#mnemonic#"($src1++$src2)" ,
1754   [], "$src1 = $_dst_" > {
1755     bits<5> dst;
1756     bits<5> src1;
1757     bits<1> src2;
1758
1759     let accessSize = AccessSz;
1760     let IClass = 0b1001;
1761
1762     let Inst{27-25} = 0b110;
1763     let Inst{24-21} = MajOp;
1764     let Inst{20-16} = src1;
1765     let Inst{13}    = src2;
1766     let Inst{12}    = 0b0;
1767     let Inst{7}     = 0b0;
1768     let Inst{4-0}   = dst;
1769   }
1770
1771 let hasNewValue = 1, isCodeGenOnly = 0 in {
1772   def L2_loadrb_pr  : T_load_pr <"memb",  IntRegs, 0b1000, ByteAccess>;
1773   def L2_loadrub_pr : T_load_pr <"memub", IntRegs, 0b1001, ByteAccess>;
1774   def L2_loadrh_pr  : T_load_pr <"memh",  IntRegs, 0b1010, HalfWordAccess>;
1775   def L2_loadruh_pr : T_load_pr <"memuh", IntRegs, 0b1011, HalfWordAccess>;
1776   def L2_loadri_pr  : T_load_pr <"memw",  IntRegs, 0b1100, WordAccess>;
1777 }
1778
1779 let isCodeGenOnly = 0 in
1780 def L2_loadrd_pr   : T_load_pr <"memd", DoubleRegs, 0b1110, DoubleWordAccess>;
1781
1782 // Load predicate.
1783 let isExtendable = 1, opExtendable = 2, isExtentSigned = 1, opExtentBits = 13,
1784 isPseudo = 1, Defs = [R10,R11,D5], hasSideEffects = 0 in
1785 def LDriw_pred : LDInst2<(outs PredRegs:$dst),
1786             (ins MEMri:$addr),
1787             "Error; should not emit",
1788             []>;
1789
1790 let Defs = [R29, R30, R31], Uses = [R30], hasSideEffects = 0, isCodeGenOnly = 0 in
1791   def L2_deallocframe : LDInst<(outs), (ins),
1792                      "deallocframe",
1793                      []> {
1794     let IClass = 0b1001;
1795
1796     let Inst{27-16} = 0b000000011110;
1797     let Inst{13} = 0b0;
1798     let Inst{4-0} = 0b11110;
1799 }
1800
1801 // Load / Post increment circular addressing mode.
1802 let Uses = [CS], hasSideEffects = 0, hasNewValue = 1, opNewValue = 0 in
1803 class T_load_pcr<string mnemonic, RegisterClass RC, bits<4> MajOp>
1804   : LDInst <(outs RC:$dst, IntRegs:$_dst_),
1805             (ins IntRegs:$Rz, ModRegs:$Mu),
1806   "$dst = "#mnemonic#"($Rz ++ I:circ($Mu))", [],
1807   "$Rz = $_dst_" > {
1808     bits<5> dst;
1809     bits<5> Rz;
1810     bit Mu;
1811
1812     let IClass = 0b1001;
1813
1814     let Inst{27-25} = 0b100;
1815     let Inst{24-21} = MajOp;
1816     let Inst{20-16} = Rz;
1817     let Inst{13} = Mu;
1818     let Inst{12} = 0b0;
1819     let Inst{9} = 0b1;
1820     let Inst{7} = 0b0;
1821     let Inst{4-0} = dst;
1822  }
1823
1824 let accessSize = ByteAccess, isCodeGenOnly = 0 in {
1825   def L2_loadrb_pcr  : T_load_pcr <"memb",  IntRegs, 0b1000>;
1826   def L2_loadrub_pcr : T_load_pcr <"memub", IntRegs, 0b1001>;
1827 }
1828
1829 let accessSize = HalfWordAccess, isCodeGenOnly = 0 in {
1830   def L2_loadrh_pcr   : T_load_pcr <"memh",   IntRegs, 0b1010>;
1831   def L2_loadruh_pcr  : T_load_pcr <"memuh",  IntRegs, 0b1011>;
1832 }
1833
1834 let accessSize = WordAccess, isCodeGenOnly = 0 in {
1835   def  L2_loadri_pcr  : T_load_pcr <"memw", IntRegs, 0b1100>;
1836 }
1837
1838 let accessSize = DoubleWordAccess, isCodeGenOnly = 0 in
1839 def L2_loadrd_pcr  : T_load_pcr <"memd", DoubleRegs, 0b1110>;
1840
1841 //===----------------------------------------------------------------------===//
1842 // Circular loads with immediate offset.
1843 //===----------------------------------------------------------------------===//
1844 let Uses = [CS], mayLoad = 1, hasSideEffects = 0, hasNewValue = 1 in
1845 class T_load_pci <string mnemonic, RegisterClass RC,
1846                   Operand ImmOp, bits<4> MajOp>
1847   : LDInstPI<(outs RC:$dst, IntRegs:$_dst_),
1848              (ins IntRegs:$Rz, ImmOp:$offset, ModRegs:$Mu),
1849   "$dst = "#mnemonic#"($Rz ++ #$offset:circ($Mu))", [],
1850   "$Rz = $_dst_"> {
1851     bits<5> dst;
1852     bits<5> Rz;
1853     bits<1> Mu;
1854     bits<7> offset;
1855     bits<4> offsetBits;
1856
1857     string ImmOpStr = !cast<string>(ImmOp);
1858     let offsetBits = !if (!eq(ImmOpStr, "s4_3Imm"), offset{6-3},
1859                      !if (!eq(ImmOpStr, "s4_2Imm"), offset{5-2},
1860                      !if (!eq(ImmOpStr, "s4_1Imm"), offset{4-1},
1861                                       /* s4_0Imm */ offset{3-0})));
1862     let IClass      = 0b1001;
1863     let Inst{27-25} = 0b100;
1864     let Inst{24-21} = MajOp;
1865     let Inst{20-16} = Rz;
1866     let Inst{13}    = Mu;
1867     let Inst{12}    = 0b0;
1868     let Inst{9}     = 0b0;
1869     let Inst{8-5}   = offsetBits;
1870     let Inst{4-0}   = dst;
1871   }
1872
1873 // Byte variants of circ load
1874 let accessSize = ByteAccess, isCodeGenOnly = 0 in {
1875   def L2_loadrb_pci  : T_load_pci <"memb",  IntRegs, s4_0Imm, 0b1000>;
1876   def L2_loadrub_pci : T_load_pci <"memub", IntRegs, s4_0Imm, 0b1001>;
1877 }
1878
1879 // Half word variants of circ load
1880 let accessSize = HalfWordAccess, isCodeGenOnly = 0 in {
1881   def L2_loadrh_pci   : T_load_pci <"memh",   IntRegs, s4_1Imm, 0b1010>;
1882   def L2_loadruh_pci  : T_load_pci <"memuh",  IntRegs, s4_1Imm, 0b1011>;
1883 }
1884
1885 // Word variants of circ load
1886 let accessSize = WordAccess, isCodeGenOnly = 0 in
1887 def L2_loadri_pci   : T_load_pci <"memw",   IntRegs,    s4_2Imm, 0b1100>;
1888
1889 let accessSize = DoubleWordAccess, hasNewValue = 0, isCodeGenOnly = 0 in
1890 def L2_loadrd_pci : T_load_pci <"memd", DoubleRegs, s4_3Imm, 0b1110>;
1891
1892 // L[24]_load[wd]_locked: Load word/double with lock.
1893 let isSoloAX = 1 in
1894 class T_load_locked <string mnemonic, RegisterClass RC>
1895   : LD0Inst <(outs RC:$dst),
1896              (ins IntRegs:$src),
1897     "$dst = "#mnemonic#"($src)"> {
1898     bits<5> dst;
1899     bits<5> src;
1900     let IClass = 0b1001;
1901     let Inst{27-21} = 0b0010000;
1902     let Inst{20-16} = src;
1903     let Inst{13-12} = !if (!eq(mnemonic, "memd_locked"), 0b01, 0b00);
1904     let Inst{4-0} = dst;
1905 }
1906 let hasNewValue = 1, accessSize = WordAccess, opNewValue = 0, isCodeGenOnly = 0 in
1907   def L2_loadw_locked : T_load_locked <"memw_locked", IntRegs>;
1908 let accessSize = DoubleWordAccess, isCodeGenOnly = 0 in
1909   def L4_loadd_locked : T_load_locked <"memd_locked", DoubleRegs>;
1910 //===----------------------------------------------------------------------===//
1911 // Bit-reversed loads with auto-increment register
1912 //===----------------------------------------------------------------------===//
1913 let hasSideEffects = 0 in
1914 class T_load_pbr<string mnemonic, RegisterClass RC,
1915                             MemAccessSize addrSize, bits<4> majOp>
1916   : LDInst
1917     <(outs RC:$dst, IntRegs:$_dst_),
1918      (ins IntRegs:$Rz, ModRegs:$Mu),
1919      "$dst = "#mnemonic#"($Rz ++ $Mu:brev)" ,
1920       [] , "$Rz = $_dst_" > {
1921
1922       let accessSize = addrSize;
1923
1924       bits<5> dst;
1925       bits<5> Rz;
1926       bits<1> Mu;
1927
1928       let IClass = 0b1001;
1929
1930       let Inst{27-25} = 0b111;
1931       let Inst{24-21} = majOp;
1932       let Inst{20-16} = Rz;
1933       let Inst{13} = Mu;
1934       let Inst{12} = 0b0;
1935       let Inst{7} = 0b0;
1936       let Inst{4-0} = dst;
1937   }
1938
1939 let hasNewValue =1, opNewValue = 0, isCodeGenOnly = 0 in {
1940   def L2_loadrb_pbr   : T_load_pbr <"memb",  IntRegs, ByteAccess, 0b1000>;
1941   def L2_loadrub_pbr  : T_load_pbr <"memub", IntRegs, ByteAccess, 0b1001>;
1942   def L2_loadrh_pbr   : T_load_pbr <"memh",  IntRegs, HalfWordAccess, 0b1010>;
1943   def L2_loadruh_pbr  : T_load_pbr <"memuh", IntRegs, HalfWordAccess, 0b1011>;
1944   def L2_loadri_pbr : T_load_pbr <"memw", IntRegs, WordAccess, 0b1100>;
1945 }
1946
1947 let isCodeGenOnly = 0 in
1948 def L2_loadrd_pbr : T_load_pbr <"memd", DoubleRegs, DoubleWordAccess, 0b1110>;
1949
1950 //===----------------------------------------------------------------------===//
1951 // LD -
1952 //===----------------------------------------------------------------------===//
1953
1954 //===----------------------------------------------------------------------===//
1955 // MTYPE/ALU +
1956 //===----------------------------------------------------------------------===//
1957 //===----------------------------------------------------------------------===//
1958 // MTYPE/ALU -
1959 //===----------------------------------------------------------------------===//
1960
1961 //===----------------------------------------------------------------------===//
1962 // MTYPE/COMPLEX +
1963 //===----------------------------------------------------------------------===//
1964 //===----------------------------------------------------------------------===//
1965 // MTYPE/COMPLEX -
1966 //===----------------------------------------------------------------------===//
1967
1968 //===----------------------------------------------------------------------===//
1969 // MTYPE/MPYH +
1970 //===----------------------------------------------------------------------===//
1971
1972 //===----------------------------------------------------------------------===//
1973 // Template Class
1974 // MPYS / Multipy signed/unsigned halfwords
1975 //Rd=mpy[u](Rs.[H|L],Rt.[H|L])[:<<1][:rnd][:sat]
1976 //===----------------------------------------------------------------------===//
1977
1978 let hasNewValue = 1, opNewValue = 0 in
1979 class T_M2_mpy < bits<2> LHbits, bit isSat, bit isRnd,
1980                  bit hasShift, bit isUnsigned>
1981   : MInst < (outs IntRegs:$Rd), (ins IntRegs:$Rs, IntRegs:$Rt),
1982   "$Rd = "#!if(isUnsigned,"mpyu","mpy")#"($Rs."#!if(LHbits{1},"h","l")
1983                                        #", $Rt."#!if(LHbits{0},"h)","l)")
1984                                        #!if(hasShift,":<<1","")
1985                                        #!if(isRnd,":rnd","")
1986                                        #!if(isSat,":sat",""),
1987   [], "", M_tc_3x_SLOT23 > {
1988     bits<5> Rd;
1989     bits<5> Rs;
1990     bits<5> Rt;
1991
1992     let IClass = 0b1110;
1993
1994     let Inst{27-24} = 0b1100;
1995     let Inst{23} = hasShift;
1996     let Inst{22} = isUnsigned;
1997     let Inst{21} = isRnd;
1998     let Inst{7} = isSat;
1999     let Inst{6-5} = LHbits;
2000     let Inst{4-0} = Rd;
2001     let Inst{20-16} = Rs;
2002     let Inst{12-8} = Rt;
2003   }
2004
2005 //Rd=mpy(Rs.[H|L],Rt.[H|L])[:<<1]
2006 let isCodeGenOnly = 0 in {
2007 def M2_mpy_ll_s1: T_M2_mpy<0b00, 0, 0, 1, 0>;
2008 def M2_mpy_ll_s0: T_M2_mpy<0b00, 0, 0, 0, 0>;
2009 def M2_mpy_lh_s1: T_M2_mpy<0b01, 0, 0, 1, 0>;
2010 def M2_mpy_lh_s0: T_M2_mpy<0b01, 0, 0, 0, 0>;
2011 def M2_mpy_hl_s1: T_M2_mpy<0b10, 0, 0, 1, 0>;
2012 def M2_mpy_hl_s0: T_M2_mpy<0b10, 0, 0, 0, 0>;
2013 def M2_mpy_hh_s1: T_M2_mpy<0b11, 0, 0, 1, 0>;
2014 def M2_mpy_hh_s0: T_M2_mpy<0b11, 0, 0, 0, 0>;
2015 }
2016
2017 //Rd=mpyu(Rs.[H|L],Rt.[H|L])[:<<1]
2018 let isCodeGenOnly = 0 in {
2019 def M2_mpyu_ll_s1: T_M2_mpy<0b00, 0, 0, 1, 1>;
2020 def M2_mpyu_ll_s0: T_M2_mpy<0b00, 0, 0, 0, 1>;
2021 def M2_mpyu_lh_s1: T_M2_mpy<0b01, 0, 0, 1, 1>;
2022 def M2_mpyu_lh_s0: T_M2_mpy<0b01, 0, 0, 0, 1>;
2023 def M2_mpyu_hl_s1: T_M2_mpy<0b10, 0, 0, 1, 1>;
2024 def M2_mpyu_hl_s0: T_M2_mpy<0b10, 0, 0, 0, 1>;
2025 def M2_mpyu_hh_s1: T_M2_mpy<0b11, 0, 0, 1, 1>;
2026 def M2_mpyu_hh_s0: T_M2_mpy<0b11, 0, 0, 0, 1>;
2027 }
2028
2029 //Rd=mpy(Rs.[H|L],Rt.[H|L])[:<<1]:rnd
2030 let isCodeGenOnly = 0 in {
2031 def M2_mpy_rnd_ll_s1: T_M2_mpy <0b00, 0, 1, 1, 0>;
2032 def M2_mpy_rnd_ll_s0: T_M2_mpy <0b00, 0, 1, 0, 0>;
2033 def M2_mpy_rnd_lh_s1: T_M2_mpy <0b01, 0, 1, 1, 0>;
2034 def M2_mpy_rnd_lh_s0: T_M2_mpy <0b01, 0, 1, 0, 0>;
2035 def M2_mpy_rnd_hl_s1: T_M2_mpy <0b10, 0, 1, 1, 0>;
2036 def M2_mpy_rnd_hl_s0: T_M2_mpy <0b10, 0, 1, 0, 0>;
2037 def M2_mpy_rnd_hh_s1: T_M2_mpy <0b11, 0, 1, 1, 0>;
2038 def M2_mpy_rnd_hh_s0: T_M2_mpy <0b11, 0, 1, 0, 0>;
2039 }
2040
2041 //Rd=mpy(Rs.[H|L],Rt.[H|L])[:<<1][:sat]
2042 //Rd=mpy(Rs.[H|L],Rt.[H|L])[:<<1][:rnd][:sat]
2043 let Defs = [USR_OVF], isCodeGenOnly = 0 in {
2044   def M2_mpy_sat_ll_s1: T_M2_mpy <0b00, 1, 0, 1, 0>;
2045   def M2_mpy_sat_ll_s0: T_M2_mpy <0b00, 1, 0, 0, 0>;
2046   def M2_mpy_sat_lh_s1: T_M2_mpy <0b01, 1, 0, 1, 0>;
2047   def M2_mpy_sat_lh_s0: T_M2_mpy <0b01, 1, 0, 0, 0>;
2048   def M2_mpy_sat_hl_s1: T_M2_mpy <0b10, 1, 0, 1, 0>;
2049   def M2_mpy_sat_hl_s0: T_M2_mpy <0b10, 1, 0, 0, 0>;
2050   def M2_mpy_sat_hh_s1: T_M2_mpy <0b11, 1, 0, 1, 0>;
2051   def M2_mpy_sat_hh_s0: T_M2_mpy <0b11, 1, 0, 0, 0>;
2052
2053   def M2_mpy_sat_rnd_ll_s1: T_M2_mpy <0b00, 1, 1, 1, 0>;
2054   def M2_mpy_sat_rnd_ll_s0: T_M2_mpy <0b00, 1, 1, 0, 0>;
2055   def M2_mpy_sat_rnd_lh_s1: T_M2_mpy <0b01, 1, 1, 1, 0>;
2056   def M2_mpy_sat_rnd_lh_s0: T_M2_mpy <0b01, 1, 1, 0, 0>;
2057   def M2_mpy_sat_rnd_hl_s1: T_M2_mpy <0b10, 1, 1, 1, 0>;
2058   def M2_mpy_sat_rnd_hl_s0: T_M2_mpy <0b10, 1, 1, 0, 0>;
2059   def M2_mpy_sat_rnd_hh_s1: T_M2_mpy <0b11, 1, 1, 1, 0>;
2060   def M2_mpy_sat_rnd_hh_s0: T_M2_mpy <0b11, 1, 1, 0, 0>;
2061 }
2062
2063 //===----------------------------------------------------------------------===//
2064 // Template Class
2065 // MPYS / Multipy signed/unsigned halfwords and add/subtract the
2066 // result from the accumulator.
2067 //Rx [-+]= mpy[u](Rs.[H|L],Rt.[H|L])[:<<1][:sat]
2068 //===----------------------------------------------------------------------===//
2069
2070 let hasNewValue = 1, opNewValue = 0 in
2071 class T_M2_mpy_acc < bits<2> LHbits, bit isSat, bit isNac,
2072                  bit hasShift, bit isUnsigned >
2073   : MInst_acc<(outs IntRegs:$Rx), (ins IntRegs:$dst2, IntRegs:$Rs, IntRegs:$Rt),
2074   "$Rx "#!if(isNac,"-= ","+= ")#!if(isUnsigned,"mpyu","mpy")
2075                               #"($Rs."#!if(LHbits{1},"h","l")
2076                               #", $Rt."#!if(LHbits{0},"h)","l)")
2077                               #!if(hasShift,":<<1","")
2078                               #!if(isSat,":sat",""),
2079   [], "$dst2 = $Rx", M_tc_3x_SLOT23 > {
2080     bits<5> Rx;
2081     bits<5> Rs;
2082     bits<5> Rt;
2083
2084     let IClass = 0b1110;
2085     let Inst{27-24} = 0b1110;
2086     let Inst{23} = hasShift;
2087     let Inst{22} = isUnsigned;
2088     let Inst{21} = isNac;
2089     let Inst{7} = isSat;
2090     let Inst{6-5} = LHbits;
2091     let Inst{4-0} = Rx;
2092     let Inst{20-16} = Rs;
2093     let Inst{12-8} = Rt;
2094   }
2095
2096 //Rx += mpy(Rs.[H|L],Rt.[H|L])[:<<1]
2097 let isCodeGenOnly = 0 in {
2098 def M2_mpy_acc_ll_s1: T_M2_mpy_acc <0b00, 0, 0, 1, 0>;
2099 def M2_mpy_acc_ll_s0: T_M2_mpy_acc <0b00, 0, 0, 0, 0>;
2100 def M2_mpy_acc_lh_s1: T_M2_mpy_acc <0b01, 0, 0, 1, 0>;
2101 def M2_mpy_acc_lh_s0: T_M2_mpy_acc <0b01, 0, 0, 0, 0>;
2102 def M2_mpy_acc_hl_s1: T_M2_mpy_acc <0b10, 0, 0, 1, 0>;
2103 def M2_mpy_acc_hl_s0: T_M2_mpy_acc <0b10, 0, 0, 0, 0>;
2104 def M2_mpy_acc_hh_s1: T_M2_mpy_acc <0b11, 0, 0, 1, 0>;
2105 def M2_mpy_acc_hh_s0: T_M2_mpy_acc <0b11, 0, 0, 0, 0>;
2106 }
2107
2108 //Rx += mpyu(Rs.[H|L],Rt.[H|L])[:<<1]
2109 let isCodeGenOnly = 0 in {
2110 def M2_mpyu_acc_ll_s1: T_M2_mpy_acc <0b00, 0, 0, 1, 1>;
2111 def M2_mpyu_acc_ll_s0: T_M2_mpy_acc <0b00, 0, 0, 0, 1>;
2112 def M2_mpyu_acc_lh_s1: T_M2_mpy_acc <0b01, 0, 0, 1, 1>;
2113 def M2_mpyu_acc_lh_s0: T_M2_mpy_acc <0b01, 0, 0, 0, 1>;
2114 def M2_mpyu_acc_hl_s1: T_M2_mpy_acc <0b10, 0, 0, 1, 1>;
2115 def M2_mpyu_acc_hl_s0: T_M2_mpy_acc <0b10, 0, 0, 0, 1>;
2116 def M2_mpyu_acc_hh_s1: T_M2_mpy_acc <0b11, 0, 0, 1, 1>;
2117 def M2_mpyu_acc_hh_s0: T_M2_mpy_acc <0b11, 0, 0, 0, 1>;
2118 }
2119
2120 //Rx -= mpy(Rs.[H|L],Rt.[H|L])[:<<1]
2121 let isCodeGenOnly = 0 in {
2122 def M2_mpy_nac_ll_s1: T_M2_mpy_acc <0b00, 0, 1, 1, 0>;
2123 def M2_mpy_nac_ll_s0: T_M2_mpy_acc <0b00, 0, 1, 0, 0>;
2124 def M2_mpy_nac_lh_s1: T_M2_mpy_acc <0b01, 0, 1, 1, 0>;
2125 def M2_mpy_nac_lh_s0: T_M2_mpy_acc <0b01, 0, 1, 0, 0>;
2126 def M2_mpy_nac_hl_s1: T_M2_mpy_acc <0b10, 0, 1, 1, 0>;
2127 def M2_mpy_nac_hl_s0: T_M2_mpy_acc <0b10, 0, 1, 0, 0>;
2128 def M2_mpy_nac_hh_s1: T_M2_mpy_acc <0b11, 0, 1, 1, 0>;
2129 def M2_mpy_nac_hh_s0: T_M2_mpy_acc <0b11, 0, 1, 0, 0>;
2130 }
2131
2132 //Rx -= mpyu(Rs.[H|L],Rt.[H|L])[:<<1]
2133 let isCodeGenOnly = 0 in {
2134 def M2_mpyu_nac_ll_s1: T_M2_mpy_acc <0b00, 0, 1, 1, 1>;
2135 def M2_mpyu_nac_ll_s0: T_M2_mpy_acc <0b00, 0, 1, 0, 1>;
2136 def M2_mpyu_nac_lh_s1: T_M2_mpy_acc <0b01, 0, 1, 1, 1>;
2137 def M2_mpyu_nac_lh_s0: T_M2_mpy_acc <0b01, 0, 1, 0, 1>;
2138 def M2_mpyu_nac_hl_s1: T_M2_mpy_acc <0b10, 0, 1, 1, 1>;
2139 def M2_mpyu_nac_hl_s0: T_M2_mpy_acc <0b10, 0, 1, 0, 1>;
2140 def M2_mpyu_nac_hh_s1: T_M2_mpy_acc <0b11, 0, 1, 1, 1>;
2141 def M2_mpyu_nac_hh_s0: T_M2_mpy_acc <0b11, 0, 1, 0, 1>;
2142 }
2143
2144 //Rx += mpy(Rs.[H|L],Rt.[H|L])[:<<1]:sat
2145 let isCodeGenOnly = 0 in {
2146 def M2_mpy_acc_sat_ll_s1: T_M2_mpy_acc <0b00, 1, 0, 1, 0>;
2147 def M2_mpy_acc_sat_ll_s0: T_M2_mpy_acc <0b00, 1, 0, 0, 0>;
2148 def M2_mpy_acc_sat_lh_s1: T_M2_mpy_acc <0b01, 1, 0, 1, 0>;
2149 def M2_mpy_acc_sat_lh_s0: T_M2_mpy_acc <0b01, 1, 0, 0, 0>;
2150 def M2_mpy_acc_sat_hl_s1: T_M2_mpy_acc <0b10, 1, 0, 1, 0>;
2151 def M2_mpy_acc_sat_hl_s0: T_M2_mpy_acc <0b10, 1, 0, 0, 0>;
2152 def M2_mpy_acc_sat_hh_s1: T_M2_mpy_acc <0b11, 1, 0, 1, 0>;
2153 def M2_mpy_acc_sat_hh_s0: T_M2_mpy_acc <0b11, 1, 0, 0, 0>;
2154 }
2155
2156 //Rx -= mpy(Rs.[H|L],Rt.[H|L])[:<<1]:sat
2157 let isCodeGenOnly = 0 in {
2158 def M2_mpy_nac_sat_ll_s1: T_M2_mpy_acc <0b00, 1, 1, 1, 0>;
2159 def M2_mpy_nac_sat_ll_s0: T_M2_mpy_acc <0b00, 1, 1, 0, 0>;
2160 def M2_mpy_nac_sat_lh_s1: T_M2_mpy_acc <0b01, 1, 1, 1, 0>;
2161 def M2_mpy_nac_sat_lh_s0: T_M2_mpy_acc <0b01, 1, 1, 0, 0>;
2162 def M2_mpy_nac_sat_hl_s1: T_M2_mpy_acc <0b10, 1, 1, 1, 0>;
2163 def M2_mpy_nac_sat_hl_s0: T_M2_mpy_acc <0b10, 1, 1, 0, 0>;
2164 def M2_mpy_nac_sat_hh_s1: T_M2_mpy_acc <0b11, 1, 1, 1, 0>;
2165 def M2_mpy_nac_sat_hh_s0: T_M2_mpy_acc <0b11, 1, 1, 0, 0>;
2166 }
2167
2168 //===----------------------------------------------------------------------===//
2169 // Template Class
2170 // MPYS / Multipy signed/unsigned halfwords and add/subtract the
2171 // result from the 64-bit destination register.
2172 //Rxx [-+]= mpy[u](Rs.[H|L],Rt.[H|L])[:<<1][:sat]
2173 //===----------------------------------------------------------------------===//
2174
2175 class T_M2_mpyd_acc < bits<2> LHbits, bit isNac, bit hasShift, bit isUnsigned>
2176   : MInst_acc<(outs DoubleRegs:$Rxx),
2177               (ins DoubleRegs:$dst2, IntRegs:$Rs, IntRegs:$Rt),
2178   "$Rxx "#!if(isNac,"-= ","+= ")#!if(isUnsigned,"mpyu","mpy")
2179                                 #"($Rs."#!if(LHbits{1},"h","l")
2180                                 #", $Rt."#!if(LHbits{0},"h)","l)")
2181                                 #!if(hasShift,":<<1",""),
2182   [], "$dst2 = $Rxx", M_tc_3x_SLOT23 > {
2183     bits<5> Rxx;
2184     bits<5> Rs;
2185     bits<5> Rt;
2186
2187     let IClass = 0b1110;
2188
2189     let Inst{27-24} = 0b0110;
2190     let Inst{23} = hasShift;
2191     let Inst{22} = isUnsigned;
2192     let Inst{21} = isNac;
2193     let Inst{7} = 0;
2194     let Inst{6-5} = LHbits;
2195     let Inst{4-0} = Rxx;
2196     let Inst{20-16} = Rs;
2197     let Inst{12-8} = Rt;
2198   }
2199
2200 let isCodeGenOnly = 0 in {
2201 def M2_mpyd_acc_hh_s0: T_M2_mpyd_acc <0b11, 0, 0, 0>;
2202 def M2_mpyd_acc_hl_s0: T_M2_mpyd_acc <0b10, 0, 0, 0>;
2203 def M2_mpyd_acc_lh_s0: T_M2_mpyd_acc <0b01, 0, 0, 0>;
2204 def M2_mpyd_acc_ll_s0: T_M2_mpyd_acc <0b00, 0, 0, 0>;
2205
2206 def M2_mpyd_acc_hh_s1: T_M2_mpyd_acc <0b11, 0, 1, 0>;
2207 def M2_mpyd_acc_hl_s1: T_M2_mpyd_acc <0b10, 0, 1, 0>;
2208 def M2_mpyd_acc_lh_s1: T_M2_mpyd_acc <0b01, 0, 1, 0>;
2209 def M2_mpyd_acc_ll_s1: T_M2_mpyd_acc <0b00, 0, 1, 0>;
2210
2211 def M2_mpyd_nac_hh_s0: T_M2_mpyd_acc <0b11, 1, 0, 0>;
2212 def M2_mpyd_nac_hl_s0: T_M2_mpyd_acc <0b10, 1, 0, 0>;
2213 def M2_mpyd_nac_lh_s0: T_M2_mpyd_acc <0b01, 1, 0, 0>;
2214 def M2_mpyd_nac_ll_s0: T_M2_mpyd_acc <0b00, 1, 0, 0>;
2215
2216 def M2_mpyd_nac_hh_s1: T_M2_mpyd_acc <0b11, 1, 1, 0>;
2217 def M2_mpyd_nac_hl_s1: T_M2_mpyd_acc <0b10, 1, 1, 0>;
2218 def M2_mpyd_nac_lh_s1: T_M2_mpyd_acc <0b01, 1, 1, 0>;
2219 def M2_mpyd_nac_ll_s1: T_M2_mpyd_acc <0b00, 1, 1, 0>;
2220
2221 def M2_mpyud_acc_hh_s0: T_M2_mpyd_acc <0b11, 0, 0, 1>;
2222 def M2_mpyud_acc_hl_s0: T_M2_mpyd_acc <0b10, 0, 0, 1>;
2223 def M2_mpyud_acc_lh_s0: T_M2_mpyd_acc <0b01, 0, 0, 1>;
2224 def M2_mpyud_acc_ll_s0: T_M2_mpyd_acc <0b00, 0, 0, 1>;
2225
2226 def M2_mpyud_acc_hh_s1: T_M2_mpyd_acc <0b11, 0, 1, 1>;
2227 def M2_mpyud_acc_hl_s1: T_M2_mpyd_acc <0b10, 0, 1, 1>;
2228 def M2_mpyud_acc_lh_s1: T_M2_mpyd_acc <0b01, 0, 1, 1>;
2229 def M2_mpyud_acc_ll_s1: T_M2_mpyd_acc <0b00, 0, 1, 1>;
2230
2231 def M2_mpyud_nac_hh_s0: T_M2_mpyd_acc <0b11, 1, 0, 1>;
2232 def M2_mpyud_nac_hl_s0: T_M2_mpyd_acc <0b10, 1, 0, 1>;
2233 def M2_mpyud_nac_lh_s0: T_M2_mpyd_acc <0b01, 1, 0, 1>;
2234 def M2_mpyud_nac_ll_s0: T_M2_mpyd_acc <0b00, 1, 0, 1>;
2235
2236 def M2_mpyud_nac_hh_s1: T_M2_mpyd_acc <0b11, 1, 1, 1>;
2237 def M2_mpyud_nac_hl_s1: T_M2_mpyd_acc <0b10, 1, 1, 1>;
2238 def M2_mpyud_nac_lh_s1: T_M2_mpyd_acc <0b01, 1, 1, 1>;
2239 def M2_mpyud_nac_ll_s1: T_M2_mpyd_acc <0b00, 1, 1, 1>;
2240 }
2241
2242 let hasNewValue = 1, opNewValue = 0 in
2243 class T_MType_mpy <string mnemonic, bits<4> RegTyBits, RegisterClass RC,
2244                    bits<3> MajOp, bits<3> MinOp, bit isSat = 0, bit isRnd = 0,
2245                    string op2Suffix = "", bit isRaw = 0, bit isHi = 0 >
2246   : MInst <(outs IntRegs:$dst), (ins RC:$src1, RC:$src2),
2247   "$dst = "#mnemonic
2248            #"($src1, $src2"#op2Suffix#")"
2249            #!if(MajOp{2}, ":<<1", "")
2250            #!if(isRnd, ":rnd", "")
2251            #!if(isSat, ":sat", "")
2252            #!if(isRaw, !if(isHi, ":raw:hi", ":raw:lo"), ""), [] > {
2253     bits<5> dst;
2254     bits<5> src1;
2255     bits<5> src2;
2256
2257     let IClass = 0b1110;
2258
2259     let Inst{27-24} = RegTyBits;
2260     let Inst{23-21} = MajOp;
2261     let Inst{20-16} = src1;
2262     let Inst{13}    = 0b0;
2263     let Inst{12-8}  = src2;
2264     let Inst{7-5}   = MinOp;
2265     let Inst{4-0}   = dst;
2266   }
2267
2268 class T_MType_dd  <string mnemonic, bits<3> MajOp, bits<3> MinOp,
2269                    bit isSat = 0, bit isRnd = 0 >
2270   : T_MType_mpy <mnemonic, 0b1001, DoubleRegs, MajOp, MinOp, isSat, isRnd>;
2271
2272 class T_MType_rr1  <string mnemonic, bits<3> MajOp, bits<3> MinOp,
2273                     bit isSat = 0, bit isRnd = 0 >
2274   : T_MType_mpy<mnemonic, 0b1101, IntRegs, MajOp, MinOp, isSat, isRnd>;
2275
2276 class T_MType_rr2 <string mnemonic, bits<3> MajOp, bits<3> MinOp,
2277                    bit isSat = 0, bit isRnd = 0, string op2str = "" >
2278   : T_MType_mpy<mnemonic, 0b1101, IntRegs, MajOp, MinOp, isSat, isRnd, op2str>;
2279
2280 let CextOpcode = "mpyi", InputType = "reg", isCodeGenOnly = 0 in
2281 def M2_mpyi    : T_MType_rr1 <"mpyi", 0b000, 0b000>, ImmRegRel;
2282
2283 let isCodeGenOnly = 0 in {
2284 def M2_mpy_up  : T_MType_rr1 <"mpy",  0b000, 0b001>;
2285 def M2_mpyu_up : T_MType_rr1 <"mpyu", 0b010, 0b001>;
2286 }
2287
2288 let isCodeGenOnly = 0 in
2289 def M2_dpmpyss_rnd_s0 : T_MType_rr1 <"mpy", 0b001, 0b001, 0, 1>;
2290
2291 let isCodeGenOnly = 0 in {
2292 def M2_hmmpyh_rs1 : T_MType_rr2 <"mpy", 0b101, 0b100, 1, 1, ".h">;
2293 def M2_hmmpyl_rs1 : T_MType_rr2 <"mpy", 0b111, 0b100, 1, 1, ".l">;
2294 }
2295
2296 // V4 Instructions
2297 let isCodeGenOnly = 0 in {
2298 def M2_mpysu_up : T_MType_rr1 <"mpysu", 0b011, 0b001, 0>;
2299 def M2_mpy_up_s1_sat : T_MType_rr1 <"mpy", 0b111, 0b000, 1>;
2300
2301 def M2_hmmpyh_s1 : T_MType_rr2 <"mpy", 0b101, 0b000, 1, 0, ".h">;
2302 def M2_hmmpyl_s1 : T_MType_rr2 <"mpy", 0b101, 0b001, 1, 0, ".l">;
2303 }
2304
2305 def: Pat<(i32 (mul   I32:$src1, I32:$src2)), (M2_mpyi    I32:$src1, I32:$src2)>;
2306 def: Pat<(i32 (mulhs I32:$src1, I32:$src2)), (M2_mpy_up  I32:$src1, I32:$src2)>;
2307 def: Pat<(i32 (mulhu I32:$src1, I32:$src2)), (M2_mpyu_up I32:$src1, I32:$src2)>;
2308
2309 let hasNewValue = 1, opNewValue = 0 in
2310 class T_MType_mpy_ri <bit isNeg, Operand ImmOp, list<dag> pattern>
2311   : MInst < (outs IntRegs:$Rd), (ins IntRegs:$Rs, ImmOp:$u8),
2312   "$Rd ="#!if(isNeg, "- ", "+ ")#"mpyi($Rs, #$u8)" ,
2313    pattern, "", M_tc_3x_SLOT23> {
2314     bits<5> Rd;
2315     bits<5> Rs;
2316     bits<8> u8;
2317
2318     let IClass = 0b1110;
2319
2320     let Inst{27-24} = 0b0000;
2321     let Inst{23} = isNeg;
2322     let Inst{13} = 0b0;
2323     let Inst{4-0} = Rd;
2324     let Inst{20-16} = Rs;
2325     let Inst{12-5} = u8;
2326   }
2327
2328 let isExtendable = 1, opExtentBits = 8, opExtendable = 2, isCodeGenOnly = 0 in
2329 def M2_mpysip : T_MType_mpy_ri <0, u8Ext,
2330                 [(set (i32 IntRegs:$Rd), (mul IntRegs:$Rs, u8ExtPred:$u8))]>;
2331
2332 let isCodeGenOnly = 0 in
2333 def M2_mpysin :  T_MType_mpy_ri <1, u8Imm,
2334                 [(set (i32 IntRegs:$Rd), (ineg (mul IntRegs:$Rs,
2335                                                     u8ImmPred:$u8)))]>;
2336
2337 // Assember mapped to M2_mpyi
2338 let isAsmParserOnly = 1 in
2339 def M2_mpyui : MInst<(outs IntRegs:$dst),
2340                      (ins IntRegs:$src1, IntRegs:$src2),
2341   "$dst = mpyui($src1, $src2)">;
2342
2343 // Rd=mpyi(Rs,#m9)
2344 // s9 is NOT the same as m9 - but it works.. so far.
2345 // Assembler maps to either Rd=+mpyi(Rs,#u8) or Rd=-mpyi(Rs,#u8)
2346 // depending on the value of m9. See Arch Spec.
2347 let isExtendable = 1, opExtendable = 2, isExtentSigned = 1, opExtentBits = 9,
2348     CextOpcode = "mpyi", InputType = "imm", hasNewValue = 1 in
2349 def M2_mpysmi : MInst<(outs IntRegs:$dst), (ins IntRegs:$src1, s9Ext:$src2),
2350     "$dst = mpyi($src1, #$src2)",
2351     [(set (i32 IntRegs:$dst), (mul (i32 IntRegs:$src1),
2352                                    s9ExtPred:$src2))]>, ImmRegRel;
2353
2354 let hasNewValue = 1, isExtendable = 1,  opExtentBits = 8, opExtendable = 3,
2355     InputType = "imm" in
2356 class T_MType_acc_ri <string mnemonic, bits<3> MajOp, Operand ImmOp,
2357                       list<dag> pattern = []>
2358  : MInst < (outs IntRegs:$dst), (ins IntRegs:$src1, IntRegs:$src2, ImmOp:$src3),
2359   "$dst "#mnemonic#"($src2, #$src3)",
2360   pattern, "$src1 = $dst", M_tc_2_SLOT23> {
2361     bits<5> dst;
2362     bits<5> src2;
2363     bits<8> src3;
2364
2365     let IClass = 0b1110;
2366
2367     let Inst{27-26} = 0b00;
2368     let Inst{25-23} = MajOp;
2369     let Inst{20-16} = src2;
2370     let Inst{13} = 0b0;
2371     let Inst{12-5} = src3;
2372     let Inst{4-0} = dst;
2373   }
2374
2375 let InputType = "reg", hasNewValue = 1 in
2376 class T_MType_acc_rr <string mnemonic, bits<3> MajOp, bits<3> MinOp,
2377                       bit isSwap = 0, list<dag> pattern = [], bit hasNot = 0,
2378                       bit isSat = 0, bit isShift = 0>
2379   : MInst < (outs IntRegs:$dst),
2380             (ins IntRegs:$src1, IntRegs:$src2, IntRegs:$src3),
2381   "$dst "#mnemonic#"($src2, "#!if(hasNot, "~$src3)","$src3)")
2382                           #!if(isShift, ":<<1", "")
2383                           #!if(isSat, ":sat", ""),
2384   pattern, "$src1 = $dst", M_tc_2_SLOT23 > {
2385     bits<5> dst;
2386     bits<5> src2;
2387     bits<5> src3;
2388
2389     let IClass = 0b1110;
2390
2391     let Inst{27-24} = 0b1111;
2392     let Inst{23-21} = MajOp;
2393     let Inst{20-16} = !if(isSwap, src3, src2);
2394     let Inst{13} = 0b0;
2395     let Inst{12-8} = !if(isSwap, src2, src3);
2396     let Inst{7-5} = MinOp;
2397     let Inst{4-0} = dst;
2398   }
2399
2400 let CextOpcode = "MPYI_acc", Itinerary = M_tc_3x_SLOT23, isCodeGenOnly = 0 in {
2401   def M2_macsip : T_MType_acc_ri <"+= mpyi", 0b010, u8Ext,
2402                   [(set (i32 IntRegs:$dst),
2403                         (add (mul IntRegs:$src2, u8ExtPred:$src3),
2404                              IntRegs:$src1))]>, ImmRegRel;
2405
2406   def M2_maci   : T_MType_acc_rr <"+= mpyi", 0b000, 0b000, 0,
2407                  [(set (i32 IntRegs:$dst),
2408                        (add (mul IntRegs:$src2, IntRegs:$src3),
2409                             IntRegs:$src1))]>, ImmRegRel;
2410 }
2411
2412 let CextOpcode = "ADD_acc", isCodeGenOnly = 0 in {
2413   let isExtentSigned = 1 in
2414   def M2_accii : T_MType_acc_ri <"+= add", 0b100, s8Ext,
2415                  [(set (i32 IntRegs:$dst),
2416                        (add (add (i32 IntRegs:$src2), s8_16ExtPred:$src3),
2417                             (i32 IntRegs:$src1)))]>, ImmRegRel;
2418
2419   def M2_acci  : T_MType_acc_rr <"+= add",  0b000, 0b001, 0,
2420                  [(set (i32 IntRegs:$dst),
2421                        (add (add (i32 IntRegs:$src2), (i32 IntRegs:$src3)),
2422                             (i32 IntRegs:$src1)))]>, ImmRegRel;
2423 }
2424
2425 let CextOpcode = "SUB_acc", isCodeGenOnly = 0 in {
2426   let isExtentSigned = 1 in
2427   def M2_naccii : T_MType_acc_ri <"-= add", 0b101, s8Ext>, ImmRegRel;
2428
2429   def M2_nacci  : T_MType_acc_rr <"-= add",  0b100, 0b001, 0>, ImmRegRel;
2430 }
2431
2432 let Itinerary = M_tc_3x_SLOT23, isCodeGenOnly = 0 in
2433 def M2_macsin : T_MType_acc_ri <"-= mpyi", 0b011, u8Ext>;
2434
2435 let isCodeGenOnly = 0 in {
2436 def M2_xor_xacc : T_MType_acc_rr < "^= xor", 0b100, 0b011, 0>;
2437 def M2_subacc : T_MType_acc_rr <"+= sub",  0b000, 0b011, 1>;
2438 }
2439
2440 class T_MType_acc_pat1 <InstHexagon MI, SDNode firstOp, SDNode secOp,
2441                         PatLeaf ImmPred>
2442   : Pat <(secOp IntRegs:$src1, (firstOp IntRegs:$src2, ImmPred:$src3)),
2443          (MI IntRegs:$src1, IntRegs:$src2, ImmPred:$src3)>;
2444
2445 class T_MType_acc_pat2 <InstHexagon MI, SDNode firstOp, SDNode secOp>
2446   : Pat <(i32 (secOp IntRegs:$src1, (firstOp IntRegs:$src2, IntRegs:$src3))),
2447          (MI IntRegs:$src1, IntRegs:$src2, IntRegs:$src3)>;
2448
2449 def : T_MType_acc_pat2 <M2_xor_xacc, xor, xor>;
2450 def : T_MType_acc_pat1 <M2_macsin, mul, sub, u8ExtPred>;
2451
2452 def : T_MType_acc_pat1 <M2_naccii, add, sub, s8_16ExtPred>;
2453 def : T_MType_acc_pat2 <M2_nacci, add, sub>;
2454 //===----------------------------------------------------------------------===//
2455 // Template Class -- Multiply signed/unsigned halfwords with and without
2456 // saturation and rounding
2457 //===----------------------------------------------------------------------===//
2458 class T_M2_mpyd < bits<2> LHbits, bit isRnd, bit hasShift, bit isUnsigned >
2459   : MInst < (outs DoubleRegs:$Rdd), (ins IntRegs:$Rs, IntRegs:$Rt),
2460   "$Rdd = "#!if(isUnsigned,"mpyu","mpy")#"($Rs."#!if(LHbits{1},"h","l")
2461                                        #", $Rt."#!if(LHbits{0},"h)","l)")
2462                                        #!if(hasShift,":<<1","")
2463                                        #!if(isRnd,":rnd",""),
2464   [] > {
2465     bits<5> Rdd;
2466     bits<5> Rs;
2467     bits<5> Rt;
2468
2469     let IClass = 0b1110;
2470
2471     let Inst{27-24} = 0b0100;
2472     let Inst{23} = hasShift;
2473     let Inst{22} = isUnsigned;
2474     let Inst{21} = isRnd;
2475     let Inst{6-5} = LHbits;
2476     let Inst{4-0} = Rdd;
2477     let Inst{20-16} = Rs;
2478     let Inst{12-8} = Rt;
2479 }
2480
2481 let isCodeGenOnly = 0 in {
2482 def M2_mpyd_hh_s0: T_M2_mpyd<0b11, 0, 0, 0>;
2483 def M2_mpyd_hl_s0: T_M2_mpyd<0b10, 0, 0, 0>;
2484 def M2_mpyd_lh_s0: T_M2_mpyd<0b01, 0, 0, 0>;
2485 def M2_mpyd_ll_s0: T_M2_mpyd<0b00, 0, 0, 0>;
2486
2487 def M2_mpyd_hh_s1: T_M2_mpyd<0b11, 0, 1, 0>;
2488 def M2_mpyd_hl_s1: T_M2_mpyd<0b10, 0, 1, 0>;
2489 def M2_mpyd_lh_s1: T_M2_mpyd<0b01, 0, 1, 0>;
2490 def M2_mpyd_ll_s1: T_M2_mpyd<0b00, 0, 1, 0>;
2491
2492 def M2_mpyd_rnd_hh_s0: T_M2_mpyd<0b11, 1, 0, 0>;
2493 def M2_mpyd_rnd_hl_s0: T_M2_mpyd<0b10, 1, 0, 0>;
2494 def M2_mpyd_rnd_lh_s0: T_M2_mpyd<0b01, 1, 0, 0>;
2495 def M2_mpyd_rnd_ll_s0: T_M2_mpyd<0b00, 1, 0, 0>;
2496
2497 def M2_mpyd_rnd_hh_s1: T_M2_mpyd<0b11, 1, 1, 0>;
2498 def M2_mpyd_rnd_hl_s1: T_M2_mpyd<0b10, 1, 1, 0>;
2499 def M2_mpyd_rnd_lh_s1: T_M2_mpyd<0b01, 1, 1, 0>;
2500 def M2_mpyd_rnd_ll_s1: T_M2_mpyd<0b00, 1, 1, 0>;
2501
2502 //Rdd=mpyu(Rs.[HL],Rt.[HL])[:<<1]
2503 def M2_mpyud_hh_s0: T_M2_mpyd<0b11, 0, 0, 1>;
2504 def M2_mpyud_hl_s0: T_M2_mpyd<0b10, 0, 0, 1>;
2505 def M2_mpyud_lh_s0: T_M2_mpyd<0b01, 0, 0, 1>;
2506 def M2_mpyud_ll_s0: T_M2_mpyd<0b00, 0, 0, 1>;
2507
2508 def M2_mpyud_hh_s1: T_M2_mpyd<0b11, 0, 1, 1>;
2509 def M2_mpyud_hl_s1: T_M2_mpyd<0b10, 0, 1, 1>;
2510 def M2_mpyud_lh_s1: T_M2_mpyd<0b01, 0, 1, 1>;
2511 def M2_mpyud_ll_s1: T_M2_mpyd<0b00, 0, 1, 1>;
2512 }
2513 //===----------------------------------------------------------------------===//
2514 // Template Class for xtype mpy:
2515 // Vector multiply
2516 // Complex multiply
2517 // multiply 32X32 and use full result
2518 //===----------------------------------------------------------------------===//
2519 let hasSideEffects = 0 in
2520 class T_XTYPE_mpy64 <string mnemonic, bits<3> MajOp, bits<3> MinOp,
2521                      bit isSat, bit hasShift, bit isConj>
2522    : MInst <(outs DoubleRegs:$Rdd),
2523             (ins IntRegs:$Rs, IntRegs:$Rt),
2524   "$Rdd = "#mnemonic#"($Rs, $Rt"#!if(isConj,"*)",")")
2525                                 #!if(hasShift,":<<1","")
2526                                 #!if(isSat,":sat",""),
2527   [] > {
2528     bits<5> Rdd;
2529     bits<5> Rs;
2530     bits<5> Rt;
2531
2532     let IClass = 0b1110;
2533
2534     let Inst{27-24} = 0b0101;
2535     let Inst{23-21} = MajOp;
2536     let Inst{20-16} = Rs;
2537     let Inst{12-8} = Rt;
2538     let Inst{7-5} = MinOp;
2539     let Inst{4-0} = Rdd;
2540   }
2541
2542 //===----------------------------------------------------------------------===//
2543 // Template Class for xtype mpy with accumulation into 64-bit:
2544 // Vector multiply
2545 // Complex multiply
2546 // multiply 32X32 and use full result
2547 //===----------------------------------------------------------------------===//
2548 class T_XTYPE_mpy64_acc <string op1, string op2, bits<3> MajOp, bits<3> MinOp,
2549                          bit isSat, bit hasShift, bit isConj>
2550   : MInst <(outs DoubleRegs:$Rxx),
2551            (ins DoubleRegs:$dst2, IntRegs:$Rs, IntRegs:$Rt),
2552   "$Rxx "#op2#"= "#op1#"($Rs, $Rt"#!if(isConj,"*)",")")
2553                                    #!if(hasShift,":<<1","")
2554                                    #!if(isSat,":sat",""),
2555
2556   [] , "$dst2 = $Rxx" > {
2557     bits<5> Rxx;
2558     bits<5> Rs;
2559     bits<5> Rt;
2560
2561     let IClass = 0b1110;
2562
2563     let Inst{27-24} = 0b0111;
2564     let Inst{23-21} = MajOp;
2565     let Inst{20-16} = Rs;
2566     let Inst{12-8} = Rt;
2567     let Inst{7-5} = MinOp;
2568     let Inst{4-0} = Rxx;
2569   }
2570
2571 // MPY - Multiply and use full result
2572 // Rdd = mpy[u](Rs,Rt)
2573 let isCodeGenOnly = 0 in {
2574 def M2_dpmpyss_s0 : T_XTYPE_mpy64 < "mpy", 0b000, 0b000, 0, 0, 0>;
2575 def M2_dpmpyuu_s0 : T_XTYPE_mpy64 < "mpyu", 0b010, 0b000, 0, 0, 0>;
2576
2577 // Rxx[+-]= mpy[u](Rs,Rt)
2578 def M2_dpmpyss_acc_s0 : T_XTYPE_mpy64_acc < "mpy",  "+", 0b000, 0b000, 0, 0, 0>;
2579 def M2_dpmpyss_nac_s0 : T_XTYPE_mpy64_acc < "mpy",  "-", 0b001, 0b000, 0, 0, 0>;
2580 def M2_dpmpyuu_acc_s0 : T_XTYPE_mpy64_acc < "mpyu", "+", 0b010, 0b000, 0, 0, 0>;
2581 def M2_dpmpyuu_nac_s0 : T_XTYPE_mpy64_acc < "mpyu", "-", 0b011, 0b000, 0, 0, 0>;
2582 }
2583
2584 def: Pat<(i64 (mul (i64 (anyext (i32 IntRegs:$src1))),
2585                    (i64 (anyext (i32 IntRegs:$src2))))),
2586          (M2_dpmpyuu_s0 IntRegs:$src1, IntRegs:$src2)>;
2587
2588 def: Pat<(i64 (mul (i64 (sext (i32 IntRegs:$src1))),
2589                    (i64 (sext (i32 IntRegs:$src2))))),
2590          (M2_dpmpyss_s0 IntRegs:$src1, IntRegs:$src2)>;
2591
2592 def: Pat<(i64 (mul (is_sext_i32:$src1),
2593                    (is_sext_i32:$src2))),
2594          (M2_dpmpyss_s0 (LoReg DoubleRegs:$src1), (LoReg DoubleRegs:$src2))>;
2595
2596 // Multiply and accumulate, use full result.
2597 // Rxx[+-]=mpy(Rs,Rt)
2598
2599 def: Pat<(i64 (add (i64 DoubleRegs:$src1),
2600                    (mul (i64 (sext (i32 IntRegs:$src2))),
2601                         (i64 (sext (i32 IntRegs:$src3)))))),
2602          (M2_dpmpyss_acc_s0 DoubleRegs:$src1, IntRegs:$src2, IntRegs:$src3)>;
2603
2604 def: Pat<(i64 (sub (i64 DoubleRegs:$src1),
2605                    (mul (i64 (sext (i32 IntRegs:$src2))),
2606                         (i64 (sext (i32 IntRegs:$src3)))))),
2607          (M2_dpmpyss_nac_s0 DoubleRegs:$src1, IntRegs:$src2, IntRegs:$src3)>;
2608
2609 def: Pat<(i64 (add (i64 DoubleRegs:$src1),
2610                    (mul (i64 (anyext (i32 IntRegs:$src2))),
2611                         (i64 (anyext (i32 IntRegs:$src3)))))),
2612          (M2_dpmpyuu_acc_s0 DoubleRegs:$src1, IntRegs:$src2, IntRegs:$src3)>;
2613
2614 def: Pat<(i64 (add (i64 DoubleRegs:$src1),
2615                    (mul (i64 (zext (i32 IntRegs:$src2))),
2616                         (i64 (zext (i32 IntRegs:$src3)))))),
2617          (M2_dpmpyuu_acc_s0 DoubleRegs:$src1, IntRegs:$src2, IntRegs:$src3)>;
2618
2619 def: Pat<(i64 (sub (i64 DoubleRegs:$src1),
2620                    (mul (i64 (anyext (i32 IntRegs:$src2))),
2621                         (i64 (anyext (i32 IntRegs:$src3)))))),
2622          (M2_dpmpyuu_nac_s0 DoubleRegs:$src1, IntRegs:$src2, IntRegs:$src3)>;
2623
2624 def: Pat<(i64 (sub (i64 DoubleRegs:$src1),
2625                    (mul (i64 (zext (i32 IntRegs:$src2))),
2626                         (i64 (zext (i32 IntRegs:$src3)))))),
2627          (M2_dpmpyuu_nac_s0 DoubleRegs:$src1, IntRegs:$src2, IntRegs:$src3)>;
2628
2629 //===----------------------------------------------------------------------===//
2630 // MTYPE/MPYH -
2631 //===----------------------------------------------------------------------===//
2632
2633 //===----------------------------------------------------------------------===//
2634 // MTYPE/MPYS +
2635 //===----------------------------------------------------------------------===//
2636 //===----------------------------------------------------------------------===//
2637 // MTYPE/MPYS -
2638 //===----------------------------------------------------------------------===//
2639
2640 //===----------------------------------------------------------------------===//
2641 // MTYPE/VB +
2642 //===----------------------------------------------------------------------===//
2643 //===----------------------------------------------------------------------===//
2644 // MTYPE/VB -
2645 //===----------------------------------------------------------------------===//
2646
2647 //===----------------------------------------------------------------------===//
2648 // MTYPE/VH  +
2649 //===----------------------------------------------------------------------===//
2650 //===----------------------------------------------------------------------===//
2651 // MTYPE/VH  -
2652 //===----------------------------------------------------------------------===//
2653
2654 //===----------------------------------------------------------------------===//
2655 // ST +
2656 //===----------------------------------------------------------------------===//
2657 ///
2658 // Store doubleword.
2659 //===----------------------------------------------------------------------===//
2660 // Template class for non-predicated post increment stores with immediate offset
2661 //===----------------------------------------------------------------------===//
2662 let isPredicable = 1, hasSideEffects = 0, addrMode = PostInc in
2663 class T_store_pi <string mnemonic, RegisterClass RC, Operand ImmOp,
2664                  bits<4> MajOp, bit isHalf >
2665   : STInst <(outs IntRegs:$_dst_),
2666             (ins IntRegs:$src1, ImmOp:$offset, RC:$src2),
2667   mnemonic#"($src1++#$offset) = $src2"#!if(isHalf, ".h", ""),
2668   [], "$src1 = $_dst_" >,
2669   AddrModeRel {
2670     bits<5> src1;
2671     bits<5> src2;
2672     bits<7> offset;
2673     bits<4> offsetBits;
2674
2675     string ImmOpStr = !cast<string>(ImmOp);
2676     let offsetBits = !if (!eq(ImmOpStr, "s4_3Imm"), offset{6-3},
2677                      !if (!eq(ImmOpStr, "s4_2Imm"), offset{5-2},
2678                      !if (!eq(ImmOpStr, "s4_1Imm"), offset{4-1},
2679                                       /* s4_0Imm */ offset{3-0})));
2680     let isNVStorable = !if (!eq(ImmOpStr, "s4_3Imm"), 0, 1);
2681
2682     let IClass = 0b1010;
2683
2684     let Inst{27-25} = 0b101;
2685     let Inst{24-21} = MajOp;
2686     let Inst{20-16} = src1;
2687     let Inst{13}    = 0b0;
2688     let Inst{12-8}  = src2;
2689     let Inst{7}     = 0b0;
2690     let Inst{6-3}   = offsetBits;
2691     let Inst{1}     = 0b0;
2692   }
2693
2694 //===----------------------------------------------------------------------===//
2695 // Template class for predicated post increment stores with immediate offset
2696 //===----------------------------------------------------------------------===//
2697 let isPredicated = 1, hasSideEffects = 0, addrMode = PostInc in
2698 class T_pstore_pi <string mnemonic, RegisterClass RC, Operand ImmOp,
2699                       bits<4> MajOp, bit isHalf, bit isPredNot, bit isPredNew >
2700   : STInst <(outs IntRegs:$_dst_),
2701             (ins PredRegs:$src1, IntRegs:$src2, ImmOp:$offset, RC:$src3),
2702   !if(isPredNot, "if (!$src1", "if ($src1")#!if(isPredNew, ".new) ",
2703   ") ")#mnemonic#"($src2++#$offset) = $src3"#!if(isHalf, ".h", ""),
2704   [], "$src2 = $_dst_" >,
2705   AddrModeRel {
2706     bits<2> src1;
2707     bits<5> src2;
2708     bits<7> offset;
2709     bits<5> src3;
2710     bits<4> offsetBits;
2711
2712     string ImmOpStr = !cast<string>(ImmOp);
2713     let offsetBits = !if (!eq(ImmOpStr, "s4_3Imm"), offset{6-3},
2714                      !if (!eq(ImmOpStr, "s4_2Imm"), offset{5-2},
2715                      !if (!eq(ImmOpStr, "s4_1Imm"), offset{4-1},
2716                                       /* s4_0Imm */ offset{3-0})));
2717
2718     let isNVStorable = !if (!eq(ImmOpStr, "s4_3Imm"), 0, 1);
2719     let isPredicatedNew = isPredNew;
2720     let isPredicatedFalse = isPredNot;
2721
2722     let IClass = 0b1010;
2723
2724     let Inst{27-25} = 0b101;
2725     let Inst{24-21} = MajOp;
2726     let Inst{20-16} = src2;
2727     let Inst{13} = 0b1;
2728     let Inst{12-8} = src3;
2729     let Inst{7} = isPredNew;
2730     let Inst{6-3} = offsetBits;
2731     let Inst{2} = isPredNot;
2732     let Inst{1-0} = src1;
2733   }
2734
2735 multiclass ST_PostInc<string mnemonic, string BaseOp, RegisterClass RC,
2736                       Operand ImmOp, bits<4> MajOp, bit isHalf = 0 > {
2737
2738   let BaseOpcode = "POST_"#BaseOp in {
2739     def S2_#NAME#_pi : T_store_pi <mnemonic, RC, ImmOp, MajOp, isHalf>;
2740
2741     // Predicated
2742     def S2_p#NAME#t_pi : T_pstore_pi <mnemonic, RC, ImmOp, MajOp, isHalf, 0, 0>;
2743     def S2_p#NAME#f_pi : T_pstore_pi <mnemonic, RC, ImmOp, MajOp, isHalf, 1, 0>;
2744
2745     // Predicated new
2746     def S2_p#NAME#tnew_pi : T_pstore_pi <mnemonic, RC, ImmOp, MajOp,
2747                                           isHalf, 0, 1>;
2748     def S2_p#NAME#fnew_pi : T_pstore_pi <mnemonic, RC, ImmOp, MajOp,
2749                                           isHalf, 1, 1>;
2750   }
2751 }
2752
2753 let accessSize = ByteAccess, isCodeGenOnly = 0 in
2754 defm storerb: ST_PostInc <"memb", "STrib", IntRegs, s4_0Imm, 0b1000>;
2755
2756 //===----------------------------------------------------------------------===//
2757 // Post increment store
2758 //===----------------------------------------------------------------------===//
2759
2760 multiclass ST_PostInc_Pbase<string mnemonic, RegisterClass RC, Operand ImmOp,
2761                             bit isNot, bit isPredNew> {
2762   let isPredicatedNew = isPredNew in
2763   def NAME : STInst2PI<(outs IntRegs:$dst),
2764             (ins PredRegs:$src1, IntRegs:$src2, ImmOp:$offset, RC:$src3),
2765             !if(isNot, "if (!$src1", "if ($src1")#!if(isPredNew, ".new) ",
2766             ") ")#mnemonic#"($src2++#$offset) = $src3",
2767             [],
2768             "$src2 = $dst">;
2769 }
2770
2771 multiclass ST_PostInc_Pred<string mnemonic, RegisterClass RC,
2772                            Operand ImmOp, bit PredNot> {
2773   let isPredicatedFalse = PredNot in {
2774     defm _c#NAME : ST_PostInc_Pbase<mnemonic, RC, ImmOp, PredNot, 0>;
2775     // Predicate new
2776     let Predicates = [HasV4T], validSubTargets = HasV4SubT in
2777     defm _cdn#NAME#_V4 : ST_PostInc_Pbase<mnemonic, RC, ImmOp, PredNot, 1>;
2778   }
2779 }
2780
2781 let hasCtrlDep = 1, isNVStorable = 1, hasSideEffects = 0 in
2782 multiclass ST_PostInc2<string mnemonic, string BaseOp, RegisterClass RC,
2783                       Operand ImmOp> {
2784
2785   let hasCtrlDep = 1, BaseOpcode = "POST_"#BaseOp in {
2786     let isPredicable = 1 in
2787     def NAME : STInst2PI<(outs IntRegs:$dst),
2788                 (ins IntRegs:$src1, ImmOp:$offset, RC:$src2),
2789                 mnemonic#"($src1++#$offset) = $src2",
2790                 [],
2791                 "$src1 = $dst">;
2792
2793     let isPredicated = 1 in {
2794       defm Pt : ST_PostInc_Pred<mnemonic, RC, ImmOp, 0 >;
2795       defm NotPt : ST_PostInc_Pred<mnemonic, RC, ImmOp, 1 >;
2796     }
2797   }
2798 }
2799
2800 defm POST_SThri: ST_PostInc2 <"memh", "STrih", IntRegs, s4_1Imm>, AddrModeRel;
2801 defm POST_STwri: ST_PostInc2 <"memw", "STriw", IntRegs, s4_2Imm>, AddrModeRel;
2802
2803 let isNVStorable = 0 in
2804 defm POST_STdri: ST_PostInc2 <"memd", "STrid", DoubleRegs, s4_3Imm>, AddrModeRel;
2805
2806 def : Pat<(post_truncsti8 (i32 IntRegs:$src1), IntRegs:$src2,
2807                            s4_3ImmPred:$offset),
2808           (S2_storerb_pi IntRegs:$src2, s4_0ImmPred:$offset, IntRegs:$src1)>;
2809
2810 def : Pat<(post_truncsti16 (i32 IntRegs:$src1), IntRegs:$src2,
2811                             s4_3ImmPred:$offset),
2812           (POST_SThri IntRegs:$src2, s4_1ImmPred:$offset, IntRegs:$src1)>;
2813
2814 def : Pat<(post_store (i32 IntRegs:$src1), IntRegs:$src2, s4_2ImmPred:$offset),
2815           (POST_STwri IntRegs:$src2, s4_1ImmPred:$offset, IntRegs:$src1)>;
2816
2817 def : Pat<(post_store (i64 DoubleRegs:$src1), IntRegs:$src2,
2818                        s4_3ImmPred:$offset),
2819           (POST_STdri IntRegs:$src2, s4_3ImmPred:$offset, DoubleRegs:$src1)>;
2820
2821 //===----------------------------------------------------------------------===//
2822 // multiclass for the store instructions with MEMri operand.
2823 //===----------------------------------------------------------------------===//
2824 multiclass ST_MEMri_Pbase<string mnemonic, RegisterClass RC, bit isNot,
2825                           bit isPredNew> {
2826   let isPredicatedNew = isPredNew in
2827   def NAME : STInst2<(outs),
2828             (ins PredRegs:$src1, MEMri:$addr, RC: $src2),
2829             !if(isNot, "if (!$src1", "if ($src1")#!if(isPredNew, ".new) ",
2830             ") ")#mnemonic#"($addr) = $src2",
2831             []>;
2832 }
2833
2834 multiclass ST_MEMri_Pred<string mnemonic, RegisterClass RC, bit PredNot> {
2835   let isPredicatedFalse = PredNot in {
2836     defm _c#NAME : ST_MEMri_Pbase<mnemonic, RC, PredNot, 0>;
2837
2838     // Predicate new
2839     let validSubTargets = HasV4SubT, Predicates = [HasV4T] in
2840     defm _cdn#NAME#_V4 : ST_MEMri_Pbase<mnemonic, RC, PredNot, 1>;
2841   }
2842 }
2843
2844 let isExtendable = 1, isNVStorable = 1, hasSideEffects = 0 in
2845 multiclass ST_MEMri<string mnemonic, string CextOp, RegisterClass RC,
2846                     bits<5> ImmBits, bits<5> PredImmBits> {
2847
2848   let CextOpcode = CextOp, BaseOpcode = CextOp in {
2849     let opExtendable = 1, isExtentSigned = 1, opExtentBits = ImmBits,
2850          isPredicable = 1 in
2851     def NAME : STInst2<(outs),
2852             (ins MEMri:$addr, RC:$src),
2853             mnemonic#"($addr) = $src",
2854             []>;
2855
2856     let opExtendable = 2, isExtentSigned = 0, opExtentBits = PredImmBits,
2857         isPredicated = 1 in {
2858       defm Pt : ST_MEMri_Pred<mnemonic, RC, 0>;
2859       defm NotPt : ST_MEMri_Pred<mnemonic, RC, 1>;
2860     }
2861   }
2862 }
2863
2864 let addrMode = BaseImmOffset, isMEMri = "true" in {
2865   let accessSize = ByteAccess in
2866     defm STrib: ST_MEMri < "memb", "STrib", IntRegs, 11, 6>, AddrModeRel;
2867
2868   let accessSize = HalfWordAccess in
2869     defm STrih: ST_MEMri < "memh", "STrih", IntRegs, 12, 7>, AddrModeRel;
2870
2871   let accessSize = WordAccess in
2872     defm STriw: ST_MEMri < "memw", "STriw", IntRegs, 13, 8>, AddrModeRel;
2873
2874   let accessSize = DoubleWordAccess, isNVStorable = 0 in
2875     defm STrid: ST_MEMri < "memd", "STrid", DoubleRegs, 14, 9>, AddrModeRel;
2876 }
2877
2878 def : Pat<(truncstorei8 (i32 IntRegs:$src1), ADDRriS11_0:$addr),
2879           (STrib ADDRriS11_0:$addr, (i32 IntRegs:$src1))>;
2880
2881 def : Pat<(truncstorei16 (i32 IntRegs:$src1), ADDRriS11_1:$addr),
2882           (STrih ADDRriS11_1:$addr, (i32 IntRegs:$src1))>;
2883
2884 def : Pat<(store (i32 IntRegs:$src1), ADDRriS11_2:$addr),
2885           (STriw ADDRriS11_2:$addr, (i32 IntRegs:$src1))>;
2886
2887 def : Pat<(store (i64 DoubleRegs:$src1), ADDRriS11_3:$addr),
2888           (STrid ADDRriS11_3:$addr, (i64 DoubleRegs:$src1))>;
2889
2890
2891 //===----------------------------------------------------------------------===//
2892 // multiclass for the store instructions with base+immediate offset
2893 // addressing mode
2894 //===----------------------------------------------------------------------===//
2895 multiclass ST_Idxd_Pbase<string mnemonic, RegisterClass RC, Operand predImmOp,
2896                         bit isNot, bit isPredNew> {
2897   let isPredicatedNew = isPredNew in
2898   def NAME : STInst2<(outs),
2899             (ins PredRegs:$src1, IntRegs:$src2, predImmOp:$src3, RC: $src4),
2900             !if(isNot, "if (!$src1", "if ($src1")#!if(isPredNew, ".new) ",
2901             ") ")#mnemonic#"($src2+#$src3) = $src4",
2902             []>;
2903 }
2904
2905 multiclass ST_Idxd_Pred<string mnemonic, RegisterClass RC, Operand predImmOp,
2906                         bit PredNot> {
2907   let isPredicatedFalse = PredNot, isPredicated = 1 in {
2908     defm _c#NAME : ST_Idxd_Pbase<mnemonic, RC, predImmOp, PredNot, 0>;
2909
2910     // Predicate new
2911     let validSubTargets = HasV4SubT, Predicates = [HasV4T] in
2912     defm _cdn#NAME#_V4 : ST_Idxd_Pbase<mnemonic, RC, predImmOp, PredNot, 1>;
2913   }
2914 }
2915
2916 let isExtendable = 1, isNVStorable = 1, hasSideEffects = 0 in
2917 multiclass ST_Idxd<string mnemonic, string CextOp, RegisterClass RC,
2918                    Operand ImmOp, Operand predImmOp, bits<5> ImmBits,
2919                    bits<5> PredImmBits> {
2920
2921   let CextOpcode = CextOp, BaseOpcode = CextOp#_indexed in {
2922     let opExtendable = 1, isExtentSigned = 1, opExtentBits = ImmBits,
2923          isPredicable = 1 in
2924     def NAME : STInst2<(outs),
2925             (ins IntRegs:$src1, ImmOp:$src2, RC:$src3),
2926             mnemonic#"($src1+#$src2) = $src3",
2927             []>;
2928
2929     let opExtendable = 2, isExtentSigned = 0, opExtentBits = PredImmBits in {
2930       defm Pt : ST_Idxd_Pred<mnemonic, RC, predImmOp, 0>;
2931       defm NotPt : ST_Idxd_Pred<mnemonic, RC, predImmOp, 1>;
2932     }
2933   }
2934 }
2935
2936 let addrMode = BaseImmOffset, InputType = "reg" in {
2937   let accessSize = ByteAccess in
2938     defm STrib_indexed: ST_Idxd < "memb", "STrib", IntRegs, s11_0Ext,
2939                                   u6_0Ext, 11, 6>, AddrModeRel, ImmRegRel;
2940
2941   let accessSize = HalfWordAccess in
2942     defm STrih_indexed: ST_Idxd < "memh", "STrih", IntRegs, s11_1Ext,
2943                                   u6_1Ext, 12, 7>, AddrModeRel, ImmRegRel;
2944
2945   let accessSize = WordAccess in
2946     defm STriw_indexed: ST_Idxd < "memw", "STriw", IntRegs, s11_2Ext,
2947                                   u6_2Ext, 13, 8>, AddrModeRel, ImmRegRel;
2948
2949   let accessSize = DoubleWordAccess, isNVStorable = 0 in
2950     defm STrid_indexed: ST_Idxd < "memd", "STrid", DoubleRegs, s11_3Ext,
2951                                   u6_3Ext, 14, 9>, AddrModeRel;
2952 }
2953
2954 let AddedComplexity = 10 in {
2955 def : Pat<(truncstorei8 (i32 IntRegs:$src1), (add IntRegs:$src2,
2956                                                   s11_0ExtPred:$offset)),
2957           (STrib_indexed IntRegs:$src2, s11_0ImmPred:$offset,
2958                          (i32 IntRegs:$src1))>;
2959
2960 def : Pat<(truncstorei16 (i32 IntRegs:$src1), (add IntRegs:$src2,
2961                                                    s11_1ExtPred:$offset)),
2962           (STrih_indexed IntRegs:$src2, s11_1ImmPred:$offset,
2963                          (i32 IntRegs:$src1))>;
2964
2965 def : Pat<(store (i32 IntRegs:$src1), (add IntRegs:$src2,
2966                                            s11_2ExtPred:$offset)),
2967           (STriw_indexed IntRegs:$src2, s11_2ImmPred:$offset,
2968                          (i32 IntRegs:$src1))>;
2969
2970 def : Pat<(store (i64 DoubleRegs:$src1), (add IntRegs:$src2,
2971                                               s11_3ExtPred:$offset)),
2972           (STrid_indexed IntRegs:$src2, s11_3ImmPred:$offset,
2973                          (i64 DoubleRegs:$src1))>;
2974 }
2975
2976 // memh(Rx++#s4:1)=Rt.H
2977
2978 // Store word.
2979 // Store predicate.
2980 let Defs = [R10,R11,D5], hasSideEffects = 0 in
2981 def STriw_pred : STInst2<(outs),
2982             (ins MEMri:$addr, PredRegs:$src1),
2983             "Error; should not emit",
2984             []>;
2985
2986 // Allocate stack frame.
2987 let Defs = [R29, R30], Uses = [R31, R30], hasSideEffects = 0 in {
2988   def ALLOCFRAME : STInst2<(outs),
2989              (ins i32imm:$amt),
2990              "allocframe(#$amt)",
2991              []>;
2992 }
2993 //===----------------------------------------------------------------------===//
2994 // ST -
2995 //===----------------------------------------------------------------------===//
2996
2997 //===----------------------------------------------------------------------===//
2998 // STYPE/ALU +
2999 //===----------------------------------------------------------------------===//
3000 // Logical NOT.
3001 def NOT_rr64 : ALU64_rr<(outs DoubleRegs:$dst), (ins DoubleRegs:$src1),
3002                "$dst = not($src1)",
3003                [(set (i64 DoubleRegs:$dst), (not (i64 DoubleRegs:$src1)))]>;
3004
3005
3006 //===----------------------------------------------------------------------===//
3007 // STYPE/ALU -
3008 //===----------------------------------------------------------------------===//
3009
3010 let hasSideEffects = 0 in
3011 class T_S2op_1 <string mnemonic, bits<4> RegTyBits, RegisterClass RCOut,
3012                 RegisterClass RCIn, bits<2> MajOp, bits<3> MinOp, bit isSat>
3013   : SInst <(outs RCOut:$dst), (ins RCIn:$src),
3014   "$dst = "#mnemonic#"($src)"#!if(isSat, ":sat", ""),
3015   [], "", S_2op_tc_1_SLOT23 > {
3016     bits<5> dst;
3017     bits<5> src;
3018
3019     let IClass = 0b1000;
3020
3021     let Inst{27-24} = RegTyBits;
3022     let Inst{23-22} = MajOp;
3023     let Inst{21} = 0b0;
3024     let Inst{20-16} = src;
3025     let Inst{7-5} = MinOp;
3026     let Inst{4-0} = dst;
3027   }
3028
3029 class T_S2op_1_di <string mnemonic, bits<2> MajOp, bits<3> MinOp>
3030   : T_S2op_1 <mnemonic, 0b0100, DoubleRegs, IntRegs, MajOp, MinOp, 0>;
3031
3032 let hasNewValue = 1 in
3033 class T_S2op_1_id <string mnemonic, bits<2> MajOp, bits<3> MinOp, bit isSat = 0>
3034   : T_S2op_1 <mnemonic, 0b1000, IntRegs, DoubleRegs, MajOp, MinOp, isSat>;
3035
3036 let hasNewValue = 1 in
3037 class T_S2op_1_ii <string mnemonic, bits<2> MajOp, bits<3> MinOp, bit isSat = 0>
3038   : T_S2op_1 <mnemonic, 0b1100, IntRegs, IntRegs, MajOp, MinOp, isSat>;
3039
3040 // Sign extend word to doubleword
3041 let isCodeGenOnly = 0 in
3042 def A2_sxtw   : T_S2op_1_di <"sxtw", 0b01, 0b000>;
3043
3044 def: Pat <(i64 (sext I32:$src)), (A2_sxtw I32:$src)>;
3045
3046 // Swizzle the bytes of a word
3047 let isCodeGenOnly = 0 in
3048 def A2_swiz : T_S2op_1_ii <"swiz", 0b10, 0b111>;
3049
3050 // Saturate
3051 let Defs = [USR_OVF], isCodeGenOnly = 0 in {
3052   def A2_sat   : T_S2op_1_id <"sat", 0b11, 0b000>;
3053   def A2_satb  : T_S2op_1_ii <"satb", 0b11, 0b111>;
3054   def A2_satub : T_S2op_1_ii <"satub", 0b11, 0b110>;
3055   def A2_sath  : T_S2op_1_ii <"sath", 0b11, 0b100>;
3056   def A2_satuh : T_S2op_1_ii <"satuh", 0b11, 0b101>;
3057 }
3058
3059 let Itinerary = S_2op_tc_2_SLOT23, isCodeGenOnly = 0 in {
3060   // Absolute value word
3061   def A2_abs    : T_S2op_1_ii <"abs", 0b10, 0b100>;
3062
3063   let Defs = [USR_OVF] in
3064   def A2_abssat : T_S2op_1_ii <"abs", 0b10, 0b101, 1>;
3065
3066   // Negate with saturation
3067   let Defs = [USR_OVF] in
3068   def A2_negsat : T_S2op_1_ii <"neg", 0b10, 0b110, 1>;
3069 }
3070
3071 def: Pat<(i32 (select (i1 (setlt (i32 IntRegs:$src), 0)),
3072                       (i32 (sub 0, (i32 IntRegs:$src))),
3073                       (i32 IntRegs:$src))),
3074          (A2_abs IntRegs:$src)>;
3075
3076 let AddedComplexity = 50 in
3077 def: Pat<(i32 (xor (add (sra (i32 IntRegs:$src), (i32 31)),
3078                         (i32 IntRegs:$src)),
3079                    (sra (i32 IntRegs:$src), (i32 31)))),
3080          (A2_abs IntRegs:$src)>;
3081
3082 class T_S2op_2 <string mnemonic, bits<4> RegTyBits, RegisterClass RCOut,
3083                 RegisterClass RCIn, bits<3> MajOp, bits<3> MinOp,
3084                 bit isSat, bit isRnd, list<dag> pattern = []>
3085   : SInst <(outs RCOut:$dst),
3086   (ins RCIn:$src, u5Imm:$u5),
3087   "$dst = "#mnemonic#"($src, #$u5)"#!if(isSat, ":sat", "")
3088                                    #!if(isRnd, ":rnd", ""),
3089   pattern, "", S_2op_tc_2_SLOT23> {
3090     bits<5> dst;
3091     bits<5> src;
3092     bits<5> u5;
3093
3094     let IClass = 0b1000;
3095
3096     let Inst{27-24} = RegTyBits;
3097     let Inst{23-21} = MajOp;
3098     let Inst{20-16} = src;
3099     let Inst{13} = 0b0;
3100     let Inst{12-8} = u5;
3101     let Inst{7-5} = MinOp;
3102     let Inst{4-0} = dst;
3103   }
3104   
3105 let hasNewValue = 1 in
3106 class T_S2op_2_ii <string mnemonic, bits<3> MajOp, bits<3> MinOp,
3107                    bit isSat = 0, bit isRnd = 0, list<dag> pattern = []>
3108   : T_S2op_2 <mnemonic, 0b1100, IntRegs, IntRegs, MajOp, MinOp,
3109               isSat, isRnd, pattern>;
3110
3111 class T_S2op_shift <string mnemonic, bits<3> MajOp, bits<3> MinOp, SDNode OpNd>
3112   : T_S2op_2_ii <mnemonic, MajOp, MinOp, 0, 0,
3113     [(set (i32 IntRegs:$dst), (OpNd (i32 IntRegs:$src),
3114                                     (u5ImmPred:$u5)))]>;
3115
3116 // Arithmetic/logical shift right/left by immediate
3117 let Itinerary = S_2op_tc_1_SLOT23, isCodeGenOnly = 0 in {
3118   def S2_asr_i_r : T_S2op_shift <"asr", 0b000, 0b000, sra>;
3119   def S2_lsr_i_r : T_S2op_shift <"lsr", 0b000, 0b001, srl>;
3120   def S2_asl_i_r : T_S2op_shift <"asl", 0b000, 0b010, shl>;
3121 }
3122
3123 // Shift left by immediate with saturation
3124 let Defs = [USR_OVF], isCodeGenOnly = 0 in
3125 def S2_asl_i_r_sat : T_S2op_2_ii <"asl", 0b010, 0b010, 1>;
3126
3127 // Shift right with round
3128 let isCodeGenOnly = 0 in
3129 def S2_asr_i_r_rnd : T_S2op_2_ii <"asr", 0b010, 0b000, 0, 1>;
3130
3131 def: Pat<(i32 (sra (i32 (add (i32 (sra I32:$src1, u5ImmPred:$src2)),
3132                              (i32 1))),
3133                    (i32 1))),
3134          (S2_asr_i_r_rnd IntRegs:$src1, u5ImmPred:$src2)>;
3135
3136 class T_S2op_3<string opc, bits<2>MajOp, bits<3>minOp, bits<1> sat = 0>
3137   : SInst<(outs DoubleRegs:$Rdd), (ins DoubleRegs:$Rss),
3138            "$Rdd = "#opc#"($Rss)"#!if(!eq(sat, 1),":sat","")> {
3139   bits<5> Rss;
3140   bits<5> Rdd;
3141   let IClass = 0b1000;
3142   let Inst{27-24} = 0;
3143   let Inst{23-22} = MajOp;
3144   let Inst{20-16} = Rss;
3145   let Inst{7-5} = minOp;
3146   let Inst{4-0} = Rdd;
3147 }
3148
3149 let isCodeGenOnly = 0 in {
3150 def A2_absp : T_S2op_3 <"abs", 0b10, 0b110>;
3151 def A2_negp : T_S2op_3 <"neg", 0b10, 0b101>;
3152 def A2_notp : T_S2op_3 <"not", 0b10, 0b100>;
3153 }
3154
3155 // Innterleave/deinterleave
3156 let isCodeGenOnly = 0 in {
3157 def S2_interleave   : T_S2op_3 <"interleave",   0b11, 0b101>;
3158 def S2_deinterleave : T_S2op_3 <"deinterleave", 0b11, 0b100>;
3159 }
3160
3161 //===----------------------------------------------------------------------===//
3162 // STYPE/BIT +
3163 //===----------------------------------------------------------------------===//
3164 // Bit count
3165
3166 let hasSideEffects = 0, hasNewValue = 1 in
3167 class T_COUNT_LEADING<string MnOp, bits<3> MajOp, bits<3> MinOp, bit Is32,
3168                 dag Out, dag Inp>
3169     : SInst<Out, Inp, "$Rd = "#MnOp#"($Rs)", [], "", S_2op_tc_1_SLOT23> {
3170   bits<5> Rs;
3171   bits<5> Rd;
3172   let IClass = 0b1000;
3173   let Inst{27} = 0b1;
3174   let Inst{26} = Is32;
3175   let Inst{25-24} = 0b00;
3176   let Inst{23-21} = MajOp;
3177   let Inst{20-16} = Rs;
3178   let Inst{7-5} = MinOp;
3179   let Inst{4-0} = Rd;
3180 }
3181
3182 class T_COUNT_LEADING_32<string MnOp, bits<3> MajOp, bits<3> MinOp>
3183     : T_COUNT_LEADING<MnOp, MajOp, MinOp, 0b1,
3184                       (outs IntRegs:$Rd), (ins IntRegs:$Rs)>;
3185
3186 class T_COUNT_LEADING_64<string MnOp, bits<3> MajOp, bits<3> MinOp>
3187     : T_COUNT_LEADING<MnOp, MajOp, MinOp, 0b0,
3188                       (outs IntRegs:$Rd), (ins DoubleRegs:$Rs)>;
3189
3190 let isCodeGenOnly = 0 in {
3191 def S2_cl0     : T_COUNT_LEADING_32<"cl0",     0b000, 0b101>;
3192 def S2_cl1     : T_COUNT_LEADING_32<"cl1",     0b000, 0b110>;
3193 def S2_ct0     : T_COUNT_LEADING_32<"ct0",     0b010, 0b100>;
3194 def S2_ct1     : T_COUNT_LEADING_32<"ct1",     0b010, 0b101>;
3195 def S2_cl0p    : T_COUNT_LEADING_64<"cl0",     0b010, 0b010>;
3196 def S2_cl1p    : T_COUNT_LEADING_64<"cl1",     0b010, 0b100>;
3197 def S2_clb     : T_COUNT_LEADING_32<"clb",     0b000, 0b100>;
3198 def S2_clbp    : T_COUNT_LEADING_64<"clb",     0b010, 0b000>;
3199 def S2_clbnorm : T_COUNT_LEADING_32<"normamt", 0b000, 0b111>;
3200 }
3201
3202 def: Pat<(i32 (ctlz I32:$Rs)),                (S2_cl0 I32:$Rs)>;
3203 def: Pat<(i32 (ctlz (not I32:$Rs))),          (S2_cl1 I32:$Rs)>;
3204 def: Pat<(i32 (cttz I32:$Rs)),                (S2_ct0 I32:$Rs)>;
3205 def: Pat<(i32 (cttz (not I32:$Rs))),          (S2_ct1 I32:$Rs)>;
3206 def: Pat<(i32 (trunc (ctlz I64:$Rss))),       (S2_cl0p I64:$Rss)>;
3207 def: Pat<(i32 (trunc (ctlz (not I64:$Rss)))), (S2_cl1p I64:$Rss)>;
3208
3209 // Bit set/clear/toggle
3210
3211 let hasSideEffects = 0, hasNewValue = 1 in
3212 class T_SCT_BIT_IMM<string MnOp, bits<3> MinOp>
3213     : SInst<(outs IntRegs:$Rd), (ins IntRegs:$Rs, u5Imm:$u5),
3214             "$Rd = "#MnOp#"($Rs, #$u5)", [], "", S_2op_tc_1_SLOT23> {
3215   bits<5> Rd;
3216   bits<5> Rs;
3217   bits<5> u5;
3218   let IClass = 0b1000;
3219   let Inst{27-21} = 0b1100110;
3220   let Inst{20-16} = Rs;
3221   let Inst{13} = 0b0;
3222   let Inst{12-8} = u5;
3223   let Inst{7-5} = MinOp;
3224   let Inst{4-0} = Rd;
3225 }
3226
3227 let hasSideEffects = 0, hasNewValue = 1 in
3228 class T_SCT_BIT_REG<string MnOp, bits<2> MinOp>
3229     : SInst<(outs IntRegs:$Rd), (ins IntRegs:$Rs, IntRegs:$Rt),
3230             "$Rd = "#MnOp#"($Rs, $Rt)", [], "", S_3op_tc_1_SLOT23> {
3231   bits<5> Rd;
3232   bits<5> Rs;
3233   bits<5> Rt;
3234   let IClass = 0b1100;
3235   let Inst{27-22} = 0b011010;
3236   let Inst{20-16} = Rs;
3237   let Inst{12-8} = Rt;
3238   let Inst{7-6} = MinOp;
3239   let Inst{4-0} = Rd;
3240 }
3241
3242 let isCodeGenOnly = 0 in {
3243 def S2_clrbit_i    : T_SCT_BIT_IMM<"clrbit",    0b001>;
3244 def S2_setbit_i    : T_SCT_BIT_IMM<"setbit",    0b000>;
3245 def S2_togglebit_i : T_SCT_BIT_IMM<"togglebit", 0b010>;
3246 def S2_clrbit_r    : T_SCT_BIT_REG<"clrbit",    0b01>;
3247 def S2_setbit_r    : T_SCT_BIT_REG<"setbit",    0b00>;
3248 def S2_togglebit_r : T_SCT_BIT_REG<"togglebit", 0b10>;
3249 }
3250
3251 def: Pat<(i32 (and (i32 IntRegs:$Rs), (not (shl 1, u5ImmPred:$u5)))),
3252          (S2_clrbit_i IntRegs:$Rs, u5ImmPred:$u5)>;
3253 def: Pat<(i32 (or (i32 IntRegs:$Rs), (shl 1, u5ImmPred:$u5))),
3254          (S2_setbit_i IntRegs:$Rs, u5ImmPred:$u5)>;
3255 def: Pat<(i32 (xor (i32 IntRegs:$Rs), (shl 1, u5ImmPred:$u5))),
3256          (S2_togglebit_i IntRegs:$Rs, u5ImmPred:$u5)>;
3257 def: Pat<(i32 (and (i32 IntRegs:$Rs), (not (shl 1, (i32 IntRegs:$Rt))))),
3258          (S2_clrbit_r IntRegs:$Rs, IntRegs:$Rt)>;
3259 def: Pat<(i32 (or (i32 IntRegs:$Rs), (shl 1, (i32 IntRegs:$Rt)))),
3260          (S2_setbit_r IntRegs:$Rs, IntRegs:$Rt)>;
3261 def: Pat<(i32 (xor (i32 IntRegs:$Rs), (shl 1, (i32 IntRegs:$Rt)))),
3262          (S2_togglebit_r IntRegs:$Rs, IntRegs:$Rt)>;
3263
3264 // Bit test
3265
3266 let hasSideEffects = 0 in
3267 class T_TEST_BIT_IMM<string MnOp, bits<3> MajOp>
3268     : SInst<(outs PredRegs:$Pd), (ins IntRegs:$Rs, u5Imm:$u5),
3269             "$Pd = "#MnOp#"($Rs, #$u5)",
3270             [], "", S_2op_tc_2early_SLOT23> {
3271   bits<2> Pd;
3272   bits<5> Rs;
3273   bits<5> u5;
3274   let IClass = 0b1000;
3275   let Inst{27-24} = 0b0101;
3276   let Inst{23-21} = MajOp;
3277   let Inst{20-16} = Rs;
3278   let Inst{13} = 0;
3279   let Inst{12-8} = u5;
3280   let Inst{1-0} = Pd;
3281 }
3282
3283 let hasSideEffects = 0 in
3284 class T_TEST_BIT_REG<string MnOp, bit IsNeg>
3285     : SInst<(outs PredRegs:$Pd), (ins IntRegs:$Rs, IntRegs:$Rt),
3286             "$Pd = "#MnOp#"($Rs, $Rt)",
3287             [], "", S_3op_tc_2early_SLOT23> {
3288   bits<2> Pd;
3289   bits<5> Rs;
3290   bits<5> Rt;
3291   let IClass = 0b1100;
3292   let Inst{27-22} = 0b011100;
3293   let Inst{21} = IsNeg;
3294   let Inst{20-16} = Rs;
3295   let Inst{12-8} = Rt;
3296   let Inst{1-0} = Pd;
3297 }
3298
3299 let isCodeGenOnly = 0 in {
3300 def S2_tstbit_i : T_TEST_BIT_IMM<"tstbit", 0b000>;
3301 def S2_tstbit_r : T_TEST_BIT_REG<"tstbit", 0>;
3302 }
3303
3304 let AddedComplexity = 20 in { // Complexity greater than cmp reg-imm.
3305   def: Pat<(i1 (setne (and (shl 1, u5ImmPred:$u5), (i32 IntRegs:$Rs)), 0)),
3306            (S2_tstbit_i IntRegs:$Rs, u5ImmPred:$u5)>;
3307   def: Pat<(i1 (setne (and (shl 1, (i32 IntRegs:$Rt)), (i32 IntRegs:$Rs)), 0)),
3308            (S2_tstbit_r IntRegs:$Rs, IntRegs:$Rt)>;
3309   def: Pat<(i1 (trunc (i32 IntRegs:$Rs))),
3310            (S2_tstbit_i IntRegs:$Rs, 0)>;
3311   def: Pat<(i1 (trunc (i64 DoubleRegs:$Rs))),
3312            (S2_tstbit_i (LoReg DoubleRegs:$Rs), 0)>;
3313 }
3314 let hasSideEffects = 0 in
3315 class T_TEST_BITS_IMM<string MnOp, bits<2> MajOp, bit IsNeg>
3316     : SInst<(outs PredRegs:$Pd), (ins IntRegs:$Rs, u6Imm:$u6),
3317             "$Pd = "#MnOp#"($Rs, #$u6)",
3318             [], "", S_2op_tc_2early_SLOT23> {
3319   bits<2> Pd;
3320   bits<5> Rs;
3321   bits<6> u6;
3322   let IClass = 0b1000;
3323   let Inst{27-24} = 0b0101;
3324   let Inst{23-22} = MajOp;
3325   let Inst{21} = IsNeg;
3326   let Inst{20-16} = Rs;
3327   let Inst{13-8} = u6;
3328   let Inst{1-0} = Pd;
3329 }
3330
3331 let hasSideEffects = 0 in
3332 class T_TEST_BITS_REG<string MnOp, bits<2> MajOp, bit IsNeg>
3333     : SInst<(outs PredRegs:$Pd), (ins IntRegs:$Rs, IntRegs:$Rt),
3334             "$Pd = "#MnOp#"($Rs, $Rt)",
3335             [], "", S_3op_tc_2early_SLOT23> {
3336   bits<2> Pd;
3337   bits<5> Rs;
3338   bits<5> Rt;
3339   let IClass = 0b1100;
3340   let Inst{27-24} = 0b0111;
3341   let Inst{23-22} = MajOp;
3342   let Inst{21} = IsNeg;
3343   let Inst{20-16} = Rs;
3344   let Inst{12-8} = Rt;
3345   let Inst{1-0} = Pd;
3346 }
3347
3348 let isCodeGenOnly = 0 in {
3349 def C2_bitsclri : T_TEST_BITS_IMM<"bitsclr", 0b10, 0>;
3350 def C2_bitsclr  : T_TEST_BITS_REG<"bitsclr", 0b10, 0>;
3351 def C2_bitsset  : T_TEST_BITS_REG<"bitsset", 0b01, 0>;
3352 }
3353
3354 let AddedComplexity = 20 in { // Complexity greater than compare reg-imm.
3355   def: Pat<(i1 (seteq (and (i32 IntRegs:$Rs), u6ImmPred:$u6), 0)),
3356            (C2_bitsclri IntRegs:$Rs, u6ImmPred:$u6)>;
3357   def: Pat<(i1 (seteq (and (i32 IntRegs:$Rs), (i32 IntRegs:$Rt)), 0)),
3358            (C2_bitsclr IntRegs:$Rs, IntRegs:$Rt)>;
3359 }
3360
3361 let AddedComplexity = 10 in   // Complexity greater than compare reg-reg.
3362 def: Pat<(i1 (seteq (and (i32 IntRegs:$Rs), (i32 IntRegs:$Rt)), IntRegs:$Rt)),
3363          (C2_bitsset IntRegs:$Rs, IntRegs:$Rt)>;
3364
3365 //===----------------------------------------------------------------------===//
3366 // STYPE/BIT -
3367 //===----------------------------------------------------------------------===//
3368
3369 //===----------------------------------------------------------------------===//
3370 // STYPE/COMPLEX +
3371 //===----------------------------------------------------------------------===//
3372 //===----------------------------------------------------------------------===//
3373 // STYPE/COMPLEX -
3374 //===----------------------------------------------------------------------===//
3375
3376 //===----------------------------------------------------------------------===//
3377 // XTYPE/PERM +
3378 //===----------------------------------------------------------------------===//
3379
3380 //===----------------------------------------------------------------------===//
3381 // XTYPE/PERM -
3382 //===----------------------------------------------------------------------===//
3383
3384 //===----------------------------------------------------------------------===//
3385 // STYPE/PRED +
3386 //===----------------------------------------------------------------------===//
3387
3388 // Predicate transfer.
3389 let hasSideEffects = 0, hasNewValue = 1, isCodeGenOnly = 0 in
3390 def C2_tfrpr : SInst<(outs IntRegs:$Rd), (ins PredRegs:$Ps),
3391       "$Rd = $Ps", [], "", S_2op_tc_1_SLOT23> {
3392   bits<5> Rd;
3393   bits<2> Ps;
3394
3395   let IClass = 0b1000;
3396   let Inst{27-24} = 0b1001;
3397   let Inst{22} = 0b1;
3398   let Inst{17-16} = Ps;
3399   let Inst{4-0} = Rd;
3400 }
3401
3402 // Transfer general register to predicate.
3403 let hasSideEffects = 0, isCodeGenOnly = 0 in
3404 def C2_tfrrp: SInst<(outs PredRegs:$Pd), (ins IntRegs:$Rs),
3405       "$Pd = $Rs", [], "", S_2op_tc_2early_SLOT23> {
3406   bits<2> Pd;
3407   bits<5> Rs;
3408
3409   let IClass = 0b1000;
3410   let Inst{27-21} = 0b0101010;
3411   let Inst{20-16} = Rs;
3412   let Inst{1-0} = Pd;
3413 }
3414
3415
3416 //===----------------------------------------------------------------------===//
3417 // STYPE/PRED -
3418 //===----------------------------------------------------------------------===//
3419
3420 //===----------------------------------------------------------------------===//
3421 // STYPE/SHIFT +
3422 //===----------------------------------------------------------------------===//
3423 class S_2OpInstImm<string Mnemonic, bits<3>MajOp, bits<3>MinOp,
3424                    Operand Imm, list<dag> pattern = [], bit isRnd = 0>
3425   : SInst<(outs DoubleRegs:$dst), (ins DoubleRegs:$src1, Imm:$src2),
3426            "$dst = "#Mnemonic#"($src1, #$src2)"#!if(isRnd, ":rnd", ""),
3427            pattern> {
3428   bits<5> src1;
3429   bits<5> dst;
3430   let IClass = 0b1000;
3431   let Inst{27-24} = 0;
3432   let Inst{23-21} = MajOp;
3433   let Inst{20-16} = src1;
3434   let Inst{7-5} = MinOp;
3435   let Inst{4-0} = dst;
3436 }
3437
3438 class S_2OpInstImmI6<string Mnemonic, SDNode OpNode, bits<3>MinOp>
3439   : S_2OpInstImm<Mnemonic, 0b000, MinOp, u6Imm,
3440   [(set (i64 DoubleRegs:$dst), (OpNode (i64 DoubleRegs:$src1),
3441                                         u6ImmPred:$src2))]> {
3442   bits<6> src2;
3443   let Inst{13-8} = src2;
3444 }
3445
3446 // Shift by immediate.
3447 let isCodeGenOnly = 0 in {
3448 def S2_asr_i_p : S_2OpInstImmI6<"asr", sra, 0b000>;
3449 def S2_asl_i_p : S_2OpInstImmI6<"asl", shl, 0b010>;
3450 def S2_lsr_i_p : S_2OpInstImmI6<"lsr", srl, 0b001>;
3451 }
3452
3453 // Shift left by small amount and add.
3454 let AddedComplexity = 100, hasNewValue = 1, hasSideEffects = 0,
3455     isCodeGenOnly = 0 in
3456 def S2_addasl_rrri: SInst <(outs IntRegs:$Rd),
3457                            (ins IntRegs:$Rt, IntRegs:$Rs, u3Imm:$u3),
3458   "$Rd = addasl($Rt, $Rs, #$u3)" ,
3459   [(set (i32 IntRegs:$Rd), (add (i32 IntRegs:$Rt),
3460                                 (shl (i32 IntRegs:$Rs), u3ImmPred:$u3)))],
3461   "", S_3op_tc_2_SLOT23> {
3462     bits<5> Rd;
3463     bits<5> Rt;
3464     bits<5> Rs;
3465     bits<3> u3;
3466
3467     let IClass = 0b1100;
3468
3469     let Inst{27-21} = 0b0100000;
3470     let Inst{20-16} = Rs;
3471     let Inst{13}    = 0b0;
3472     let Inst{12-8}  = Rt;
3473     let Inst{7-5}   = u3;
3474     let Inst{4-0}   = Rd;
3475   }
3476
3477 //===----------------------------------------------------------------------===//
3478 // STYPE/SHIFT -
3479 //===----------------------------------------------------------------------===//
3480
3481 //===----------------------------------------------------------------------===//
3482 // STYPE/VH +
3483 //===----------------------------------------------------------------------===//
3484 //===----------------------------------------------------------------------===//
3485 // STYPE/VH -
3486 //===----------------------------------------------------------------------===//
3487
3488 //===----------------------------------------------------------------------===//
3489 // STYPE/VW +
3490 //===----------------------------------------------------------------------===//
3491 //===----------------------------------------------------------------------===//
3492 // STYPE/VW -
3493 //===----------------------------------------------------------------------===//
3494
3495 //===----------------------------------------------------------------------===//
3496 // SYSTEM/SUPER +
3497 //===----------------------------------------------------------------------===//
3498
3499 //===----------------------------------------------------------------------===//
3500 // SYSTEM/USER +
3501 //===----------------------------------------------------------------------===//
3502 def HexagonBARRIER: SDNode<"HexagonISD::BARRIER", SDTNone, [SDNPHasChain]>;
3503
3504 let hasSideEffects = 1, isSoloAX = 1, isCodeGenOnly = 0 in
3505 def BARRIER : SYSInst<(outs), (ins),
3506                      "barrier",
3507                      [(HexagonBARRIER)],"",ST_tc_st_SLOT0> {
3508   let Inst{31-28} = 0b1010;
3509   let Inst{27-21} = 0b1000000;
3510 }
3511
3512 //===----------------------------------------------------------------------===//
3513 // SYSTEM/SUPER -
3514 //===----------------------------------------------------------------------===//
3515 //===----------------------------------------------------------------------===//
3516 // CRUSER - Type.
3517 //===----------------------------------------------------------------------===//
3518 // HW loop
3519 let isExtendable = 1, isExtentSigned = 1, opExtentBits = 9, opExtentAlign = 2,
3520     opExtendable = 0, hasSideEffects = 0 in
3521 class LOOP_iBase<string mnemonic, Operand brOp, bit mustExtend = 0>
3522          : CRInst<(outs), (ins brOp:$offset, u10Imm:$src2),
3523            #mnemonic#"($offset, #$src2)",
3524            [], "" , CR_tc_3x_SLOT3> {
3525     bits<9> offset;
3526     bits<10> src2;
3527
3528     let IClass = 0b0110;
3529
3530     let Inst{27-22} = 0b100100;
3531     let Inst{21} = !if (!eq(mnemonic, "loop0"), 0b0, 0b1);
3532     let Inst{20-16} = src2{9-5};
3533     let Inst{12-8} = offset{8-4};
3534     let Inst{7-5} = src2{4-2};
3535     let Inst{4-3} = offset{3-2};
3536     let Inst{1-0} = src2{1-0};
3537 }
3538
3539 let isExtendable = 1, isExtentSigned = 1, opExtentBits = 9, opExtentAlign = 2,
3540     opExtendable = 0, hasSideEffects = 0 in
3541 class LOOP_rBase<string mnemonic, Operand brOp, bit mustExtend = 0>
3542          : CRInst<(outs), (ins brOp:$offset, IntRegs:$src2),
3543            #mnemonic#"($offset, $src2)",
3544            [], "" ,CR_tc_3x_SLOT3> {
3545     bits<9> offset;
3546     bits<5> src2;
3547
3548     let IClass = 0b0110;
3549
3550     let Inst{27-22} = 0b000000;
3551     let Inst{21} = !if (!eq(mnemonic, "loop0"), 0b0, 0b1);
3552     let Inst{20-16} = src2;
3553     let Inst{12-8} = offset{8-4};
3554     let Inst{4-3} = offset{3-2};
3555   }
3556
3557 multiclass LOOP_ri<string mnemonic> {
3558   def i : LOOP_iBase<mnemonic, brtarget>;
3559   def r : LOOP_rBase<mnemonic, brtarget>;
3560 }
3561
3562
3563 let Defs = [SA0, LC0, USR], isCodeGenOnly = 0 in
3564 defm J2_loop0 : LOOP_ri<"loop0">;
3565
3566 // Interestingly only loop0's appear to set usr.lpcfg
3567 let Defs = [SA1, LC1], isCodeGenOnly = 0 in
3568 defm J2_loop1 : LOOP_ri<"loop1">;
3569
3570 let isBranch = 1, isTerminator = 1, hasSideEffects = 0,
3571     Defs = [PC, LC0], Uses = [SA0, LC0] in {
3572 def ENDLOOP0 : Endloop<(outs), (ins brtarget:$offset),
3573                        ":endloop0",
3574                        []>;
3575 }
3576
3577 let isBranch = 1, isTerminator = 1, hasSideEffects = 0,
3578     Defs = [PC, LC1], Uses = [SA1, LC1] in {
3579 def ENDLOOP1 : Endloop<(outs), (ins brtarget:$offset),
3580                        ":endloop1",
3581                        []>;
3582 }
3583
3584 // Pipelined loop instructions, sp[123]loop0
3585 let Defs = [LC0, SA0, P3, USR], hasSideEffects = 0,
3586     isExtentSigned = 1, isExtendable = 1, opExtentBits = 9, opExtentAlign = 2,
3587     opExtendable = 0, isPredicateLate = 1 in
3588 class SPLOOP_iBase<string SP, bits<2> op>
3589   : CRInst <(outs), (ins brtarget:$r7_2, u10Imm:$U10),
3590   "p3 = sp"#SP#"loop0($r7_2, #$U10)" > {
3591     bits<9> r7_2;
3592     bits<10> U10;
3593
3594     let IClass = 0b0110;
3595
3596     let Inst{22-21} = op;
3597     let Inst{27-23} = 0b10011;
3598     let Inst{20-16} = U10{9-5};
3599     let Inst{12-8} = r7_2{8-4};
3600     let Inst{7-5} = U10{4-2};
3601     let Inst{4-3} = r7_2{3-2};
3602     let Inst{1-0} = U10{1-0};
3603   }
3604
3605 let Defs = [LC0, SA0, P3, USR], hasSideEffects = 0,
3606     isExtentSigned = 1, isExtendable = 1, opExtentBits = 9, opExtentAlign = 2,
3607     opExtendable = 0, isPredicateLate = 1 in
3608 class SPLOOP_rBase<string SP, bits<2> op>
3609   : CRInst <(outs), (ins brtarget:$r7_2, IntRegs:$Rs),
3610   "p3 = sp"#SP#"loop0($r7_2, $Rs)" > {
3611     bits<9> r7_2;
3612     bits<5> Rs;
3613
3614     let IClass = 0b0110;
3615
3616     let Inst{22-21} = op;
3617     let Inst{27-23} = 0b00001;
3618     let Inst{20-16} = Rs;
3619     let Inst{12-8} = r7_2{8-4};
3620     let Inst{4-3} = r7_2{3-2};
3621   }
3622
3623 multiclass SPLOOP_ri<string mnemonic, bits<2> op> {
3624   def i : SPLOOP_iBase<mnemonic, op>;
3625   def r : SPLOOP_rBase<mnemonic, op>;
3626 }
3627
3628 let isCodeGenOnly = 0 in {
3629 defm J2_ploop1s : SPLOOP_ri<"1", 0b01>;
3630 defm J2_ploop2s : SPLOOP_ri<"2", 0b10>;
3631 defm J2_ploop3s : SPLOOP_ri<"3", 0b11>;
3632 }
3633
3634 // Transfer to/from Control/GPR Guest/GPR
3635 let hasSideEffects = 0 in
3636 class TFR_CR_RS_base<RegisterClass CTRC, RegisterClass RC, bit isDouble>
3637   : CRInst <(outs CTRC:$dst), (ins RC:$src),
3638   "$dst = $src", [], "", CR_tc_3x_SLOT3> {
3639     bits<5> dst;
3640     bits<5> src;
3641
3642     let IClass = 0b0110;
3643
3644     let Inst{27-25} = 0b001;
3645     let Inst{24} = isDouble;
3646     let Inst{23-21} = 0b001;
3647     let Inst{20-16} = src;
3648     let Inst{4-0} = dst;
3649   }
3650 let isCodeGenOnly = 0 in
3651 def A2_tfrrcr : TFR_CR_RS_base<CtrRegs, IntRegs, 0b0>;
3652 def : InstAlias<"m0 = $Rs", (A2_tfrrcr C6, IntRegs:$Rs)>;
3653 def : InstAlias<"m1 = $Rs", (A2_tfrrcr C7, IntRegs:$Rs)>;
3654
3655 let hasSideEffects = 0 in
3656 class TFR_RD_CR_base<RegisterClass RC, RegisterClass CTRC, bit isSingle>
3657   : CRInst <(outs RC:$dst), (ins CTRC:$src),
3658   "$dst = $src", [], "", CR_tc_3x_SLOT3> {
3659     bits<5> dst;
3660     bits<5> src;
3661
3662     let IClass = 0b0110;
3663
3664     let Inst{27-26} = 0b10;
3665     let Inst{25} = isSingle;
3666     let Inst{24-21} = 0b0000;
3667     let Inst{20-16} = src;
3668     let Inst{4-0} = dst;
3669   }
3670
3671 let hasNewValue = 1, opNewValue = 0, isCodeGenOnly = 0 in
3672 def A2_tfrcrr : TFR_RD_CR_base<IntRegs, CtrRegs, 1>;
3673 def : InstAlias<"$Rd = m0", (A2_tfrcrr IntRegs:$Rd, C6)>;
3674 def : InstAlias<"$Rd = m1", (A2_tfrcrr IntRegs:$Rd, C7)>;
3675
3676 // Y4_trace: Send value to etm trace.
3677 let isSoloAX = 1, hasSideEffects = 0, isCodeGenOnly = 0 in
3678 def Y4_trace: CRInst <(outs), (ins IntRegs:$Rs),
3679   "trace($Rs)"> {
3680     bits<5> Rs;
3681
3682     let IClass = 0b0110;
3683     let Inst{27-21} = 0b0010010;
3684     let Inst{20-16} = Rs;
3685   }
3686
3687 let AddedComplexity = 100, isPredicated = 1 in
3688 def TFR_condset_ri : ALU32_rr<(outs IntRegs:$dst),
3689             (ins PredRegs:$src1, IntRegs:$src2, s12Imm:$src3),
3690             "Error; should not emit",
3691             [(set (i32 IntRegs:$dst),
3692              (i32 (select (i1 PredRegs:$src1), (i32 IntRegs:$src2),
3693                           s12ImmPred:$src3)))]>;
3694
3695 let AddedComplexity = 100, isPredicated = 1 in
3696 def TFR_condset_ir : ALU32_rr<(outs IntRegs:$dst),
3697             (ins PredRegs:$src1, s12Imm:$src2, IntRegs:$src3),
3698             "Error; should not emit",
3699             [(set (i32 IntRegs:$dst),
3700              (i32 (select (i1 PredRegs:$src1), s12ImmPred:$src2,
3701                           (i32 IntRegs:$src3))))]>;
3702
3703 let AddedComplexity = 100, isPredicated = 1 in
3704 def TFR_condset_ii : ALU32_rr<(outs IntRegs:$dst),
3705                               (ins PredRegs:$src1, s12Imm:$src2, s12Imm:$src3),
3706                      "Error; should not emit",
3707                      [(set (i32 IntRegs:$dst),
3708                            (i32 (select (i1 PredRegs:$src1), s12ImmPred:$src2,
3709                                         s12ImmPred:$src3)))]>;
3710
3711 // Generate frameindex addresses.
3712 let isReMaterializable = 1 in
3713 def TFR_FI : ALU32_ri<(outs IntRegs:$dst), (ins FrameIndex:$src1),
3714              "$dst = add($src1)",
3715              [(set (i32 IntRegs:$dst), ADDRri:$src1)]>;
3716
3717 // Support for generating global address.
3718 // Taken from X86InstrInfo.td.
3719 def SDTHexagonCONST32 : SDTypeProfile<1, 1, [
3720                                             SDTCisVT<0, i32>,
3721                                             SDTCisVT<1, i32>,
3722                                             SDTCisPtrTy<0>]>;
3723 def HexagonCONST32 : SDNode<"HexagonISD::CONST32",     SDTHexagonCONST32>;
3724 def HexagonCONST32_GP : SDNode<"HexagonISD::CONST32_GP",     SDTHexagonCONST32>;
3725
3726 // HI/LO Instructions
3727 let isReMaterializable = 1, isMoveImm = 1, hasSideEffects = 0 in
3728 def LO : ALU32_ri<(outs IntRegs:$dst), (ins globaladdress:$global),
3729                   "$dst.l = #LO($global)",
3730                   []>;
3731
3732 let isReMaterializable = 1, isMoveImm = 1, hasSideEffects = 0 in
3733 def HI : ALU32_ri<(outs IntRegs:$dst), (ins globaladdress:$global),
3734                   "$dst.h = #HI($global)",
3735                   []>;
3736
3737 let isReMaterializable = 1, isMoveImm = 1, hasSideEffects = 0 in
3738 def LOi : ALU32_ri<(outs IntRegs:$dst), (ins i32imm:$imm_value),
3739                   "$dst.l = #LO($imm_value)",
3740                   []>;
3741
3742
3743 let isReMaterializable = 1, isMoveImm = 1, hasSideEffects = 0 in
3744 def HIi : ALU32_ri<(outs IntRegs:$dst), (ins i32imm:$imm_value),
3745                   "$dst.h = #HI($imm_value)",
3746                   []>;
3747
3748 let isReMaterializable = 1, isMoveImm = 1, hasSideEffects = 0 in
3749 def LO_jt : ALU32_ri<(outs IntRegs:$dst), (ins jumptablebase:$jt),
3750                   "$dst.l = #LO($jt)",
3751                   []>;
3752
3753 let isReMaterializable = 1, isMoveImm = 1, hasSideEffects = 0 in
3754 def HI_jt : ALU32_ri<(outs IntRegs:$dst), (ins jumptablebase:$jt),
3755                   "$dst.h = #HI($jt)",
3756                   []>;
3757
3758
3759 let isReMaterializable = 1, isMoveImm = 1, hasSideEffects = 0 in
3760 def LO_label : ALU32_ri<(outs IntRegs:$dst), (ins bblabel:$label),
3761                   "$dst.l = #LO($label)",
3762                   []>;
3763
3764 let isReMaterializable = 1, isMoveImm = 1 , hasSideEffects = 0 in
3765 def HI_label : ALU32_ri<(outs IntRegs:$dst), (ins bblabel:$label),
3766                   "$dst.h = #HI($label)",
3767                   []>;
3768
3769 // This pattern is incorrect. When we add small data, we should change
3770 // this pattern to use memw(#foo).
3771 // This is for sdata.
3772 let isMoveImm = 1 in
3773 def CONST32 : LDInst<(outs IntRegs:$dst), (ins globaladdress:$global),
3774               "$dst = CONST32(#$global)",
3775               [(set (i32 IntRegs:$dst),
3776                     (load (HexagonCONST32 tglobaltlsaddr:$global)))]>;
3777
3778 // This is for non-sdata.
3779 let isReMaterializable = 1, isMoveImm = 1 in
3780 def CONST32_set : LDInst2<(outs IntRegs:$dst), (ins globaladdress:$global),
3781                   "$dst = CONST32(#$global)",
3782                   [(set (i32 IntRegs:$dst),
3783                         (HexagonCONST32 tglobaladdr:$global))]>;
3784
3785 let isReMaterializable = 1, isMoveImm = 1 in
3786 def CONST32_set_jt : LDInst2<(outs IntRegs:$dst), (ins jumptablebase:$jt),
3787                      "$dst = CONST32(#$jt)",
3788                      [(set (i32 IntRegs:$dst),
3789                            (HexagonCONST32 tjumptable:$jt))]>;
3790
3791 let isReMaterializable = 1, isMoveImm = 1 in
3792 def CONST32GP_set : LDInst2<(outs IntRegs:$dst), (ins globaladdress:$global),
3793                     "$dst = CONST32(#$global)",
3794                     [(set (i32 IntRegs:$dst),
3795                           (HexagonCONST32_GP tglobaladdr:$global))]>;
3796
3797 let isReMaterializable = 1, isMoveImm = 1 in
3798 def CONST32_Int_Real : LDInst2<(outs IntRegs:$dst), (ins i32imm:$global),
3799                        "$dst = CONST32(#$global)",
3800                        [(set (i32 IntRegs:$dst), imm:$global) ]>;
3801
3802 // Map BlockAddress lowering to CONST32_Int_Real
3803 def : Pat<(HexagonCONST32_GP tblockaddress:$addr),
3804           (CONST32_Int_Real tblockaddress:$addr)>;
3805
3806 let isReMaterializable = 1, isMoveImm = 1 in
3807 def CONST32_Label : LDInst2<(outs IntRegs:$dst), (ins bblabel:$label),
3808                     "$dst = CONST32($label)",
3809                     [(set (i32 IntRegs:$dst), (HexagonCONST32 bbl:$label))]>;
3810
3811 let isReMaterializable = 1, isMoveImm = 1 in
3812 def CONST64_Int_Real : LDInst2<(outs DoubleRegs:$dst), (ins i64imm:$global),
3813                        "$dst = CONST64(#$global)",
3814                        [(set (i64 DoubleRegs:$dst), imm:$global) ]>;
3815
3816 def TFR_PdFalse : SInst<(outs PredRegs:$dst), (ins),
3817                   "$dst = xor($dst, $dst)",
3818                   [(set (i1 PredRegs:$dst), 0)]>;
3819
3820 def MPY_trsext : MInst<(outs IntRegs:$dst), (ins IntRegs:$src1, IntRegs:$src2),
3821        "$dst = mpy($src1, $src2)",
3822        [(set (i32 IntRegs:$dst),
3823              (trunc (i64 (srl (i64 (mul (i64 (sext (i32 IntRegs:$src1))),
3824                                         (i64 (sext (i32 IntRegs:$src2))))),
3825                               (i32 32)))))]>;
3826
3827 // Pseudo instructions.
3828 def SDT_SPCallSeqStart : SDCallSeqStart<[ SDTCisVT<0, i32> ]>;
3829
3830 def SDT_SPCallSeqEnd : SDCallSeqEnd<[ SDTCisVT<0, i32>,
3831                                         SDTCisVT<1, i32> ]>;
3832
3833 def callseq_end : SDNode<"ISD::CALLSEQ_END",   SDT_SPCallSeqEnd,
3834                   [SDNPHasChain, SDNPOptInGlue, SDNPOutGlue]>;
3835
3836 def callseq_start : SDNode<"ISD::CALLSEQ_START", SDT_SPCallSeqStart,
3837                     [SDNPHasChain, SDNPOutGlue]>;
3838
3839 def SDT_SPCall : SDTypeProfile<0, 1, [SDTCisVT<0, i32>]>;
3840
3841 def call : SDNode<"HexagonISD::CALL", SDT_SPCall,
3842            [SDNPHasChain, SDNPOptInGlue, SDNPOutGlue, SDNPVariadic]>;
3843
3844 // For tailcalls a HexagonTCRet SDNode has 3 SDNode Properties - a chain,
3845 // Optional Flag and Variable Arguments.
3846 // Its 1 Operand has pointer type.
3847 def HexagonTCRet    : SDNode<"HexagonISD::TC_RETURN", SDT_SPCall,
3848                      [SDNPHasChain,  SDNPOptInGlue, SDNPVariadic]>;
3849
3850 let Defs = [R29, R30], Uses = [R31, R30, R29] in {
3851  def ADJCALLSTACKDOWN : Pseudo<(outs), (ins i32imm:$amt),
3852                         "Should never be emitted",
3853                         [(callseq_start timm:$amt)]>;
3854 }
3855
3856 let Defs = [R29, R30, R31], Uses = [R29] in {
3857  def ADJCALLSTACKUP : Pseudo<(outs), (ins i32imm:$amt1, i32imm:$amt2),
3858                       "Should never be emitted",
3859                       [(callseq_end timm:$amt1, timm:$amt2)]>;
3860 }
3861 // Call subroutine.
3862 let isCall = 1, hasSideEffects = 0,
3863   Defs = [D0, D1, D2, D3, D4, D5, D6, D7, D8, D9, D10,
3864           R22, R23, R28, R31, P0, P1, P2, P3, LC0, LC1, SA0, SA1] in {
3865   def CALL : JInst<(outs), (ins calltarget:$dst),
3866              "call $dst", []>;
3867 }
3868
3869 // Call subroutine indirectly.
3870 let Defs = VolatileV3.Regs, isCodeGenOnly = 0 in
3871 def J2_callr : JUMPR_MISC_CALLR<0, 1>;
3872
3873 // Indirect tail-call.
3874 let isCodeGenOnly = 1, isCall = 1, isReturn = 1  in
3875 def TCRETURNR : T_JMPr;
3876
3877 // Direct tail-calls.
3878 let isCall = 1, isReturn = 1, isBarrier = 1, isPredicable = 0,
3879 isTerminator = 1, isCodeGenOnly = 1 in {
3880   def TCRETURNtg   : JInst<(outs), (ins calltarget:$dst), "jump $dst",
3881       [], "", J_tc_2early_SLOT23>;
3882   def TCRETURNtext : JInst<(outs), (ins calltarget:$dst), "jump $dst",
3883       [], "", J_tc_2early_SLOT23>;
3884 }
3885
3886 // Map call instruction.
3887 def : Pat<(call (i32 IntRegs:$dst)),
3888       (J2_callr (i32 IntRegs:$dst))>, Requires<[HasV2TOnly]>;
3889 def : Pat<(call tglobaladdr:$dst),
3890       (CALL tglobaladdr:$dst)>, Requires<[HasV2TOnly]>;
3891 def : Pat<(call texternalsym:$dst),
3892       (CALL texternalsym:$dst)>, Requires<[HasV2TOnly]>;
3893 //Tail calls.
3894 def : Pat<(HexagonTCRet tglobaladdr:$dst),
3895       (TCRETURNtg tglobaladdr:$dst)>;
3896 def : Pat<(HexagonTCRet texternalsym:$dst),
3897       (TCRETURNtext texternalsym:$dst)>;
3898 def : Pat<(HexagonTCRet (i32 IntRegs:$dst)),
3899       (TCRETURNR (i32 IntRegs:$dst))>;
3900
3901 // Atomic load and store support
3902 // 8 bit atomic load
3903 def : Pat<(atomic_load_8 ADDRriS11_0:$src1),
3904           (i32 (L2_loadrub_io AddrFI:$src1, 0))>;
3905
3906 def : Pat<(atomic_load_8 (add (i32 IntRegs:$src1), s11_0ImmPred:$offset)),
3907           (i32 (L2_loadrub_io (i32 IntRegs:$src1), s11_0ImmPred:$offset))>;
3908
3909 // 16 bit atomic load
3910 def : Pat<(atomic_load_16 ADDRriS11_1:$src1),
3911           (i32 (L2_loadruh_io AddrFI:$src1, 0))>;
3912
3913 def : Pat<(atomic_load_16 (add (i32 IntRegs:$src1), s11_1ImmPred:$offset)),
3914           (i32 (L2_loadruh_io (i32 IntRegs:$src1), s11_1ImmPred:$offset))>;
3915
3916 def : Pat<(atomic_load_32 ADDRriS11_2:$src1),
3917           (i32 (L2_loadri_io AddrFI:$src1, 0))>;
3918
3919 def : Pat<(atomic_load_32 (add (i32 IntRegs:$src1), s11_2ImmPred:$offset)),
3920           (i32 (L2_loadri_io (i32 IntRegs:$src1), s11_2ImmPred:$offset))>;
3921
3922 // 64 bit atomic load
3923 def : Pat<(atomic_load_64 ADDRriS11_3:$src1),
3924           (i64 (L2_loadrd_io AddrFI:$src1, 0))>;
3925
3926 def : Pat<(atomic_load_64 (add (i32 IntRegs:$src1), s11_3ImmPred:$offset)),
3927           (i64 (L2_loadrd_io (i32 IntRegs:$src1), s11_3ImmPred:$offset))>;
3928
3929
3930 def : Pat<(atomic_store_8 ADDRriS11_0:$src2, (i32 IntRegs:$src1)),
3931           (STrib ADDRriS11_0:$src2, (i32 IntRegs:$src1))>;
3932
3933 def : Pat<(atomic_store_8 (add (i32 IntRegs:$src2), s11_0ImmPred:$offset),
3934                           (i32 IntRegs:$src1)),
3935           (STrib_indexed (i32 IntRegs:$src2), s11_0ImmPred:$offset,
3936                          (i32 IntRegs:$src1))>;
3937
3938
3939 def : Pat<(atomic_store_16 ADDRriS11_1:$src2, (i32 IntRegs:$src1)),
3940           (STrih ADDRriS11_1:$src2, (i32 IntRegs:$src1))>;
3941
3942 def : Pat<(atomic_store_16 (i32 IntRegs:$src1),
3943                           (add (i32 IntRegs:$src2), s11_1ImmPred:$offset)),
3944           (STrih_indexed (i32 IntRegs:$src2), s11_1ImmPred:$offset,
3945                          (i32 IntRegs:$src1))>;
3946
3947 def : Pat<(atomic_store_32 ADDRriS11_2:$src2, (i32 IntRegs:$src1)),
3948           (STriw ADDRriS11_2:$src2, (i32 IntRegs:$src1))>;
3949
3950 def : Pat<(atomic_store_32 (add (i32 IntRegs:$src2), s11_2ImmPred:$offset),
3951                            (i32 IntRegs:$src1)),
3952           (STriw_indexed (i32 IntRegs:$src2), s11_2ImmPred:$offset,
3953                          (i32 IntRegs:$src1))>;
3954
3955
3956
3957
3958 def : Pat<(atomic_store_64 ADDRriS11_3:$src2, (i64 DoubleRegs:$src1)),
3959           (STrid ADDRriS11_3:$src2, (i64 DoubleRegs:$src1))>;
3960
3961 def : Pat<(atomic_store_64 (add (i32 IntRegs:$src2), s11_3ImmPred:$offset),
3962                            (i64 DoubleRegs:$src1)),
3963           (STrid_indexed (i32 IntRegs:$src2), s11_3ImmPred:$offset,
3964                          (i64 DoubleRegs:$src1))>;
3965
3966 // Map from r0 = and(r1, 65535) to r0 = zxth(r1)
3967 def : Pat <(and (i32 IntRegs:$src1), 65535),
3968       (A2_zxth (i32 IntRegs:$src1))>;
3969
3970 // Map from r0 = and(r1, 255) to r0 = zxtb(r1).
3971 def : Pat <(and (i32 IntRegs:$src1), 255),
3972       (A2_zxtb (i32 IntRegs:$src1))>;
3973
3974 // Map Add(p1, true) to p1 = not(p1).
3975 //     Add(p1, false) should never be produced,
3976 //     if it does, it got to be mapped to NOOP.
3977 def : Pat <(add (i1 PredRegs:$src1), -1),
3978       (C2_not (i1 PredRegs:$src1))>;
3979
3980 // Map from p0 = pnot(p0); r0 = mux(p0, #i, #j) => r0 = mux(p0, #j, #i).
3981 def : Pat <(select (not (i1 PredRegs:$src1)), s8ImmPred:$src2, s8ImmPred:$src3),
3982       (i32 (TFR_condset_ii (i1 PredRegs:$src1), s8ImmPred:$src3,
3983                            s8ImmPred:$src2))>;
3984
3985 // Map from p0 = pnot(p0); r0 = select(p0, #i, r1)
3986 // => r0 = TFR_condset_ri(p0, r1, #i)
3987 def : Pat <(select (not (i1 PredRegs:$src1)), s12ImmPred:$src2,
3988                    (i32 IntRegs:$src3)),
3989       (i32 (TFR_condset_ri (i1 PredRegs:$src1), (i32 IntRegs:$src3),
3990                            s12ImmPred:$src2))>;
3991
3992 // Map from p0 = pnot(p0); r0 = mux(p0, r1, #i)
3993 // => r0 = TFR_condset_ir(p0, #i, r1)
3994 def : Pat <(select (not (i1 PredRegs:$src1)), IntRegs:$src2, s12ImmPred:$src3),
3995       (i32 (TFR_condset_ir (i1 PredRegs:$src1), s12ImmPred:$src3,
3996                            (i32 IntRegs:$src2)))>;
3997
3998 // Map from p0 = pnot(p0); if (p0) jump => if (!p0) jump.
3999 def : Pat <(brcond (not (i1 PredRegs:$src1)), bb:$offset),
4000       (J2_jumpf (i1 PredRegs:$src1), bb:$offset)>;
4001
4002 // Map from p2 = pnot(p2); p1 = and(p0, p2) => p1 = and(p0, !p2).
4003 def : Pat <(and (i1 PredRegs:$src1), (not (i1 PredRegs:$src2))),
4004       (i1 (C2_andn (i1 PredRegs:$src1), (i1 PredRegs:$src2)))>;
4005
4006
4007 let AddedComplexity = 100 in
4008 def : Pat <(i64 (zextloadi1 (HexagonCONST32 tglobaladdr:$global))),
4009       (i64 (A2_combinew (A2_tfrsi 0),
4010                        (L2_loadrub_io (CONST32_set tglobaladdr:$global), 0)))>,
4011       Requires<[NoV4T]>;
4012
4013 // Map from i1 loads to 32 bits. This assumes that the i1* is byte aligned.
4014 let AddedComplexity = 10 in
4015 def : Pat <(i32 (zextloadi1 ADDRriS11_0:$addr)),
4016       (i32 (A2_and (i32 (L2_loadrb_io AddrFI:$addr, 0)), (A2_tfrsi 0x1)))>;
4017
4018 // Map from Rdd = sign_extend_inreg(Rss, i32) -> Rdd = A2_sxtw(Rss.lo).
4019 def : Pat <(i64 (sext_inreg (i64 DoubleRegs:$src1), i32)),
4020       (i64 (A2_sxtw (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src1), subreg_loreg))))>;
4021
4022 // Map from Rdd = sign_extend_inreg(Rss, i16) -> Rdd = A2_sxtw(SXTH(Rss.lo)).
4023 def : Pat <(i64 (sext_inreg (i64 DoubleRegs:$src1), i16)),
4024       (i64 (A2_sxtw (i32 (A2_sxth (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src1),
4025                                                  subreg_loreg))))))>;
4026
4027 // Map from Rdd = sign_extend_inreg(Rss, i8) -> Rdd = A2_sxtw(SXTB(Rss.lo)).
4028 def : Pat <(i64 (sext_inreg (i64 DoubleRegs:$src1), i8)),
4029       (i64 (A2_sxtw (i32 (A2_sxtb (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src1),
4030                                                  subreg_loreg))))))>;
4031
4032 // We want to prevent emitting pnot's as much as possible.
4033 // Map brcond with an unsupported setcc to a J2_jumpf.
4034 def : Pat <(brcond (i1 (setne (i32 IntRegs:$src1), (i32 IntRegs:$src2))),
4035                         bb:$offset),
4036       (J2_jumpf (C2_cmpeq (i32 IntRegs:$src1), (i32 IntRegs:$src2)),
4037                 bb:$offset)>;
4038
4039 def : Pat <(brcond (i1 (setne (i32 IntRegs:$src1), s10ImmPred:$src2)),
4040                         bb:$offset),
4041       (J2_jumpf (C2_cmpeqi (i32 IntRegs:$src1), s10ImmPred:$src2), bb:$offset)>;
4042
4043 def : Pat <(brcond (i1 (setne (i1 PredRegs:$src1), (i1 -1))), bb:$offset),
4044       (J2_jumpf (i1 PredRegs:$src1), bb:$offset)>;
4045
4046 def : Pat <(brcond (i1 (setne (i1 PredRegs:$src1), (i1 0))), bb:$offset),
4047       (J2_jumpt (i1 PredRegs:$src1), bb:$offset)>;
4048
4049 // cmp.lt(Rs, Imm) -> !cmp.ge(Rs, Imm) -> !cmp.gt(Rs, Imm-1)
4050 def : Pat <(brcond (i1 (setlt (i32 IntRegs:$src1), s8ImmPred:$src2)),
4051                         bb:$offset),
4052       (J2_jumpf (C2_cmpgti (i32 IntRegs:$src1),
4053                 (DEC_CONST_SIGNED s8ImmPred:$src2)), bb:$offset)>;
4054
4055 // cmp.lt(r0, r1) -> cmp.gt(r1, r0)
4056 def : Pat <(brcond (i1 (setlt (i32 IntRegs:$src1), (i32 IntRegs:$src2))),
4057                         bb:$offset),
4058       (J2_jumpt (C2_cmpgt (i32 IntRegs:$src2), (i32 IntRegs:$src1)), bb:$offset)>;
4059
4060 def : Pat <(brcond (i1 (setuge (i64 DoubleRegs:$src1), (i64 DoubleRegs:$src2))),
4061                    bb:$offset),
4062       (J2_jumpf (C2_cmpgtup (i64 DoubleRegs:$src2), (i64 DoubleRegs:$src1)),
4063                    bb:$offset)>;
4064
4065 def : Pat <(brcond (i1 (setule (i32 IntRegs:$src1), (i32 IntRegs:$src2))),
4066                         bb:$offset),
4067       (J2_jumpf (C2_cmpgtu (i32 IntRegs:$src1), (i32 IntRegs:$src2)),
4068                 bb:$offset)>;
4069
4070 def : Pat <(brcond (i1 (setule (i64 DoubleRegs:$src1), (i64 DoubleRegs:$src2))),
4071                    bb:$offset),
4072       (J2_jumpf (C2_cmpgtup (i64 DoubleRegs:$src1), (i64 DoubleRegs:$src2)),
4073                 bb:$offset)>;
4074
4075 // Map from a 64-bit select to an emulated 64-bit mux.
4076 // Hexagon does not support 64-bit MUXes; so emulate with combines.
4077 def : Pat <(select (i1 PredRegs:$src1), (i64 DoubleRegs:$src2),
4078                    (i64 DoubleRegs:$src3)),
4079       (i64 (A2_combinew (i32 (C2_mux (i1 PredRegs:$src1),
4080                                     (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src2),
4081                                                          subreg_hireg)),
4082                                     (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src3),
4083                                                          subreg_hireg)))),
4084                        (i32 (C2_mux (i1 PredRegs:$src1),
4085                                     (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src2),
4086                                                          subreg_loreg)),
4087                                     (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src3),
4088                                                          subreg_loreg))))))>;
4089
4090 // Map from a 1-bit select to logical ops.
4091 // From LegalizeDAG.cpp: (B1 ? B2 : B3) <=> (B1 & B2)|(!B1&B3).
4092 def : Pat <(select (i1 PredRegs:$src1), (i1 PredRegs:$src2),
4093                    (i1 PredRegs:$src3)),
4094       (C2_or (C2_and (i1 PredRegs:$src1), (i1 PredRegs:$src2)),
4095              (C2_and (C2_not (i1 PredRegs:$src1)), (i1 PredRegs:$src3)))>;
4096
4097 // Map Pd = load(addr) -> Rs = load(addr); Pd = Rs.
4098 def : Pat<(i1 (load ADDRriS11_2:$addr)),
4099       (i1 (C2_tfrrp (i32 (L2_loadrb_io AddrFI:$addr, 0))))>;
4100
4101 // Map for truncating from 64 immediates to 32 bit immediates.
4102 def : Pat<(i32 (trunc (i64 DoubleRegs:$src))),
4103       (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src), subreg_loreg))>;
4104
4105 // Map for truncating from i64 immediates to i1 bit immediates.
4106 def :  Pat<(i1 (trunc (i64 DoubleRegs:$src))),
4107        (i1 (C2_tfrrp (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src),
4108                                           subreg_loreg))))>;
4109
4110 // Map memb(Rs) = Rdd -> memb(Rs) = Rt.
4111 def : Pat<(truncstorei8 (i64 DoubleRegs:$src), ADDRriS11_0:$addr),
4112       (STrib ADDRriS11_0:$addr, (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src),
4113                                                      subreg_loreg)))>;
4114
4115 // Map memh(Rs) = Rdd -> memh(Rs) = Rt.
4116 def : Pat<(truncstorei16 (i64 DoubleRegs:$src), ADDRriS11_0:$addr),
4117       (STrih ADDRriS11_0:$addr, (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src),
4118                                                      subreg_loreg)))>;
4119 // Map memw(Rs) = Rdd -> memw(Rs) = Rt
4120 def : Pat<(truncstorei32 (i64  DoubleRegs:$src), ADDRriS11_0:$addr),
4121       (STriw ADDRriS11_0:$addr, (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src),
4122                                                      subreg_loreg)))>;
4123
4124 // Map memw(Rs) = Rdd -> memw(Rs) = Rt.
4125 def : Pat<(truncstorei32 (i64 DoubleRegs:$src), ADDRriS11_0:$addr),
4126       (STriw ADDRriS11_0:$addr, (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src),
4127                                                      subreg_loreg)))>;
4128
4129 // Map from i1 = constant<-1>; memw(addr) = i1 -> r0 = 1; memw(addr) = r0.
4130 def : Pat<(store (i1 -1), ADDRriS11_2:$addr),
4131       (STrib ADDRriS11_2:$addr, (A2_tfrsi 1))>;
4132
4133
4134 // Map from i1 = constant<-1>; store i1 -> r0 = 1; store r0.
4135 def : Pat<(store (i1 -1), ADDRriS11_2:$addr),
4136       (STrib ADDRriS11_2:$addr, (A2_tfrsi 1))>;
4137
4138 // Map from memb(Rs) = Pd -> Rt = mux(Pd, #0, #1); store Rt.
4139 def : Pat<(store (i1 PredRegs:$src1), ADDRriS11_2:$addr),
4140       (STrib ADDRriS11_2:$addr, (i32 (C2_muxii (i1 PredRegs:$src1), 1, 0)) )>;
4141
4142 // Map Rdd = anyext(Rs) -> Rdd = A2_sxtw(Rs).
4143 // Hexagon_TODO: We can probably use combine but that will cost 2 instructions.
4144 // Better way to do this?
4145 def : Pat<(i64 (anyext (i32 IntRegs:$src1))),
4146       (i64 (A2_sxtw (i32 IntRegs:$src1)))>;
4147
4148 // Map cmple -> cmpgt.
4149 // rs <= rt -> !(rs > rt).
4150 def : Pat<(i1 (setle (i32 IntRegs:$src1), s10ExtPred:$src2)),
4151       (i1 (C2_not (C2_cmpgti (i32 IntRegs:$src1), s10ExtPred:$src2)))>;
4152
4153 // rs <= rt -> !(rs > rt).
4154 def : Pat<(i1 (setle (i32 IntRegs:$src1), (i32 IntRegs:$src2))),
4155       (i1 (C2_not (C2_cmpgt (i32 IntRegs:$src1), (i32 IntRegs:$src2))))>;
4156
4157 // Rss <= Rtt -> !(Rss > Rtt).
4158 def : Pat<(i1 (setle (i64 DoubleRegs:$src1), (i64 DoubleRegs:$src2))),
4159       (i1 (C2_not (C2_cmpgtp (i64 DoubleRegs:$src1), (i64 DoubleRegs:$src2))))>;
4160
4161 // Map cmpne -> cmpeq.
4162 // Hexagon_TODO: We should improve on this.
4163 // rs != rt -> !(rs == rt).
4164 def : Pat <(i1 (setne (i32 IntRegs:$src1), s10ExtPred:$src2)),
4165       (i1 (C2_not(i1 (C2_cmpeqi (i32 IntRegs:$src1), s10ExtPred:$src2))))>;
4166
4167 // Map cmpne(Rs) -> !cmpeqe(Rs).
4168 // rs != rt -> !(rs == rt).
4169 def : Pat <(i1 (setne (i32 IntRegs:$src1), (i32 IntRegs:$src2))),
4170       (i1 (C2_not (i1 (C2_cmpeq (i32 IntRegs:$src1), (i32 IntRegs:$src2)))))>;
4171
4172 // Convert setne back to xor for hexagon since we compute w/ pred registers.
4173 def : Pat <(i1 (setne (i1 PredRegs:$src1), (i1 PredRegs:$src2))),
4174       (i1 (C2_xor (i1 PredRegs:$src1), (i1 PredRegs:$src2)))>;
4175
4176 // Map cmpne(Rss) -> !cmpew(Rss).
4177 // rs != rt -> !(rs == rt).
4178 def : Pat <(i1 (setne (i64 DoubleRegs:$src1), (i64 DoubleRegs:$src2))),
4179       (i1 (C2_not (i1 (C2_cmpeqp (i64 DoubleRegs:$src1),
4180                                      (i64 DoubleRegs:$src2)))))>;
4181
4182 // Map cmpge(Rs, Rt) -> !(cmpgt(Rs, Rt).
4183 // rs >= rt -> !(rt > rs).
4184 def : Pat <(i1 (setge (i32 IntRegs:$src1), (i32 IntRegs:$src2))),
4185       (i1 (C2_not (i1 (C2_cmpgt (i32 IntRegs:$src2), (i32 IntRegs:$src1)))))>;
4186
4187 // cmpge(Rs, Imm) -> cmpgt(Rs, Imm-1)
4188 def : Pat <(i1 (setge (i32 IntRegs:$src1), s8ExtPred:$src2)),
4189       (i1 (C2_cmpgti (i32 IntRegs:$src1), (DEC_CONST_SIGNED s8ExtPred:$src2)))>;
4190
4191 // Map cmpge(Rss, Rtt) -> !cmpgt(Rtt, Rss).
4192 // rss >= rtt -> !(rtt > rss).
4193 def : Pat <(i1 (setge (i64 DoubleRegs:$src1), (i64 DoubleRegs:$src2))),
4194       (i1 (C2_not (i1 (C2_cmpgtp (i64 DoubleRegs:$src2),
4195                                 (i64 DoubleRegs:$src1)))))>;
4196
4197 // Map cmplt(Rs, Imm) -> !cmpge(Rs, Imm).
4198 // !cmpge(Rs, Imm) -> !cmpgt(Rs, Imm-1).
4199 // rs < rt -> !(rs >= rt).
4200 def : Pat <(i1 (setlt (i32 IntRegs:$src1), s8ExtPred:$src2)),
4201       (i1 (C2_not (C2_cmpgti (i32 IntRegs:$src1), (DEC_CONST_SIGNED s8ExtPred:$src2))))>;
4202
4203 // Map cmplt(Rs, Rt) -> cmpgt(Rt, Rs).
4204 // rs < rt -> rt > rs.
4205 // We can let assembler map it, or we can do in the compiler itself.
4206 def : Pat <(i1 (setlt (i32 IntRegs:$src1), (i32 IntRegs:$src2))),
4207       (i1 (C2_cmpgt (i32 IntRegs:$src2), (i32 IntRegs:$src1)))>;
4208
4209 // Map cmplt(Rss, Rtt) -> cmpgt(Rtt, Rss).
4210 // rss < rtt -> (rtt > rss).
4211 def : Pat <(i1 (setlt (i64 DoubleRegs:$src1), (i64 DoubleRegs:$src2))),
4212       (i1 (C2_cmpgtp (i64 DoubleRegs:$src2), (i64 DoubleRegs:$src1)))>;
4213
4214 // Map from cmpltu(Rs, Rd) -> cmpgtu(Rd, Rs)
4215 // rs < rt -> rt > rs.
4216 // We can let assembler map it, or we can do in the compiler itself.
4217 def : Pat <(i1 (setult (i32 IntRegs:$src1), (i32 IntRegs:$src2))),
4218       (i1 (C2_cmpgtu (i32 IntRegs:$src2), (i32 IntRegs:$src1)))>;
4219
4220 // Map from cmpltu(Rss, Rdd) -> cmpgtu(Rdd, Rss).
4221 // rs < rt -> rt > rs.
4222 def : Pat <(i1 (setult (i64 DoubleRegs:$src1), (i64 DoubleRegs:$src2))),
4223       (i1 (C2_cmpgtup (i64 DoubleRegs:$src2), (i64 DoubleRegs:$src1)))>;
4224
4225 // Generate cmpgeu(Rs, #0) -> cmpeq(Rs, Rs)
4226 def : Pat <(i1 (setuge (i32 IntRegs:$src1), 0)),
4227       (i1 (C2_cmpeq (i32 IntRegs:$src1), (i32 IntRegs:$src1)))>;
4228
4229 // Generate cmpgeu(Rs, #u8) -> cmpgtu(Rs, #u8 -1)
4230 def : Pat <(i1 (setuge (i32 IntRegs:$src1), u8ExtPred:$src2)),
4231       (i1 (C2_cmpgtui (i32 IntRegs:$src1), (DEC_CONST_UNSIGNED u8ExtPred:$src2)))>;
4232
4233 // Generate cmpgtu(Rs, #u9)
4234 def : Pat <(i1 (setugt (i32 IntRegs:$src1), u9ExtPred:$src2)),
4235       (i1 (C2_cmpgtui (i32 IntRegs:$src1), u9ExtPred:$src2))>;
4236
4237 // Map from Rs >= Rt -> !(Rt > Rs).
4238 // rs >= rt -> !(rt > rs).
4239 def : Pat <(i1 (setuge (i32 IntRegs:$src1), (i32 IntRegs:$src2))),
4240       (i1 (C2_not (C2_cmpgtu (i32 IntRegs:$src2), (i32 IntRegs:$src1))))>;
4241
4242 // Map from Rs >= Rt -> !(Rt > Rs).
4243 // rs >= rt -> !(rt > rs).
4244 def : Pat <(i1 (setuge (i64 DoubleRegs:$src1), (i64 DoubleRegs:$src2))),
4245       (i1 (C2_not (C2_cmpgtup (i64 DoubleRegs:$src2), (i64 DoubleRegs:$src1))))>;
4246
4247 // Map from cmpleu(Rs, Rt) -> !cmpgtu(Rs, Rt).
4248 // Map from (Rs <= Rt) -> !(Rs > Rt).
4249 def : Pat <(i1 (setule (i32 IntRegs:$src1), (i32 IntRegs:$src2))),
4250       (i1 (C2_not (C2_cmpgtu (i32 IntRegs:$src1), (i32 IntRegs:$src2))))>;
4251
4252 // Map from cmpleu(Rss, Rtt) -> !cmpgtu(Rss, Rtt-1).
4253 // Map from (Rs <= Rt) -> !(Rs > Rt).
4254 def : Pat <(i1 (setule (i64 DoubleRegs:$src1), (i64 DoubleRegs:$src2))),
4255       (i1 (C2_not (C2_cmpgtup (i64 DoubleRegs:$src1), (i64 DoubleRegs:$src2))))>;
4256
4257 // Sign extends.
4258 // i1 -> i32
4259 def : Pat <(i32 (sext (i1 PredRegs:$src1))),
4260       (i32 (C2_muxii (i1 PredRegs:$src1), -1, 0))>;
4261
4262 // i1 -> i64
4263 def : Pat <(i64 (sext (i1 PredRegs:$src1))),
4264       (i64 (A2_combinew (A2_tfrsi -1), (C2_muxii (i1 PredRegs:$src1), -1, 0)))>;
4265
4266 // Convert sign-extended load back to load and sign extend.
4267 // i8 -> i64
4268 def:  Pat <(i64 (sextloadi8 ADDRriS11_0:$src1)),
4269       (i64 (A2_sxtw (L2_loadrb_io AddrFI:$src1, 0)))>;
4270
4271 // Convert any-extended load back to load and sign extend.
4272 // i8 -> i64
4273 def:  Pat <(i64 (extloadi8 ADDRriS11_0:$src1)),
4274       (i64 (A2_sxtw (L2_loadrb_io AddrFI:$src1, 0)))>;
4275
4276 // Convert sign-extended load back to load and sign extend.
4277 // i16 -> i64
4278 def:  Pat <(i64 (sextloadi16 ADDRriS11_1:$src1)),
4279       (i64 (A2_sxtw (L2_loadrh_io AddrFI:$src1, 0)))>;
4280
4281 // Convert sign-extended load back to load and sign extend.
4282 // i32 -> i64
4283 def:  Pat <(i64 (sextloadi32 ADDRriS11_2:$src1)),
4284       (i64 (A2_sxtw (L2_loadri_io AddrFI:$src1, 0)))>;
4285
4286
4287 // Zero extends.
4288 // i1 -> i32
4289 def : Pat <(i32 (zext (i1 PredRegs:$src1))),
4290       (i32 (C2_muxii (i1 PredRegs:$src1), 1, 0))>;
4291
4292 // i1 -> i64
4293 def : Pat <(i64 (zext (i1 PredRegs:$src1))),
4294       (i64 (A2_combinew (A2_tfrsi 0), (C2_muxii (i1 PredRegs:$src1), 1, 0)))>,
4295       Requires<[NoV4T]>;
4296
4297 // i32 -> i64
4298 def : Pat <(i64 (zext (i32 IntRegs:$src1))),
4299       (i64 (A2_combinew (A2_tfrsi 0), (i32 IntRegs:$src1)))>,
4300       Requires<[NoV4T]>;
4301
4302 // i8 -> i64
4303 def:  Pat <(i64 (zextloadi8 ADDRriS11_0:$src1)),
4304       (i64 (A2_combinew (A2_tfrsi 0), (L2_loadrub_io AddrFI:$src1, 0)))>,
4305       Requires<[NoV4T]>;
4306
4307 let AddedComplexity = 20 in
4308 def:  Pat <(i64 (zextloadi8 (add (i32 IntRegs:$src1),
4309                                 s11_0ExtPred:$offset))),
4310       (i64 (A2_combinew (A2_tfrsi 0), (L2_loadrub_io IntRegs:$src1,
4311                                   s11_0ExtPred:$offset)))>,
4312       Requires<[NoV4T]>;
4313
4314 // i1 -> i64
4315 def:  Pat <(i64 (zextloadi1 ADDRriS11_0:$src1)),
4316       (i64 (A2_combinew (A2_tfrsi 0), (L2_loadrub_io AddrFI:$src1, 0)))>,
4317       Requires<[NoV4T]>;
4318
4319 let AddedComplexity = 20 in
4320 def:  Pat <(i64 (zextloadi1 (add (i32 IntRegs:$src1),
4321                                 s11_0ExtPred:$offset))),
4322       (i64 (A2_combinew (A2_tfrsi 0), (L2_loadrub_io IntRegs:$src1,
4323                                   s11_0ExtPred:$offset)))>,
4324       Requires<[NoV4T]>;
4325
4326 // i16 -> i64
4327 def:  Pat <(i64 (zextloadi16 ADDRriS11_1:$src1)),
4328       (i64 (A2_combinew (A2_tfrsi 0), (L2_loadruh_io AddrFI:$src1, 0)))>,
4329       Requires<[NoV4T]>;
4330
4331 let AddedComplexity = 20 in
4332 def:  Pat <(i64 (zextloadi16 (add (i32 IntRegs:$src1),
4333                                   s11_1ExtPred:$offset))),
4334       (i64 (A2_combinew (A2_tfrsi 0), (L2_loadruh_io IntRegs:$src1,
4335                                   s11_1ExtPred:$offset)))>,
4336       Requires<[NoV4T]>;
4337
4338 // i32 -> i64
4339 def:  Pat <(i64 (zextloadi32 ADDRriS11_2:$src1)),
4340       (i64 (A2_combinew (A2_tfrsi 0), (L2_loadri_io AddrFI:$src1, 0)))>,
4341       Requires<[NoV4T]>;
4342
4343 let AddedComplexity = 100 in
4344 def:  Pat <(i64 (zextloadi32 (i32 (add IntRegs:$src1, s11_2ExtPred:$offset)))),
4345       (i64 (A2_combinew (A2_tfrsi 0), (L2_loadri_io IntRegs:$src1,
4346                                   s11_2ExtPred:$offset)))>,
4347       Requires<[NoV4T]>;
4348
4349 let AddedComplexity = 10 in
4350 def:  Pat <(i32 (zextloadi1 ADDRriS11_0:$src1)),
4351       (i32 (L2_loadri_io AddrFI:$src1, 0))>;
4352
4353 // Map from Rs = Pd to Pd = mux(Pd, #1, #0)
4354 def : Pat <(i32 (zext (i1 PredRegs:$src1))),
4355       (i32 (C2_muxii (i1 PredRegs:$src1), 1, 0))>;
4356
4357 // Map from Rs = Pd to Pd = mux(Pd, #1, #0)
4358 def : Pat <(i32 (anyext (i1 PredRegs:$src1))),
4359       (i32 (C2_muxii (i1 PredRegs:$src1), 1, 0))>;
4360
4361 // Map from Rss = Pd to Rdd = A2_sxtw (mux(Pd, #1, #0))
4362 def : Pat <(i64 (anyext (i1 PredRegs:$src1))),
4363       (i64 (A2_sxtw (i32 (C2_muxii (i1 PredRegs:$src1), 1, 0))))>;
4364
4365
4366 let AddedComplexity = 100 in
4367 def: Pat<(i64 (or (i64 (shl (i64 DoubleRegs:$srcHigh),
4368                            (i32 32))),
4369                (i64 (zextloadi32 (i32 (add IntRegs:$src2,
4370                                          s11_2ExtPred:$offset2)))))),
4371         (i64 (A2_combinew (EXTRACT_SUBREG (i64 DoubleRegs:$srcHigh), subreg_loreg),
4372                         (L2_loadri_io IntRegs:$src2,
4373                                        s11_2ExtPred:$offset2)))>;
4374
4375 def: Pat<(i64 (or (i64 (shl (i64 DoubleRegs:$srcHigh),
4376                            (i32 32))),
4377                (i64 (zextloadi32 ADDRriS11_2:$srcLow)))),
4378         (i64 (A2_combinew (EXTRACT_SUBREG (i64 DoubleRegs:$srcHigh), subreg_loreg),
4379                         (L2_loadri_io AddrFI:$srcLow, 0)))>;
4380
4381 def: Pat<(i64 (or (i64 (shl (i64 DoubleRegs:$srcHigh),
4382                            (i32 32))),
4383                (i64 (zext (i32 IntRegs:$srcLow))))),
4384         (i64 (A2_combinew (EXTRACT_SUBREG (i64 DoubleRegs:$srcHigh), subreg_loreg),
4385                         IntRegs:$srcLow))>;
4386
4387 let AddedComplexity = 100 in
4388 def: Pat<(i64 (or (i64 (shl (i64 DoubleRegs:$srcHigh),
4389                            (i32 32))),
4390                (i64 (zextloadi32 (i32 (add IntRegs:$src2,
4391                                          s11_2ExtPred:$offset2)))))),
4392         (i64 (A2_combinew (EXTRACT_SUBREG (i64 DoubleRegs:$srcHigh), subreg_loreg),
4393                         (L2_loadri_io IntRegs:$src2,
4394                                        s11_2ExtPred:$offset2)))>;
4395
4396 def: Pat<(i64 (or (i64 (shl (i64 DoubleRegs:$srcHigh),
4397                            (i32 32))),
4398                (i64 (zextloadi32 ADDRriS11_2:$srcLow)))),
4399         (i64 (A2_combinew (EXTRACT_SUBREG (i64 DoubleRegs:$srcHigh), subreg_loreg),
4400                         (L2_loadri_io AddrFI:$srcLow, 0)))>;
4401
4402 def: Pat<(i64 (or (i64 (shl (i64 DoubleRegs:$srcHigh),
4403                            (i32 32))),
4404                (i64 (zext (i32 IntRegs:$srcLow))))),
4405         (i64 (A2_combinew (EXTRACT_SUBREG (i64 DoubleRegs:$srcHigh), subreg_loreg),
4406                         IntRegs:$srcLow))>;
4407
4408 // Any extended 64-bit load.
4409 // anyext i32 -> i64
4410 def:  Pat <(i64 (extloadi32 ADDRriS11_2:$src1)),
4411       (i64 (A2_combinew (A2_tfrsi 0), (L2_loadri_io AddrFI:$src1, 0)))>,
4412       Requires<[NoV4T]>;
4413
4414 // When there is an offset we should prefer the pattern below over the pattern above.
4415 // The complexity of the above is 13 (gleaned from HexagonGenDAGIsel.inc)
4416 // So this complexity below is comfortably higher to allow for choosing the below.
4417 // If this is not done then we generate addresses such as
4418 // ********************************************
4419 //        r1 = add (r0, #4)
4420 //        r1 = memw(r1 + #0)
4421 //  instead of
4422 //        r1 = memw(r0 + #4)
4423 // ********************************************
4424 let AddedComplexity = 100 in
4425 def:  Pat <(i64 (extloadi32 (i32 (add IntRegs:$src1, s11_2ExtPred:$offset)))),
4426       (i64 (A2_combinew (A2_tfrsi 0), (L2_loadri_io IntRegs:$src1,
4427                                   s11_2ExtPred:$offset)))>,
4428       Requires<[NoV4T]>;
4429
4430 // anyext i16 -> i64.
4431 def:  Pat <(i64 (extloadi16 ADDRriS11_2:$src1)),
4432       (i64 (A2_combinew (A2_tfrsi 0), (L2_loadrh_io AddrFI:$src1, 0)))>,
4433       Requires<[NoV4T]>;
4434
4435 let AddedComplexity = 20 in
4436 def:  Pat <(i64 (extloadi16 (add (i32 IntRegs:$src1),
4437                                   s11_1ExtPred:$offset))),
4438       (i64 (A2_combinew (A2_tfrsi 0), (L2_loadrh_io IntRegs:$src1,
4439                                   s11_1ExtPred:$offset)))>,
4440       Requires<[NoV4T]>;
4441
4442 // Map from Rdd = zxtw(Rs) -> Rdd = combine(0, Rs).
4443 def : Pat<(i64 (zext (i32 IntRegs:$src1))),
4444       (i64 (A2_combinew (A2_tfrsi 0), (i32 IntRegs:$src1)))>,
4445       Requires<[NoV4T]>;
4446
4447 // Multiply 64-bit unsigned and use upper result.
4448 def : Pat <(mulhu (i64 DoubleRegs:$src1), (i64 DoubleRegs:$src2)),
4449       (i64
4450        (M2_dpmpyuu_acc_s0
4451         (i64
4452          (A2_combinew
4453           (A2_tfrsi 0),
4454            (i32
4455             (EXTRACT_SUBREG
4456              (i64
4457               (S2_lsr_i_p
4458                (i64
4459                 (M2_dpmpyuu_acc_s0
4460                  (i64
4461                   (M2_dpmpyuu_acc_s0
4462                    (i64
4463                     (A2_combinew (A2_tfrsi 0),
4464                      (i32
4465                       (EXTRACT_SUBREG
4466                        (i64
4467                         (S2_lsr_i_p
4468                          (i64
4469                           (M2_dpmpyuu_s0 
4470                             (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src1),
4471                                                        subreg_loreg)),
4472                                   (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src2),
4473                                                        subreg_loreg)))), 32)),
4474                        subreg_loreg)))),
4475                   (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src1), subreg_hireg)),
4476                   (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src2), subreg_loreg)))),
4477                  (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src1), subreg_loreg)),
4478                  (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src2), subreg_hireg)))),
4479                32)), subreg_loreg)))),
4480         (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src1), subreg_hireg)),
4481         (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src2), subreg_hireg))))>;
4482
4483 // Multiply 64-bit signed and use upper result.
4484 def : Pat <(mulhs (i64 DoubleRegs:$src1), (i64 DoubleRegs:$src2)),
4485       (i64
4486        (M2_dpmpyss_acc_s0
4487         (i64
4488          (A2_combinew (A2_tfrsi 0),
4489           (i32
4490            (EXTRACT_SUBREG
4491             (i64
4492              (S2_lsr_i_p
4493               (i64
4494                (M2_dpmpyss_acc_s0
4495                 (i64
4496                  (M2_dpmpyss_acc_s0
4497                   (i64
4498                    (A2_combinew (A2_tfrsi 0),
4499                     (i32
4500                      (EXTRACT_SUBREG
4501                       (i64
4502                        (S2_lsr_i_p
4503                         (i64
4504                          (M2_dpmpyuu_s0 
4505                            (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src1),
4506                                                       subreg_loreg)),
4507                                  (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src2),
4508                                                       subreg_loreg)))), 32)),
4509                       subreg_loreg)))),
4510                   (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src1), subreg_hireg)),
4511                   (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src2), subreg_loreg)))),
4512                 (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src1), subreg_loreg)),
4513                 (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src2), subreg_hireg)))),
4514               32)), subreg_loreg)))),
4515         (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src1), subreg_hireg)),
4516         (i32 (EXTRACT_SUBREG (i64 DoubleRegs:$src2), subreg_hireg))))>;
4517
4518 // Hexagon specific ISD nodes.
4519 //def SDTHexagonADJDYNALLOC : SDTypeProfile<1, 2, [SDTCisSameAs<0, 1>]>;
4520 def SDTHexagonADJDYNALLOC : SDTypeProfile<1, 2,
4521                                   [SDTCisVT<0, i32>, SDTCisVT<1, i32>]>;
4522 def Hexagon_ADJDYNALLOC : SDNode<"HexagonISD::ADJDYNALLOC",
4523                                   SDTHexagonADJDYNALLOC>;
4524 // Needed to tag these instructions for stack layout.
4525 let usesCustomInserter = 1 in
4526 def ADJDYNALLOC : ALU32_ri<(outs IntRegs:$dst), (ins IntRegs:$src1,
4527                                                      s16Imm:$src2),
4528                   "$dst = add($src1, #$src2)",
4529                   [(set (i32 IntRegs:$dst),
4530                         (Hexagon_ADJDYNALLOC (i32 IntRegs:$src1),
4531                                              s16ImmPred:$src2))]>;
4532
4533 def SDTHexagonARGEXTEND : SDTypeProfile<1, 1, [SDTCisVT<0, i32>]>;
4534 def Hexagon_ARGEXTEND : SDNode<"HexagonISD::ARGEXTEND", SDTHexagonARGEXTEND>;
4535 def ARGEXTEND : ALU32_rr <(outs IntRegs:$dst), (ins IntRegs:$src1),
4536                 "$dst = $src1",
4537                 [(set (i32 IntRegs:$dst),
4538                       (Hexagon_ARGEXTEND (i32 IntRegs:$src1)))]>;
4539
4540 let AddedComplexity = 100 in
4541 def : Pat<(i32 (sext_inreg (Hexagon_ARGEXTEND (i32 IntRegs:$src1)), i16)),
4542       (COPY (i32 IntRegs:$src1))>;
4543
4544 def HexagonWrapperJT: SDNode<"HexagonISD::WrapperJT", SDTIntUnaryOp>;
4545
4546 def : Pat<(HexagonWrapperJT tjumptable:$dst),
4547           (i32 (CONST32_set_jt tjumptable:$dst))>;
4548
4549 // XTYPE/SHIFT
4550 //
4551 //===----------------------------------------------------------------------===//
4552 // Template Class
4553 // Shift by immediate/register and accumulate/logical
4554 //===----------------------------------------------------------------------===//
4555
4556 // Rx[+-&|]=asr(Rs,#u5)
4557 // Rx[+-&|^]=lsr(Rs,#u5)
4558 // Rx[+-&|^]=asl(Rs,#u5)
4559
4560 let hasNewValue = 1, opNewValue = 0 in
4561 class T_shift_imm_acc_r <string opc1, string opc2, SDNode OpNode1,
4562                          SDNode OpNode2, bits<3> majOp, bits<2> minOp>
4563   : SInst_acc<(outs IntRegs:$Rx),
4564               (ins IntRegs:$src1, IntRegs:$Rs, u5Imm:$u5),
4565   "$Rx "#opc2#opc1#"($Rs, #$u5)",
4566   [(set (i32 IntRegs:$Rx),
4567          (OpNode2 (i32 IntRegs:$src1),
4568                   (OpNode1 (i32 IntRegs:$Rs), u5ImmPred:$u5)))],
4569   "$src1 = $Rx", S_2op_tc_2_SLOT23> {
4570     bits<5> Rx;
4571     bits<5> Rs;
4572     bits<5> u5;
4573
4574     let IClass = 0b1000;
4575
4576     let Inst{27-24} = 0b1110;
4577     let Inst{23-22} = majOp{2-1};
4578     let Inst{13} = 0b0;
4579     let Inst{7} = majOp{0};
4580     let Inst{6-5} = minOp;
4581     let Inst{4-0} = Rx;
4582     let Inst{20-16} = Rs;
4583     let Inst{12-8} = u5;
4584   }
4585
4586 // Rx[+-&|]=asr(Rs,Rt)
4587 // Rx[+-&|^]=lsr(Rs,Rt)
4588 // Rx[+-&|^]=asl(Rs,Rt)
4589
4590 let hasNewValue = 1, opNewValue = 0 in
4591 class T_shift_reg_acc_r <string opc1, string opc2, SDNode OpNode1,
4592                          SDNode OpNode2, bits<2> majOp, bits<2> minOp>
4593   : SInst_acc<(outs IntRegs:$Rx),
4594               (ins IntRegs:$src1, IntRegs:$Rs, IntRegs:$Rt),
4595   "$Rx "#opc2#opc1#"($Rs, $Rt)",
4596   [(set (i32 IntRegs:$Rx),
4597          (OpNode2 (i32 IntRegs:$src1),
4598                   (OpNode1 (i32 IntRegs:$Rs), (i32 IntRegs:$Rt))))],
4599   "$src1 = $Rx", S_3op_tc_2_SLOT23 > {
4600     bits<5> Rx;
4601     bits<5> Rs;
4602     bits<5> Rt;
4603
4604     let IClass = 0b1100;
4605
4606     let Inst{27-24} = 0b1100;
4607     let Inst{23-22} = majOp;
4608     let Inst{7-6} = minOp;
4609     let Inst{4-0} = Rx;
4610     let Inst{20-16} = Rs;
4611     let Inst{12-8} = Rt;
4612   }
4613
4614 // Rxx[+-&|]=asr(Rss,#u6)
4615 // Rxx[+-&|^]=lsr(Rss,#u6)
4616 // Rxx[+-&|^]=asl(Rss,#u6)
4617
4618 class T_shift_imm_acc_p <string opc1, string opc2, SDNode OpNode1,
4619                          SDNode OpNode2, bits<3> majOp, bits<2> minOp>
4620   : SInst_acc<(outs DoubleRegs:$Rxx),
4621               (ins DoubleRegs:$src1, DoubleRegs:$Rss, u6Imm:$u6),
4622   "$Rxx "#opc2#opc1#"($Rss, #$u6)",
4623   [(set (i64 DoubleRegs:$Rxx),
4624         (OpNode2 (i64 DoubleRegs:$src1),
4625                  (OpNode1 (i64 DoubleRegs:$Rss), u6ImmPred:$u6)))],
4626   "$src1 = $Rxx", S_2op_tc_2_SLOT23> {
4627     bits<5> Rxx;
4628     bits<5> Rss;
4629     bits<6> u6;
4630
4631     let IClass = 0b1000;
4632
4633     let Inst{27-24} = 0b0010;
4634     let Inst{23-22} = majOp{2-1};
4635     let Inst{7} = majOp{0};
4636     let Inst{6-5} = minOp;
4637     let Inst{4-0} = Rxx;
4638     let Inst{20-16} = Rss;
4639     let Inst{13-8} = u6;
4640   }
4641
4642
4643 // Rxx[+-&|]=asr(Rss,Rt)
4644 // Rxx[+-&|^]=lsr(Rss,Rt)
4645 // Rxx[+-&|^]=asl(Rss,Rt)
4646 // Rxx[+-&|^]=lsl(Rss,Rt)
4647
4648 class T_shift_reg_acc_p <string opc1, string opc2, SDNode OpNode1,
4649                          SDNode OpNode2, bits<3> majOp, bits<2> minOp>
4650   : SInst_acc<(outs DoubleRegs:$Rxx),
4651               (ins DoubleRegs:$src1, DoubleRegs:$Rss, IntRegs:$Rt),
4652   "$Rxx "#opc2#opc1#"($Rss, $Rt)",
4653   [(set (i64 DoubleRegs:$Rxx),
4654         (OpNode2 (i64 DoubleRegs:$src1),
4655                  (OpNode1 (i64 DoubleRegs:$Rss), (i32 IntRegs:$Rt))))],
4656   "$src1 = $Rxx", S_3op_tc_2_SLOT23> {
4657     bits<5> Rxx;
4658     bits<5> Rss;
4659     bits<5> Rt;
4660
4661     let IClass = 0b1100;
4662
4663     let Inst{27-24} = 0b1011;
4664     let Inst{23-21} = majOp;
4665     let Inst{20-16} = Rss;
4666     let Inst{12-8} = Rt;
4667     let Inst{7-6} = minOp;
4668     let Inst{4-0} = Rxx;
4669   }
4670
4671 //===----------------------------------------------------------------------===//
4672 // Multi-class for the shift instructions with logical/arithmetic operators.
4673 //===----------------------------------------------------------------------===//
4674
4675 multiclass xtype_imm_base<string OpcStr1, string OpcStr2, SDNode OpNode1,
4676                          SDNode OpNode2, bits<3> majOp, bits<2> minOp > {
4677   def _i_r#NAME : T_shift_imm_acc_r< OpcStr1, OpcStr2, OpNode1,
4678                                      OpNode2, majOp, minOp >;
4679   def _i_p#NAME : T_shift_imm_acc_p< OpcStr1, OpcStr2, OpNode1,
4680                                      OpNode2, majOp, minOp >;
4681 }
4682
4683 multiclass xtype_imm_acc<string opc1, SDNode OpNode, bits<2>minOp> {
4684   let AddedComplexity = 100 in
4685   defm _acc  : xtype_imm_base< opc1, "+= ", OpNode, add, 0b001, minOp>;
4686
4687   defm _nac  : xtype_imm_base< opc1, "-= ", OpNode, sub, 0b000, minOp>;
4688   defm _and  : xtype_imm_base< opc1, "&= ", OpNode, and, 0b010, minOp>;
4689   defm _or   : xtype_imm_base< opc1, "|= ", OpNode,  or, 0b011, minOp>;
4690 }
4691
4692 multiclass xtype_xor_imm_acc<string opc1, SDNode OpNode, bits<2>minOp> {
4693 let AddedComplexity = 100 in
4694   defm _xacc  : xtype_imm_base< opc1, "^= ", OpNode, xor, 0b100, minOp>;
4695 }
4696
4697 let isCodeGenOnly = 0 in {
4698 defm S2_asr : xtype_imm_acc<"asr", sra, 0b00>;
4699
4700 defm S2_lsr : xtype_imm_acc<"lsr", srl, 0b01>,
4701               xtype_xor_imm_acc<"lsr", srl, 0b01>;
4702
4703 defm S2_asl : xtype_imm_acc<"asl", shl, 0b10>,
4704               xtype_xor_imm_acc<"asl", shl, 0b10>;
4705 }
4706
4707 multiclass xtype_reg_acc_r<string opc1, SDNode OpNode, bits<2>minOp> {
4708   let AddedComplexity = 100 in
4709   def _acc : T_shift_reg_acc_r <opc1, "+= ", OpNode, add, 0b11, minOp>;
4710
4711   def _nac : T_shift_reg_acc_r <opc1, "-= ", OpNode, sub, 0b10, minOp>;
4712   def _and : T_shift_reg_acc_r <opc1, "&= ", OpNode, and, 0b01, minOp>;
4713   def _or  : T_shift_reg_acc_r <opc1, "|= ", OpNode,  or, 0b00, minOp>;
4714 }
4715
4716 multiclass xtype_reg_acc_p<string opc1, SDNode OpNode, bits<2>minOp> {
4717   let AddedComplexity = 100 in
4718   def _acc : T_shift_reg_acc_p <opc1, "+= ", OpNode, add, 0b110, minOp>;
4719
4720   def _nac : T_shift_reg_acc_p <opc1, "-= ", OpNode, sub, 0b100, minOp>;
4721   def _and : T_shift_reg_acc_p <opc1, "&= ", OpNode, and, 0b010, minOp>;
4722   def _or  : T_shift_reg_acc_p <opc1, "|= ", OpNode,  or, 0b000, minOp>;
4723   def _xor : T_shift_reg_acc_p <opc1, "^= ", OpNode, xor, 0b011, minOp>;
4724 }
4725
4726 multiclass xtype_reg_acc<string OpcStr, SDNode OpNode, bits<2> minOp > {
4727   defm _r_r : xtype_reg_acc_r <OpcStr, OpNode, minOp>;
4728   defm _r_p : xtype_reg_acc_p <OpcStr, OpNode, minOp>;
4729 }
4730
4731 let isCodeGenOnly = 0 in {
4732 defm S2_asl : xtype_reg_acc<"asl", shl, 0b10>;
4733 defm S2_asr : xtype_reg_acc<"asr", sra, 0b00>;
4734 defm S2_lsr : xtype_reg_acc<"lsr", srl, 0b01>;
4735 defm S2_lsl : xtype_reg_acc<"lsl", shl, 0b11>;
4736 }
4737
4738 //===----------------------------------------------------------------------===//
4739 let hasSideEffects = 0 in
4740 class T_S3op_1 <string mnemonic, RegisterClass RC, bits<2> MajOp, bits<3> MinOp,
4741                 bit SwapOps, bit isSat = 0, bit isRnd = 0, bit hasShift = 0>
4742   : SInst <(outs RC:$dst),
4743            (ins DoubleRegs:$src1, DoubleRegs:$src2),
4744   "$dst = "#mnemonic#"($src1, $src2)"#!if(isRnd, ":rnd", "")
4745                                      #!if(hasShift,":>>1","")
4746                                      #!if(isSat, ":sat", ""),
4747   [], "", S_3op_tc_2_SLOT23 > {
4748     bits<5> dst;
4749     bits<5> src1;
4750     bits<5> src2;
4751
4752     let IClass = 0b1100;
4753
4754     let Inst{27-24} = 0b0001;
4755     let Inst{23-22} = MajOp;
4756     let Inst{20-16} = !if (SwapOps, src2, src1);
4757     let Inst{12-8}  = !if (SwapOps, src1, src2);
4758     let Inst{7-5}   = MinOp;
4759     let Inst{4-0}   = dst;
4760   }
4761
4762 class T_S3op_64 <string mnemonic, bits<2> MajOp, bits<3> MinOp, bit SwapOps,
4763                  bit isSat = 0, bit isRnd = 0, bit hasShift = 0 >
4764   : T_S3op_1 <mnemonic, DoubleRegs, MajOp, MinOp, SwapOps,
4765               isSat, isRnd, hasShift>;
4766
4767 let isCodeGenOnly = 0 in
4768 def S2_lfsp : T_S3op_64 < "lfs", 0b10, 0b110, 0>;
4769
4770 //===----------------------------------------------------------------------===//
4771 // Template class used by vector shift, vector rotate, vector neg,
4772 // 32-bit shift, 64-bit shifts, etc.
4773 //===----------------------------------------------------------------------===//
4774
4775 let hasSideEffects = 0 in
4776 class T_S3op_3 <string mnemonic, RegisterClass RC, bits<2> MajOp,
4777                  bits<2> MinOp, bit isSat = 0, list<dag> pattern = [] >
4778   : SInst <(outs RC:$dst),
4779            (ins RC:$src1, IntRegs:$src2),
4780   "$dst = "#mnemonic#"($src1, $src2)"#!if(isSat, ":sat", ""),
4781   pattern, "", S_3op_tc_1_SLOT23> {
4782     bits<5> dst;
4783     bits<5> src1;
4784     bits<5> src2;
4785
4786     let IClass = 0b1100;
4787
4788     let Inst{27-24} = !if(!eq(!cast<string>(RC), "IntRegs"), 0b0110, 0b0011);
4789     let Inst{23-22} = MajOp;
4790     let Inst{20-16} = src1;
4791     let Inst{12-8} = src2;
4792     let Inst{7-6} = MinOp;
4793     let Inst{4-0} = dst;
4794   }
4795
4796 let hasNewValue = 1 in
4797 class T_S3op_shift32 <string mnemonic, SDNode OpNode, bits<2> MinOp>
4798   : T_S3op_3 <mnemonic, IntRegs, 0b01, MinOp, 0,
4799     [(set (i32 IntRegs:$dst), (OpNode (i32 IntRegs:$src1),
4800                                       (i32 IntRegs:$src2)))]>;
4801
4802 let hasNewValue = 1, Itinerary = S_3op_tc_2_SLOT23 in
4803 class T_S3op_shift32_Sat <string mnemonic, bits<2> MinOp>
4804   : T_S3op_3 <mnemonic, IntRegs, 0b00, MinOp, 1, []>;
4805
4806
4807 class T_S3op_shift64 <string mnemonic, SDNode OpNode, bits<2> MinOp>
4808   : T_S3op_3 <mnemonic, DoubleRegs, 0b10, MinOp, 0,
4809     [(set (i64 DoubleRegs:$dst), (OpNode (i64 DoubleRegs:$src1),
4810                                          (i32 IntRegs:$src2)))]>;
4811
4812
4813 class T_S3op_shiftVect <string mnemonic, bits<2> MajOp, bits<2> MinOp>
4814   : T_S3op_3 <mnemonic, DoubleRegs, MajOp, MinOp, 0, []>;
4815
4816
4817 // Shift by register
4818 // Rdd=[asr|lsr|asl|lsl](Rss,Rt)
4819
4820 let isCodeGenOnly = 0 in {
4821 def S2_asr_r_p : T_S3op_shift64 < "asr", sra, 0b00>;
4822 def S2_lsr_r_p : T_S3op_shift64 < "lsr", srl, 0b01>;
4823 def S2_asl_r_p : T_S3op_shift64 < "asl", shl, 0b10>;
4824 def S2_lsl_r_p : T_S3op_shift64 < "lsl", shl, 0b11>;
4825 }
4826
4827 // Rd=[asr|lsr|asl|lsl](Rs,Rt)
4828
4829 let isCodeGenOnly = 0 in {
4830 def S2_asr_r_r : T_S3op_shift32<"asr", sra, 0b00>;
4831 def S2_lsr_r_r : T_S3op_shift32<"lsr", srl, 0b01>;
4832 def S2_asl_r_r : T_S3op_shift32<"asl", shl, 0b10>;
4833 def S2_lsl_r_r : T_S3op_shift32<"lsl", shl, 0b11>;
4834 }
4835
4836 // Shift by register with saturation
4837 // Rd=asr(Rs,Rt):sat
4838 // Rd=asl(Rs,Rt):sat
4839
4840 let Defs = [USR_OVF], isCodeGenOnly = 0 in {
4841   def S2_asr_r_r_sat : T_S3op_shift32_Sat<"asr", 0b00>;
4842   def S2_asl_r_r_sat : T_S3op_shift32_Sat<"asl", 0b10>;
4843 }
4844
4845 //===----------------------------------------------------------------------===//
4846 // Template class for 'insert bitfield' instructions
4847 //===----------------------------------------------------------------------===//
4848 let hasSideEffects = 0 in
4849 class T_S3op_insert <string mnemonic, RegisterClass RC>
4850   : SInst <(outs RC:$dst),
4851            (ins RC:$src1, RC:$src2, DoubleRegs:$src3),
4852   "$dst = "#mnemonic#"($src2, $src3)" ,
4853   [], "$src1 = $dst", S_3op_tc_1_SLOT23 > {
4854     bits<5> dst;
4855     bits<5> src2;
4856     bits<5> src3;
4857
4858     let IClass = 0b1100;
4859
4860     let Inst{27-26} = 0b10;
4861     let Inst{25-24} = !if(!eq(!cast<string>(RC), "IntRegs"), 0b00, 0b10);
4862     let Inst{23}    = 0b0;
4863     let Inst{20-16} = src2;
4864     let Inst{12-8}  = src3;
4865     let Inst{4-0}   = dst;
4866   }
4867
4868 let hasSideEffects = 0 in
4869 class T_S2op_insert <bits<4> RegTyBits, RegisterClass RC, Operand ImmOp>
4870   : SInst <(outs RC:$dst), (ins RC:$dst2, RC:$src1, ImmOp:$src2, ImmOp:$src3),
4871   "$dst = insert($src1, #$src2, #$src3)",
4872   [], "$dst2 = $dst", S_2op_tc_2_SLOT23> {
4873     bits<5> dst;
4874     bits<5> src1;
4875     bits<6> src2;
4876     bits<6> src3;
4877     bit bit23;
4878     bit bit13;
4879     string ImmOpStr = !cast<string>(ImmOp);
4880
4881     let bit23 = !if (!eq(ImmOpStr, "u6Imm"), src3{5}, 0);
4882     let bit13 = !if (!eq(ImmOpStr, "u6Imm"), src2{5}, 0);
4883
4884     let IClass = 0b1000;
4885
4886     let Inst{27-24} = RegTyBits;
4887     let Inst{23}    = bit23;
4888     let Inst{22-21} = src3{4-3};
4889     let Inst{20-16} = src1;
4890     let Inst{13}    = bit13;
4891     let Inst{12-8}  = src2{4-0};
4892     let Inst{7-5}   = src3{2-0};
4893     let Inst{4-0}   = dst;
4894   }
4895
4896 // Rx=insert(Rs,Rtt)
4897 // Rx=insert(Rs,#u5,#U5)
4898 let hasNewValue = 1, isCodeGenOnly = 0 in {
4899   def S2_insert_rp : T_S3op_insert <"insert", IntRegs>;
4900   def S2_insert    : T_S2op_insert <0b1111, IntRegs, u5Imm>;
4901 }
4902
4903 // Rxx=insert(Rss,Rtt)
4904 // Rxx=insert(Rss,#u6,#U6)
4905 let isCodeGenOnly = 0 in {
4906 def S2_insertp_rp : T_S3op_insert<"insert", DoubleRegs>;
4907 def S2_insertp    : T_S2op_insert <0b0011, DoubleRegs, u6Imm>;
4908 }
4909
4910 //===----------------------------------------------------------------------===//
4911 // Template class for 'extract bitfield' instructions
4912 //===----------------------------------------------------------------------===//
4913 let hasNewValue = 1, hasSideEffects = 0 in
4914 class T_S3op_extract <string mnemonic, bits<2> MinOp>
4915   : SInst <(outs IntRegs:$Rd), (ins IntRegs:$Rs, DoubleRegs:$Rtt),
4916   "$Rd = "#mnemonic#"($Rs, $Rtt)",
4917   [], "", S_3op_tc_2_SLOT23 > {
4918     bits<5> Rd;
4919     bits<5> Rs;
4920     bits<5> Rtt;
4921
4922     let IClass = 0b1100;
4923
4924     let Inst{27-22} = 0b100100;
4925     let Inst{20-16} = Rs;
4926     let Inst{12-8}  = Rtt;
4927     let Inst{7-6}   = MinOp;
4928     let Inst{4-0}   = Rd;
4929   }
4930
4931 let hasSideEffects = 0 in
4932 class T_S2op_extract <string mnemonic, bits<4> RegTyBits,
4933                       RegisterClass RC, Operand ImmOp>
4934   : SInst <(outs RC:$dst), (ins RC:$src1, ImmOp:$src2, ImmOp:$src3),
4935   "$dst = "#mnemonic#"($src1, #$src2, #$src3)",
4936   [], "", S_2op_tc_2_SLOT23> {
4937     bits<5> dst;
4938     bits<5> src1;
4939     bits<6> src2;
4940     bits<6> src3;
4941     bit bit23;
4942     bit bit13;
4943     string ImmOpStr = !cast<string>(ImmOp);
4944
4945     let bit23 = !if (!eq(ImmOpStr, "u6Imm"), src3{5},
4946                 !if (!eq(mnemonic, "extractu"), 0, 1));
4947
4948     let bit13 = !if (!eq(ImmOpStr, "u6Imm"), src2{5}, 0);
4949
4950     let IClass = 0b1000;
4951
4952     let Inst{27-24} = RegTyBits;
4953     let Inst{23}    = bit23;
4954     let Inst{22-21} = src3{4-3};
4955     let Inst{20-16} = src1;
4956     let Inst{13}    = bit13;
4957     let Inst{12-8}  = src2{4-0};
4958     let Inst{7-5}   = src3{2-0};
4959     let Inst{4-0}   = dst;
4960   }
4961
4962 // Extract bitfield
4963
4964 // Rdd=extractu(Rss,Rtt)
4965 // Rdd=extractu(Rss,#u6,#U6)
4966 let isCodeGenOnly = 0 in {
4967 def S2_extractup_rp : T_S3op_64 < "extractu", 0b00, 0b000, 0>;
4968 def S2_extractup    : T_S2op_extract <"extractu", 0b0001, DoubleRegs, u6Imm>;
4969 }
4970
4971 // Rd=extractu(Rs,Rtt)
4972 // Rd=extractu(Rs,#u5,#U5)
4973 let hasNewValue = 1, isCodeGenOnly = 0 in {
4974   def S2_extractu_rp : T_S3op_extract<"extractu", 0b00>;
4975   def S2_extractu    : T_S2op_extract <"extractu", 0b1101, IntRegs, u5Imm>;
4976 }
4977
4978 //===----------------------------------------------------------------------===//
4979 // :raw for of tableindx[bdhw] insns
4980 //===----------------------------------------------------------------------===//
4981
4982 let hasSideEffects = 0, hasNewValue = 1, opNewValue = 0 in
4983 class tableidxRaw<string OpStr, bits<2>MinOp>
4984   : SInst <(outs IntRegs:$Rx),
4985            (ins IntRegs:$_dst_, IntRegs:$Rs, u4Imm:$u4, s6Imm:$S6),
4986            "$Rx = "#OpStr#"($Rs, #$u4, #$S6):raw",
4987     [], "$Rx = $_dst_" > {
4988     bits<5> Rx;
4989     bits<5> Rs;
4990     bits<4> u4;
4991     bits<6> S6;
4992
4993     let IClass = 0b1000;
4994
4995     let Inst{27-24} = 0b0111;
4996     let Inst{23-22} = MinOp;
4997     let Inst{21}    = u4{3};
4998     let Inst{20-16} = Rs;
4999     let Inst{13-8}  = S6;
5000     let Inst{7-5}   = u4{2-0};
5001     let Inst{4-0}   = Rx;
5002   }
5003
5004 let isCodeGenOnly = 0 in {
5005 def S2_tableidxb : tableidxRaw<"tableidxb", 0b00>;
5006 def S2_tableidxh : tableidxRaw<"tableidxh", 0b01>;
5007 def S2_tableidxw : tableidxRaw<"tableidxw", 0b10>;
5008 def S2_tableidxd : tableidxRaw<"tableidxd", 0b11>;
5009 }
5010
5011 // Change the sign of the immediate for Rd=-mpyi(Rs,#u8)
5012 def : Pat <(mul (i32 IntRegs:$src1), (ineg n8ImmPred:$src2)),
5013       (i32 (M2_mpysin (i32 IntRegs:$src1), u8ImmPred:$src2))>;
5014
5015 //===----------------------------------------------------------------------===//
5016 // V3 Instructions +
5017 //===----------------------------------------------------------------------===//
5018
5019 include "HexagonInstrInfoV3.td"
5020
5021 //===----------------------------------------------------------------------===//
5022 // V3 Instructions -
5023 //===----------------------------------------------------------------------===//
5024
5025 //===----------------------------------------------------------------------===//
5026 // V4 Instructions +
5027 //===----------------------------------------------------------------------===//
5028
5029 include "HexagonInstrInfoV4.td"
5030
5031 //===----------------------------------------------------------------------===//
5032 // V4 Instructions -
5033 //===----------------------------------------------------------------------===//
5034
5035 //===----------------------------------------------------------------------===//
5036 // V5 Instructions +
5037 //===----------------------------------------------------------------------===//
5038
5039 include "HexagonInstrInfoV5.td"
5040
5041 //===----------------------------------------------------------------------===//
5042 // V5 Instructions -
5043 //===----------------------------------------------------------------------===//