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