Move imm0_255 to ARMInstrInfo.td with the other immediate predicates.
[oota-llvm.git] / lib / Target / ARM / ARMInstrThumb.td
1 //===- ARMInstrThumb.td - Thumb support for ARM ------------*- 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 Thumb instruction set.
11 //
12 //===----------------------------------------------------------------------===//
13
14 //===----------------------------------------------------------------------===//
15 // Thumb specific DAG Nodes.
16 //
17
18 def ARMtcall : SDNode<"ARMISD::tCALL", SDT_ARMcall,
19                       [SDNPHasChain, SDNPOptInGlue, SDNPOutGlue,
20                        SDNPVariadic]>;
21
22 def imm_neg_XFORM : SDNodeXForm<imm, [{
23   return CurDAG->getTargetConstant(-(int)N->getZExtValue(), MVT::i32);
24 }]>;
25 def imm_comp_XFORM : SDNodeXForm<imm, [{
26   return CurDAG->getTargetConstant(~((uint32_t)N->getZExtValue()), MVT::i32);
27 }]>;
28
29 def imm0_7_neg : PatLeaf<(i32 imm), [{
30   return (uint32_t)-N->getZExtValue() < 8;
31 }], imm_neg_XFORM>;
32
33 def imm0_255_comp : PatLeaf<(i32 imm), [{
34   return ~((uint32_t)N->getZExtValue()) < 256;
35 }]>;
36
37 def imm8_255 : ImmLeaf<i32, [{
38   return Imm >= 8 && Imm < 256;
39 }]>;
40 def imm8_255_neg : PatLeaf<(i32 imm), [{
41   unsigned Val = -N->getZExtValue();
42   return Val >= 8 && Val < 256;
43 }], imm_neg_XFORM>;
44
45 // Break imm's up into two pieces: an immediate + a left shift. This uses
46 // thumb_immshifted to match and thumb_immshifted_val and thumb_immshifted_shamt
47 // to get the val/shift pieces.
48 def thumb_immshifted : PatLeaf<(imm), [{
49   return ARM_AM::isThumbImmShiftedVal((unsigned)N->getZExtValue());
50 }]>;
51
52 def thumb_immshifted_val : SDNodeXForm<imm, [{
53   unsigned V = ARM_AM::getThumbImmNonShiftedVal((unsigned)N->getZExtValue());
54   return CurDAG->getTargetConstant(V, MVT::i32);
55 }]>;
56
57 def thumb_immshifted_shamt : SDNodeXForm<imm, [{
58   unsigned V = ARM_AM::getThumbImmValShift((unsigned)N->getZExtValue());
59   return CurDAG->getTargetConstant(V, MVT::i32);
60 }]>;
61
62 // ADR instruction labels.
63 def t_adrlabel : Operand<i32> {
64   let EncoderMethod = "getThumbAdrLabelOpValue";
65 }
66
67 // Scaled 4 immediate.
68 def t_imm_s4 : Operand<i32> {
69   let PrintMethod = "printThumbS4ImmOperand";
70   let OperandType = "OPERAND_IMMEDIATE";
71 }
72
73 // Define Thumb specific addressing modes.
74
75 let OperandType = "OPERAND_PCREL" in {
76 def t_brtarget : Operand<OtherVT> {
77   let EncoderMethod = "getThumbBRTargetOpValue";
78 }
79
80 def t_bcctarget : Operand<i32> {
81   let EncoderMethod = "getThumbBCCTargetOpValue";
82 }
83
84 def t_cbtarget : Operand<i32> {
85   let EncoderMethod = "getThumbCBTargetOpValue";
86 }
87
88 def t_bltarget : Operand<i32> {
89   let EncoderMethod = "getThumbBLTargetOpValue";
90 }
91
92 def t_blxtarget : Operand<i32> {
93   let EncoderMethod = "getThumbBLXTargetOpValue";
94 }
95 }
96
97 def MemModeRegThumbAsmOperand : AsmOperandClass {
98   let Name = "MemModeRegThumb";
99   let SuperClasses = [];
100 }
101
102 def MemModeImmThumbAsmOperand : AsmOperandClass {
103   let Name = "MemModeImmThumb";
104   let SuperClasses = [];
105 }
106
107 // t_addrmode_rr := reg + reg
108 //
109 def t_addrmode_rr : Operand<i32>,
110                     ComplexPattern<i32, 2, "SelectThumbAddrModeRR", []> {
111   let EncoderMethod = "getThumbAddrModeRegRegOpValue";
112   let PrintMethod = "printThumbAddrModeRROperand";
113   let MIOperandInfo = (ops tGPR:$base, tGPR:$offsreg);
114 }
115
116 // t_addrmode_rrs := reg + reg
117 //
118 def t_addrmode_rrs1 : Operand<i32>,
119                       ComplexPattern<i32, 2, "SelectThumbAddrModeRI5S1", []> {
120   let EncoderMethod = "getThumbAddrModeRegRegOpValue";
121   let PrintMethod = "printThumbAddrModeRROperand";
122   let MIOperandInfo = (ops tGPR:$base, tGPR:$offsreg);
123   let ParserMatchClass = MemModeRegThumbAsmOperand;
124 }
125 def t_addrmode_rrs2 : Operand<i32>,
126                       ComplexPattern<i32, 2, "SelectThumbAddrModeRI5S2", []> {
127   let EncoderMethod = "getThumbAddrModeRegRegOpValue";
128   let PrintMethod = "printThumbAddrModeRROperand";
129   let MIOperandInfo = (ops tGPR:$base, tGPR:$offsreg);
130   let ParserMatchClass = MemModeRegThumbAsmOperand;
131 }
132 def t_addrmode_rrs4 : Operand<i32>,
133                       ComplexPattern<i32, 2, "SelectThumbAddrModeRI5S4", []> {
134   let EncoderMethod = "getThumbAddrModeRegRegOpValue";
135   let PrintMethod = "printThumbAddrModeRROperand";
136   let MIOperandInfo = (ops tGPR:$base, tGPR:$offsreg);
137   let ParserMatchClass = MemModeRegThumbAsmOperand;
138 }
139
140 // t_addrmode_is4 := reg + imm5 * 4
141 //
142 def t_addrmode_is4 : Operand<i32>,
143                      ComplexPattern<i32, 2, "SelectThumbAddrModeImm5S4", []> {
144   let EncoderMethod = "getAddrModeISOpValue";
145   let PrintMethod = "printThumbAddrModeImm5S4Operand";
146   let MIOperandInfo = (ops tGPR:$base, i32imm:$offsimm);
147   let ParserMatchClass = MemModeImmThumbAsmOperand;
148 }
149
150 // t_addrmode_is2 := reg + imm5 * 2
151 //
152 def t_addrmode_is2 : Operand<i32>,
153                      ComplexPattern<i32, 2, "SelectThumbAddrModeImm5S2", []> {
154   let EncoderMethod = "getAddrModeISOpValue";
155   let PrintMethod = "printThumbAddrModeImm5S2Operand";
156   let MIOperandInfo = (ops tGPR:$base, i32imm:$offsimm);
157   let ParserMatchClass = MemModeImmThumbAsmOperand;
158 }
159
160 // t_addrmode_is1 := reg + imm5
161 //
162 def t_addrmode_is1 : Operand<i32>,
163                      ComplexPattern<i32, 2, "SelectThumbAddrModeImm5S1", []> {
164   let EncoderMethod = "getAddrModeISOpValue";
165   let PrintMethod = "printThumbAddrModeImm5S1Operand";
166   let MIOperandInfo = (ops tGPR:$base, i32imm:$offsimm);
167   let ParserMatchClass = MemModeImmThumbAsmOperand;
168 }
169
170 // t_addrmode_sp := sp + imm8 * 4
171 //
172 def t_addrmode_sp : Operand<i32>,
173                     ComplexPattern<i32, 2, "SelectThumbAddrModeSP", []> {
174   let EncoderMethod = "getAddrModeThumbSPOpValue";
175   let PrintMethod = "printThumbAddrModeSPOperand";
176   let MIOperandInfo = (ops GPR:$base, i32imm:$offsimm);
177   let ParserMatchClass = MemModeImmThumbAsmOperand;
178 }
179
180 // t_addrmode_pc := <label> => pc + imm8 * 4
181 //
182 def t_addrmode_pc : Operand<i32> {
183   let EncoderMethod = "getAddrModePCOpValue";
184   let ParserMatchClass = MemModeImmThumbAsmOperand;
185 }
186
187 //===----------------------------------------------------------------------===//
188 //  Miscellaneous Instructions.
189 //
190
191 // FIXME: Marking these as hasSideEffects is necessary to prevent machine DCE
192 // from removing one half of the matched pairs. That breaks PEI, which assumes
193 // these will always be in pairs, and asserts if it finds otherwise. Better way?
194 let Defs = [SP], Uses = [SP], hasSideEffects = 1 in {
195 def tADJCALLSTACKUP :
196   PseudoInst<(outs), (ins i32imm:$amt1, i32imm:$amt2), NoItinerary,
197              [(ARMcallseq_end imm:$amt1, imm:$amt2)]>,
198             Requires<[IsThumb, IsThumb1Only]>;
199
200 def tADJCALLSTACKDOWN :
201   PseudoInst<(outs), (ins i32imm:$amt), NoItinerary,
202              [(ARMcallseq_start imm:$amt)]>,
203             Requires<[IsThumb, IsThumb1Only]>;
204 }
205
206 // T1Disassembly - A simple class to make encoding some disassembly patterns
207 // easier and less verbose.
208 class T1Disassembly<bits<2> op1, bits<8> op2>
209   : T1Encoding<0b101111> {
210   let Inst{9-8} = op1;
211   let Inst{7-0} = op2;
212 }
213
214 def tNOP : T1pI<(outs), (ins), NoItinerary, "nop", "",
215                 [/* For disassembly only; pattern left blank */]>,
216            T1Disassembly<0b11, 0x00>; // A8.6.110
217
218 def tYIELD : T1pI<(outs), (ins), NoItinerary, "yield", "",
219                   [/* For disassembly only; pattern left blank */]>,
220            T1Disassembly<0b11, 0x10>; // A8.6.410
221
222 def tWFE : T1pI<(outs), (ins), NoItinerary, "wfe", "",
223                 [/* For disassembly only; pattern left blank */]>,
224            T1Disassembly<0b11, 0x20>; // A8.6.408
225
226 def tWFI : T1pI<(outs), (ins), NoItinerary, "wfi", "",
227                 [/* For disassembly only; pattern left blank */]>,
228            T1Disassembly<0b11, 0x30>; // A8.6.409
229
230 def tSEV : T1pI<(outs), (ins), NoItinerary, "sev", "",
231                 [/* For disassembly only; pattern left blank */]>,
232            T1Disassembly<0b11, 0x40>; // A8.6.157
233
234 // The i32imm operand $val can be used by a debugger to store more information
235 // about the breakpoint.
236 def tBKPT : T1I<(outs), (ins i32imm:$val), NoItinerary, "bkpt\t$val",
237                 [/* For disassembly only; pattern left blank */]>,
238            T1Disassembly<0b10, {?,?,?,?,?,?,?,?}> {
239   // A8.6.22
240   bits<8> val;
241   let Inst{7-0} = val;
242 }
243
244 def tSETEND : T1I<(outs), (ins setend_op:$end), NoItinerary, "setend\t$end",
245                   []>, T1Encoding<0b101101> {
246   bits<1> end;
247   // A8.6.156
248   let Inst{9-5} = 0b10010;
249   let Inst{4}   = 1;
250   let Inst{3}   = end;
251   let Inst{2-0} = 0b000;
252 }
253
254 // Change Processor State is a system instruction -- for disassembly only.
255 def tCPS : T1I<(outs), (ins imod_op:$imod, iflags_op:$iflags),
256                 NoItinerary, "cps$imod $iflags",
257                 [/* For disassembly only; pattern left blank */]>,
258            T1Misc<0b0110011> {
259   // A8.6.38 & B6.1.1
260   bit imod;
261   bits<3> iflags;
262
263   let Inst{4}   = imod;
264   let Inst{3}   = 0;
265   let Inst{2-0} = iflags;
266 }
267
268 // For both thumb1 and thumb2.
269 let isNotDuplicable = 1, isCodeGenOnly = 1 in
270 def tPICADD : TIt<(outs GPR:$dst), (ins GPR:$lhs, pclabel:$cp), IIC_iALUr, "",
271                   [(set GPR:$dst, (ARMpic_add GPR:$lhs, imm:$cp))]>,
272               T1Special<{0,0,?,?}> {
273   // A8.6.6
274   bits<3> dst;
275   let Inst{6-3} = 0b1111; // Rm = pc
276   let Inst{2-0} = dst;
277 }
278
279 // PC relative add (ADR).
280 def tADDrPCi : T1I<(outs tGPR:$dst), (ins t_imm_s4:$rhs), IIC_iALUi,
281                    "add\t$dst, pc, $rhs", []>,
282                T1Encoding<{1,0,1,0,0,?}> {
283   // A6.2 & A8.6.10
284   bits<3> dst;
285   bits<8> rhs;
286   let Inst{10-8} = dst;
287   let Inst{7-0}  = rhs;
288 }
289
290 // ADD <Rd>, sp, #<imm8>
291 // This is rematerializable, which is particularly useful for taking the
292 // address of locals.
293 let isReMaterializable = 1 in
294 def tADDrSPi : T1I<(outs tGPR:$dst), (ins GPR:$sp, t_imm_s4:$rhs), IIC_iALUi,
295                    "add\t$dst, $sp, $rhs", []>,
296                T1Encoding<{1,0,1,0,1,?}> {
297   // A6.2 & A8.6.8
298   bits<3> dst;
299   bits<8> rhs;
300   let Inst{10-8} = dst;
301   let Inst{7-0}  = rhs;
302 }
303
304 // ADD sp, sp, #<imm7>
305 def tADDspi : TIt<(outs GPR:$dst), (ins GPR:$lhs, t_imm_s4:$rhs), IIC_iALUi,
306                   "add\t$dst, $rhs", []>,
307               T1Misc<{0,0,0,0,0,?,?}> {
308   // A6.2.5 & A8.6.8
309   bits<7> rhs;
310   let Inst{6-0} = rhs;
311 }
312
313 // SUB sp, sp, #<imm7>
314 // FIXME: The encoding and the ASM string don't match up.
315 def tSUBspi : TIt<(outs GPR:$dst), (ins GPR:$lhs, t_imm_s4:$rhs), IIC_iALUi,
316                   "sub\t$dst, $rhs", []>,
317               T1Misc<{0,0,0,0,1,?,?}> {
318   // A6.2.5 & A8.6.214
319   bits<7> rhs;
320   let Inst{6-0} = rhs;
321 }
322
323 // ADD <Rm>, sp
324 def tADDrSP : TIt<(outs GPR:$dst), (ins GPR:$lhs, GPR:$rhs), IIC_iALUr,
325                   "add\t$dst, $rhs", []>,
326               T1Special<{0,0,?,?}> {
327   // A8.6.9 Encoding T1
328   bits<4> dst;
329   let Inst{7}   = dst{3};
330   let Inst{6-3} = 0b1101;
331   let Inst{2-0} = dst{2-0};
332 }
333
334 // ADD sp, <Rm>
335 def tADDspr : TIt<(outs GPR:$dst), (ins GPR:$lhs, GPR:$rhs), IIC_iALUr,
336                   "add\t$dst, $rhs", []>,
337               T1Special<{0,0,?,?}> {
338   // A8.6.9 Encoding T2
339   bits<4> dst;
340   let Inst{7} = 1;
341   let Inst{6-3} = dst;
342   let Inst{2-0} = 0b101;
343 }
344
345 //===----------------------------------------------------------------------===//
346 //  Control Flow Instructions.
347 //
348
349 // Indirect branches
350 let isBranch = 1, isTerminator = 1, isBarrier = 1, isIndirectBranch = 1 in {
351   def tBX : TI<(outs), (ins GPR:$Rm, pred:$p), IIC_Br, "bx${p}\t$Rm", []>,
352             T1Special<{1,1,0,?}> {
353     // A6.2.3 & A8.6.25
354     bits<4> Rm;
355     let Inst{6-3} = Rm;
356     let Inst{2-0} = 0b000;
357   }
358 }
359
360 let isReturn = 1, isTerminator = 1, isBarrier = 1 in {
361   def tBX_RET : tPseudoExpand<(outs), (ins pred:$p), 2, IIC_Br,
362                    [(ARMretflag)], (tBX LR, pred:$p)>;
363
364   // Alternative return instruction used by vararg functions.
365   def tBX_RET_vararg : tPseudoExpand<(outs), (ins tGPR:$Rm, pred:$p),
366                    2, IIC_Br, [],
367                    (tBX GPR:$Rm, pred:$p)>;
368 }
369
370 // All calls clobber the non-callee saved registers. SP is marked as a use to
371 // prevent stack-pointer assignments that appear immediately before calls from
372 // potentially appearing dead.
373 let isCall = 1,
374   // On non-Darwin platforms R9 is callee-saved.
375   Defs = [R0,  R1,  R2,  R3,  R12, LR, QQQQ0, QQQQ2, QQQQ3, CPSR, FPSCR],
376   Uses = [SP] in {
377   // Also used for Thumb2
378   def tBL  : TIx2<0b11110, 0b11, 1,
379                   (outs), (ins pred:$p, t_bltarget:$func, variable_ops), IIC_Br,
380                   "bl${p}\t$func",
381                   [(ARMtcall tglobaladdr:$func)]>,
382              Requires<[IsThumb, IsNotDarwin]> {
383     bits<21> func;
384     let Inst{25-16} = func{20-11};
385     let Inst{13} = 1;
386     let Inst{11} = 1;
387     let Inst{10-0} = func{10-0};
388   }
389
390   // ARMv5T and above, also used for Thumb2
391   def tBLXi : TIx2<0b11110, 0b11, 0,
392                    (outs), (ins pred:$p, t_blxtarget:$func, variable_ops), IIC_Br,
393                    "blx${p}\t$func",
394                    [(ARMcall tglobaladdr:$func)]>,
395               Requires<[IsThumb, HasV5T, IsNotDarwin]> {
396     bits<21> func;
397     let Inst{25-16} = func{20-11};
398     let Inst{13} = 1;
399     let Inst{11} = 1;
400     let Inst{10-1} = func{10-1};
401     let Inst{0} = 0; // func{0} is assumed zero
402   }
403
404   // Also used for Thumb2
405   def tBLXr : TI<(outs), (ins pred:$p, GPR:$func, variable_ops), IIC_Br,
406                   "blx${p}\t$func",
407                   [(ARMtcall GPR:$func)]>,
408               Requires<[IsThumb, HasV5T, IsNotDarwin]>,
409               T1Special<{1,1,1,?}> { // A6.2.3 & A8.6.24;
410     bits<4> func;
411     let Inst{6-3} = func;
412     let Inst{2-0} = 0b000;
413   }
414
415   // ARMv4T
416   def tBX_CALL : tPseudoInst<(outs), (ins tGPR:$func, variable_ops),
417                   4, IIC_Br,
418                   [(ARMcall_nolink tGPR:$func)]>,
419             Requires<[IsThumb, IsThumb1Only, IsNotDarwin]>;
420 }
421
422 let isCall = 1,
423   // On Darwin R9 is call-clobbered.
424   // R7 is marked as a use to prevent frame-pointer assignments from being
425   // moved above / below calls.
426   Defs = [R0,  R1,  R2,  R3,  R9,  R12, LR, QQQQ0, QQQQ2, QQQQ3, CPSR, FPSCR],
427   Uses = [R7, SP] in {
428   // Also used for Thumb2
429   def tBLr9 : tPseudoExpand<(outs), (ins pred:$p, t_bltarget:$func, variable_ops),
430                           4, IIC_Br, [(ARMtcall tglobaladdr:$func)],
431                           (tBL pred:$p, t_bltarget:$func)>,
432               Requires<[IsThumb, IsDarwin]>;
433
434   // ARMv5T and above, also used for Thumb2
435   def tBLXi_r9 : tPseudoExpand<(outs), (ins pred:$p, t_blxtarget:$func, variable_ops),
436                       4, IIC_Br, [(ARMcall tglobaladdr:$func)],
437                       (tBLXi pred:$p, t_blxtarget:$func)>,
438                  Requires<[IsThumb, HasV5T, IsDarwin]>;
439
440   // Also used for Thumb2
441   def tBLXr_r9 : tPseudoExpand<(outs), (ins pred:$p, GPR:$func, variable_ops),
442                     2, IIC_Br, [(ARMtcall GPR:$func)],
443                     (tBLXr pred:$p, GPR:$func)>,
444                  Requires<[IsThumb, HasV5T, IsDarwin]>;
445
446   // ARMv4T
447   def tBXr9_CALL : tPseudoInst<(outs), (ins tGPR:$func, variable_ops),
448                    4, IIC_Br,
449                    [(ARMcall_nolink tGPR:$func)]>,
450               Requires<[IsThumb, IsThumb1Only, IsDarwin]>;
451 }
452
453 let isBranch = 1, isTerminator = 1, isBarrier = 1 in {
454   let isPredicable = 1 in
455   def tB   : T1I<(outs), (ins t_brtarget:$target), IIC_Br,
456                  "b\t$target", [(br bb:$target)]>,
457              T1Encoding<{1,1,1,0,0,?}> {
458     bits<11> target;
459     let Inst{10-0} = target;
460   }
461
462   // Far jump
463   // Just a pseudo for a tBL instruction. Needed to let regalloc know about
464   // the clobber of LR.
465   let Defs = [LR] in
466   def tBfar : tPseudoExpand<(outs), (ins t_bltarget:$target, pred:$p),
467                           4, IIC_Br, [], (tBL pred:$p, t_bltarget:$target)>;
468
469   def tBR_JTr : tPseudoInst<(outs),
470                       (ins tGPR:$target, i32imm:$jt, i32imm:$id),
471                       0, IIC_Br,
472                       [(ARMbrjt tGPR:$target, tjumptable:$jt, imm:$id)]> {
473     list<Predicate> Predicates = [IsThumb, IsThumb1Only];
474   }
475 }
476
477 // FIXME: should be able to write a pattern for ARMBrcond, but can't use
478 // a two-value operand where a dag node expects two operands. :(
479 let isBranch = 1, isTerminator = 1 in
480   def tBcc : T1I<(outs), (ins t_bcctarget:$target, pred:$p), IIC_Br,
481                  "b${p}\t$target",
482                  [/*(ARMbrcond bb:$target, imm:$cc)*/]>,
483              T1BranchCond<{1,1,0,1}> {
484   bits<4> p;
485   bits<8> target;
486   let Inst{11-8} = p;
487   let Inst{7-0} = target;
488 }
489
490 // Compare and branch on zero / non-zero
491 let isBranch = 1, isTerminator = 1 in {
492   def tCBZ  : T1I<(outs), (ins tGPR:$Rn, t_cbtarget:$target), IIC_Br,
493                   "cbz\t$Rn, $target", []>,
494               T1Misc<{0,0,?,1,?,?,?}> {
495     // A8.6.27
496     bits<6> target;
497     bits<3> Rn;
498     let Inst{9}   = target{5};
499     let Inst{7-3} = target{4-0};
500     let Inst{2-0} = Rn;
501   }
502
503   def tCBNZ : T1I<(outs), (ins tGPR:$cmp, t_cbtarget:$target), IIC_Br,
504                   "cbnz\t$cmp, $target", []>,
505               T1Misc<{1,0,?,1,?,?,?}> {
506     // A8.6.27
507     bits<6> target;
508     bits<3> Rn;
509     let Inst{9}   = target{5};
510     let Inst{7-3} = target{4-0};
511     let Inst{2-0} = Rn;
512   }
513 }
514
515 // Tail calls
516 let isCall = 1, isTerminator = 1, isReturn = 1, isBarrier = 1 in {
517   // Darwin versions.
518   let Defs = [R0, R1, R2, R3, R9, R12, QQQQ0, QQQQ2, QQQQ3, PC],
519       Uses = [SP] in {
520     // tTAILJMPd: Darwin version uses a Thumb2 branch (no Thumb1 tail calls
521     // on Darwin), so it's in ARMInstrThumb2.td.
522     def tTAILJMPr : tPseudoExpand<(outs), (ins tcGPR:$dst, variable_ops),
523                      4, IIC_Br, [],
524                      (tBX GPR:$dst, (ops 14, zero_reg))>,
525                      Requires<[IsThumb, IsDarwin]>;
526   }
527   // Non-Darwin versions (the difference is R9).
528   let Defs = [R0, R1, R2, R3, R12, QQQQ0, QQQQ2, QQQQ3, PC],
529       Uses = [SP] in {
530     def tTAILJMPdND : tPseudoExpand<(outs), (ins t_brtarget:$dst, variable_ops),
531                    4, IIC_Br, [],
532                    (tB t_brtarget:$dst)>,
533                  Requires<[IsThumb, IsNotDarwin]>;
534     def tTAILJMPrND : tPseudoExpand<(outs), (ins tcGPR:$dst, variable_ops),
535                      4, IIC_Br, [],
536                      (tBX GPR:$dst, (ops 14, zero_reg))>,
537                      Requires<[IsThumb, IsNotDarwin]>;
538   }
539 }
540
541
542 // A8.6.218 Supervisor Call (Software Interrupt) -- for disassembly only
543 // A8.6.16 B: Encoding T1
544 // If Inst{11-8} == 0b1111 then SEE SVC
545 let isCall = 1, Uses = [SP] in
546 def tSVC : T1pI<(outs), (ins imm0_255:$imm), IIC_Br,
547                 "svc", "\t$imm", []>, Encoding16 {
548   bits<8> imm;
549   let Inst{15-12} = 0b1101;
550   let Inst{11-8}  = 0b1111;
551   let Inst{7-0}   = imm;
552 }
553
554 // The assembler uses 0xDEFE for a trap instruction.
555 let isBarrier = 1, isTerminator = 1 in
556 def tTRAP : TI<(outs), (ins), IIC_Br,
557                "trap", [(trap)]>, Encoding16 {
558   let Inst = 0xdefe;
559 }
560
561 //===----------------------------------------------------------------------===//
562 //  Load Store Instructions.
563 //
564
565 // Loads: reg/reg and reg/imm5
566 let canFoldAsLoad = 1, isReMaterializable = 1 in
567 multiclass thumb_ld_rr_ri_enc<bits<3> reg_opc, bits<4> imm_opc,
568                               Operand AddrMode_r, Operand AddrMode_i,
569                               AddrMode am, InstrItinClass itin_r,
570                               InstrItinClass itin_i, string asm,
571                               PatFrag opnode> {
572   def r : // reg/reg
573     T1pILdStEncode<reg_opc,
574                    (outs tGPR:$Rt), (ins AddrMode_r:$addr),
575                    am, itin_r, asm, "\t$Rt, $addr",
576                    [(set tGPR:$Rt, (opnode AddrMode_r:$addr))]>;
577   def i : // reg/imm5
578     T1pILdStEncodeImm<imm_opc, 1 /* Load */,
579                       (outs tGPR:$Rt), (ins AddrMode_i:$addr),
580                       am, itin_i, asm, "\t$Rt, $addr",
581                       [(set tGPR:$Rt, (opnode AddrMode_i:$addr))]>;
582 }
583 // Stores: reg/reg and reg/imm5
584 multiclass thumb_st_rr_ri_enc<bits<3> reg_opc, bits<4> imm_opc,
585                               Operand AddrMode_r, Operand AddrMode_i,
586                               AddrMode am, InstrItinClass itin_r,
587                               InstrItinClass itin_i, string asm,
588                               PatFrag opnode> {
589   def r : // reg/reg
590     T1pILdStEncode<reg_opc,
591                    (outs), (ins tGPR:$Rt, AddrMode_r:$addr),
592                    am, itin_r, asm, "\t$Rt, $addr",
593                    [(opnode tGPR:$Rt, AddrMode_r:$addr)]>;
594   def i : // reg/imm5
595     T1pILdStEncodeImm<imm_opc, 0 /* Store */,
596                       (outs), (ins tGPR:$Rt, AddrMode_i:$addr),
597                       am, itin_i, asm, "\t$Rt, $addr",
598                       [(opnode tGPR:$Rt, AddrMode_i:$addr)]>;
599 }
600
601 // A8.6.57 & A8.6.60
602 defm tLDR  : thumb_ld_rr_ri_enc<0b100, 0b0110, t_addrmode_rrs4,
603                                 t_addrmode_is4, AddrModeT1_4,
604                                 IIC_iLoad_r, IIC_iLoad_i, "ldr",
605                                 UnOpFrag<(load node:$Src)>>;
606
607 // A8.6.64 & A8.6.61
608 defm tLDRB : thumb_ld_rr_ri_enc<0b110, 0b0111, t_addrmode_rrs1,
609                                 t_addrmode_is1, AddrModeT1_1,
610                                 IIC_iLoad_bh_r, IIC_iLoad_bh_i, "ldrb",
611                                 UnOpFrag<(zextloadi8 node:$Src)>>;
612
613 // A8.6.76 & A8.6.73
614 defm tLDRH : thumb_ld_rr_ri_enc<0b101, 0b1000, t_addrmode_rrs2,
615                                 t_addrmode_is2, AddrModeT1_2,
616                                 IIC_iLoad_bh_r, IIC_iLoad_bh_i, "ldrh",
617                                 UnOpFrag<(zextloadi16 node:$Src)>>;
618
619 let AddedComplexity = 10 in
620 def tLDRSB :                    // A8.6.80
621   T1pILdStEncode<0b011, (outs tGPR:$dst), (ins t_addrmode_rr:$addr),
622                  AddrModeT1_1, IIC_iLoad_bh_r,
623                  "ldrsb", "\t$dst, $addr",
624                  [(set tGPR:$dst, (sextloadi8 t_addrmode_rr:$addr))]>;
625
626 let AddedComplexity = 10 in
627 def tLDRSH :                    // A8.6.84
628   T1pILdStEncode<0b111, (outs tGPR:$dst), (ins t_addrmode_rr:$addr),
629                  AddrModeT1_2, IIC_iLoad_bh_r,
630                  "ldrsh", "\t$dst, $addr",
631                  [(set tGPR:$dst, (sextloadi16 t_addrmode_rr:$addr))]>;
632
633 let canFoldAsLoad = 1 in
634 def tLDRspi : T1pIs<(outs tGPR:$Rt), (ins t_addrmode_sp:$addr), IIC_iLoad_i,
635                     "ldr", "\t$Rt, $addr",
636                     [(set tGPR:$Rt, (load t_addrmode_sp:$addr))]>,
637               T1LdStSP<{1,?,?}> {
638   bits<3> Rt;
639   bits<8> addr;
640   let Inst{10-8} = Rt;
641   let Inst{7-0} = addr;
642 }
643
644 // Load tconstpool
645 // FIXME: Use ldr.n to work around a Darwin assembler bug.
646 let canFoldAsLoad = 1, isReMaterializable = 1, isCodeGenOnly = 1 in
647 def tLDRpci : T1pIs<(outs tGPR:$Rt), (ins t_addrmode_pc:$addr), IIC_iLoad_i,
648                   "ldr", ".n\t$Rt, $addr",
649                   [(set tGPR:$Rt, (load (ARMWrapper tconstpool:$addr)))]>,
650               T1Encoding<{0,1,0,0,1,?}> {
651   // A6.2 & A8.6.59
652   bits<3> Rt;
653   bits<8> addr;
654   let Inst{10-8} = Rt;
655   let Inst{7-0}  = addr;
656 }
657
658 // FIXME: Remove this entry when the above ldr.n workaround is fixed.
659 // For disassembly use only.
660 def tLDRpciDIS : T1pIs<(outs tGPR:$Rt), (ins t_addrmode_pc:$addr), IIC_iLoad_i,
661                        "ldr", "\t$Rt, $addr",
662                        [/* disassembly only */]>,
663                  T1Encoding<{0,1,0,0,1,?}> {
664   // A6.2 & A8.6.59
665   bits<3> Rt;
666   bits<8> addr;
667   let Inst{10-8} = Rt;
668   let Inst{7-0}  = addr;
669 }
670
671 // A8.6.194 & A8.6.192
672 defm tSTR  : thumb_st_rr_ri_enc<0b000, 0b0110, t_addrmode_rrs4,
673                                 t_addrmode_is4, AddrModeT1_4,
674                                 IIC_iStore_r, IIC_iStore_i, "str",
675                                 BinOpFrag<(store node:$LHS, node:$RHS)>>;
676
677 // A8.6.197 & A8.6.195
678 defm tSTRB : thumb_st_rr_ri_enc<0b010, 0b0111, t_addrmode_rrs1,
679                                 t_addrmode_is1, AddrModeT1_1,
680                                 IIC_iStore_bh_r, IIC_iStore_bh_i, "strb",
681                                 BinOpFrag<(truncstorei8 node:$LHS, node:$RHS)>>;
682
683 // A8.6.207 & A8.6.205
684 defm tSTRH : thumb_st_rr_ri_enc<0b001, 0b1000, t_addrmode_rrs2,
685                                t_addrmode_is2, AddrModeT1_2,
686                                IIC_iStore_bh_r, IIC_iStore_bh_i, "strh",
687                                BinOpFrag<(truncstorei16 node:$LHS, node:$RHS)>>;
688
689
690 def tSTRspi : T1pIs<(outs), (ins tGPR:$Rt, t_addrmode_sp:$addr), IIC_iStore_i,
691                     "str", "\t$Rt, $addr",
692                     [(store tGPR:$Rt, t_addrmode_sp:$addr)]>,
693               T1LdStSP<{0,?,?}> {
694   bits<3> Rt;
695   bits<8> addr;
696   let Inst{10-8} = Rt;
697   let Inst{7-0} = addr;
698 }
699
700 //===----------------------------------------------------------------------===//
701 //  Load / store multiple Instructions.
702 //
703
704 multiclass thumb_ldst_mult<string asm, InstrItinClass itin,
705                            InstrItinClass itin_upd, bits<6> T1Enc,
706                            bit L_bit, string baseOpc> {
707   def IA :
708     T1I<(outs), (ins GPR:$Rn, pred:$p, reglist:$regs, variable_ops),
709         itin, !strconcat(asm, "ia${p}\t$Rn, $regs"), []>,
710        T1Encoding<T1Enc> {
711     bits<3> Rn;
712     bits<8> regs;
713     let Inst{10-8} = Rn;
714     let Inst{7-0}  = regs;
715   }
716
717   def IA_UPD :
718     InstTemplate<AddrModeNone, 0, IndexModeNone, Pseudo, GenericDomain, 
719                  "$Rn = $wb", itin_upd>,
720     PseudoInstExpansion<(!cast<Instruction>(!strconcat(baseOpc, "IA"))
721                        GPR:$Rn, pred:$p, reglist:$regs)> {
722     let Size = 2;
723     let OutOperandList = (outs GPR:$wb);
724     let InOperandList = (ins GPR:$Rn, pred:$p, reglist:$regs, variable_ops);
725     let Pattern = [];
726     let isCodeGenOnly = 1;
727     let isPseudo = 1;
728     list<Predicate> Predicates = [IsThumb];
729   }
730 }
731
732 // These require base address to be written back or one of the loaded regs.
733 let neverHasSideEffects = 1 in {
734
735 let mayLoad = 1, hasExtraDefRegAllocReq = 1 in
736 defm tLDM : thumb_ldst_mult<"ldm", IIC_iLoad_m, IIC_iLoad_mu,
737                             {1,1,0,0,1,?}, 1, "tLDM">;
738
739 let mayStore = 1, hasExtraSrcRegAllocReq = 1 in
740 defm tSTM : thumb_ldst_mult<"stm", IIC_iStore_m, IIC_iStore_mu,
741                             {1,1,0,0,0,?}, 0, "tSTM">;
742
743 } // neverHasSideEffects
744
745 let mayLoad = 1, Uses = [SP], Defs = [SP], hasExtraDefRegAllocReq = 1 in
746 def tPOP : T1I<(outs), (ins pred:$p, reglist:$regs, variable_ops),
747                IIC_iPop,
748                "pop${p}\t$regs", []>,
749            T1Misc<{1,1,0,?,?,?,?}> {
750   bits<16> regs;
751   let Inst{8}   = regs{15};
752   let Inst{7-0} = regs{7-0};
753 }
754
755 let mayStore = 1, Uses = [SP], Defs = [SP], hasExtraSrcRegAllocReq = 1 in
756 def tPUSH : T1I<(outs), (ins pred:$p, reglist:$regs, variable_ops),
757                 IIC_iStore_m,
758                 "push${p}\t$regs", []>,
759             T1Misc<{0,1,0,?,?,?,?}> {
760   bits<16> regs;
761   let Inst{8}   = regs{14};
762   let Inst{7-0} = regs{7-0};
763 }
764
765 //===----------------------------------------------------------------------===//
766 //  Arithmetic Instructions.
767 //
768
769 // Helper classes for encoding T1pI patterns:
770 class T1pIDPEncode<bits<4> opA, dag oops, dag iops, InstrItinClass itin,
771                    string opc, string asm, list<dag> pattern>
772     : T1pI<oops, iops, itin, opc, asm, pattern>,
773       T1DataProcessing<opA> {
774   bits<3> Rm;
775   bits<3> Rn;
776   let Inst{5-3} = Rm;
777   let Inst{2-0} = Rn;
778 }
779 class T1pIMiscEncode<bits<7> opA, dag oops, dag iops, InstrItinClass itin,
780                      string opc, string asm, list<dag> pattern>
781     : T1pI<oops, iops, itin, opc, asm, pattern>,
782       T1Misc<opA> {
783   bits<3> Rm;
784   bits<3> Rd;
785   let Inst{5-3} = Rm;
786   let Inst{2-0} = Rd;
787 }
788
789 // Helper classes for encoding T1sI patterns:
790 class T1sIDPEncode<bits<4> opA, dag oops, dag iops, InstrItinClass itin,
791                    string opc, string asm, list<dag> pattern>
792     : T1sI<oops, iops, itin, opc, asm, pattern>,
793       T1DataProcessing<opA> {
794   bits<3> Rd;
795   bits<3> Rn;
796   let Inst{5-3} = Rn;
797   let Inst{2-0} = Rd;
798 }
799 class T1sIGenEncode<bits<5> opA, dag oops, dag iops, InstrItinClass itin,
800                     string opc, string asm, list<dag> pattern>
801     : T1sI<oops, iops, itin, opc, asm, pattern>,
802       T1General<opA> {
803   bits<3> Rm;
804   bits<3> Rn;
805   bits<3> Rd;
806   let Inst{8-6} = Rm;
807   let Inst{5-3} = Rn;
808   let Inst{2-0} = Rd;
809 }
810 class T1sIGenEncodeImm<bits<5> opA, dag oops, dag iops, InstrItinClass itin,
811                        string opc, string asm, list<dag> pattern>
812     : T1sI<oops, iops, itin, opc, asm, pattern>,
813       T1General<opA> {
814   bits<3> Rd;
815   bits<3> Rm;
816   let Inst{5-3} = Rm;
817   let Inst{2-0} = Rd;
818 }
819
820 // Helper classes for encoding T1sIt patterns:
821 class T1sItDPEncode<bits<4> opA, dag oops, dag iops, InstrItinClass itin,
822                     string opc, string asm, list<dag> pattern>
823     : T1sIt<oops, iops, itin, opc, asm, pattern>,
824       T1DataProcessing<opA> {
825   bits<3> Rdn;
826   bits<3> Rm;
827   let Inst{5-3} = Rm;
828   let Inst{2-0} = Rdn;
829 }
830 class T1sItGenEncodeImm<bits<5> opA, dag oops, dag iops, InstrItinClass itin,
831                         string opc, string asm, list<dag> pattern>
832     : T1sIt<oops, iops, itin, opc, asm, pattern>,
833       T1General<opA> {
834   bits<3> Rdn;
835   bits<8> imm8;
836   let Inst{10-8} = Rdn;
837   let Inst{7-0}  = imm8;
838 }
839
840 // Add with carry register
841 let isCommutable = 1, Uses = [CPSR] in
842 def tADC :                      // A8.6.2
843   T1sItDPEncode<0b0101, (outs tGPR:$Rdn), (ins tGPR:$Rn, tGPR:$Rm), IIC_iALUr,
844                 "adc", "\t$Rdn, $Rm",
845                 [(set tGPR:$Rdn, (adde tGPR:$Rn, tGPR:$Rm))]>;
846
847 // Add immediate
848 def tADDi3 :                    // A8.6.4 T1
849   T1sIGenEncodeImm<0b01110, (outs tGPR:$Rd), (ins tGPR:$Rm, i32imm:$imm3),
850                    IIC_iALUi,
851                    "add", "\t$Rd, $Rm, $imm3",
852                    [(set tGPR:$Rd, (add tGPR:$Rm, imm0_7:$imm3))]> {
853   bits<3> imm3;
854   let Inst{8-6} = imm3;
855 }
856
857 def tADDi8 :                    // A8.6.4 T2
858   T1sItGenEncodeImm<{1,1,0,?,?}, (outs tGPR:$Rdn), (ins tGPR:$Rn, i32imm:$imm8),
859                     IIC_iALUi,
860                     "add", "\t$Rdn, $imm8",
861                     [(set tGPR:$Rdn, (add tGPR:$Rn, imm8_255:$imm8))]>;
862
863 // Add register
864 let isCommutable = 1 in
865 def tADDrr :                    // A8.6.6 T1
866   T1sIGenEncode<0b01100, (outs tGPR:$Rd), (ins tGPR:$Rn, tGPR:$Rm),
867                 IIC_iALUr,
868                 "add", "\t$Rd, $Rn, $Rm",
869                 [(set tGPR:$Rd, (add tGPR:$Rn, tGPR:$Rm))]>;
870
871 let neverHasSideEffects = 1 in
872 def tADDhirr : T1pIt<(outs GPR:$Rdn), (ins GPR:$Rn, GPR:$Rm), IIC_iALUr,
873                      "add", "\t$Rdn, $Rm", []>,
874                T1Special<{0,0,?,?}> {
875   // A8.6.6 T2
876   bits<4> Rdn;
877   bits<4> Rm;
878   let Inst{7}   = Rdn{3};
879   let Inst{6-3} = Rm;
880   let Inst{2-0} = Rdn{2-0};
881 }
882
883 // AND register
884 let isCommutable = 1 in
885 def tAND :                      // A8.6.12
886   T1sItDPEncode<0b0000, (outs tGPR:$Rdn), (ins tGPR:$Rn, tGPR:$Rm),
887                 IIC_iBITr,
888                 "and", "\t$Rdn, $Rm",
889                 [(set tGPR:$Rdn, (and tGPR:$Rn, tGPR:$Rm))]>;
890
891 // ASR immediate
892 def tASRri :                    // A8.6.14
893   T1sIGenEncodeImm<{0,1,0,?,?}, (outs tGPR:$Rd), (ins tGPR:$Rm, i32imm:$imm5),
894                    IIC_iMOVsi,
895                    "asr", "\t$Rd, $Rm, $imm5",
896                    [(set tGPR:$Rd, (sra tGPR:$Rm, (i32 imm:$imm5)))]> {
897   bits<5> imm5;
898   let Inst{10-6} = imm5;
899 }
900
901 // ASR register
902 def tASRrr :                    // A8.6.15
903   T1sItDPEncode<0b0100, (outs tGPR:$Rdn), (ins tGPR:$Rn, tGPR:$Rm),
904                 IIC_iMOVsr,
905                 "asr", "\t$Rdn, $Rm",
906                 [(set tGPR:$Rdn, (sra tGPR:$Rn, tGPR:$Rm))]>;
907
908 // BIC register
909 def tBIC :                      // A8.6.20
910   T1sItDPEncode<0b1110, (outs tGPR:$Rdn), (ins tGPR:$Rn, tGPR:$Rm),
911                 IIC_iBITr,
912                 "bic", "\t$Rdn, $Rm",
913                 [(set tGPR:$Rdn, (and tGPR:$Rn, (not tGPR:$Rm)))]>;
914
915 // CMN register
916 let isCompare = 1, Defs = [CPSR] in {
917 //FIXME: Disable CMN, as CCodes are backwards from compare expectations
918 //       Compare-to-zero still works out, just not the relationals
919 //def tCMN :                     // A8.6.33
920 //  T1pIDPEncode<0b1011, (outs), (ins tGPR:$lhs, tGPR:$rhs),
921 //               IIC_iCMPr,
922 //               "cmn", "\t$lhs, $rhs",
923 //               [(ARMcmp tGPR:$lhs, (ineg tGPR:$rhs))]>;
924
925 def tCMNz :                     // A8.6.33
926   T1pIDPEncode<0b1011, (outs), (ins tGPR:$Rn, tGPR:$Rm),
927                IIC_iCMPr,
928                "cmn", "\t$Rn, $Rm",
929                [(ARMcmpZ tGPR:$Rn, (ineg tGPR:$Rm))]>;
930
931 } // isCompare = 1, Defs = [CPSR]
932
933 // CMP immediate
934 let isCompare = 1, Defs = [CPSR] in {
935 def tCMPi8 : T1pI<(outs), (ins tGPR:$Rn, i32imm:$imm8), IIC_iCMPi,
936                   "cmp", "\t$Rn, $imm8",
937                   [(ARMcmp tGPR:$Rn, imm0_255:$imm8)]>,
938              T1General<{1,0,1,?,?}> {
939   // A8.6.35
940   bits<3> Rn;
941   bits<8> imm8;
942   let Inst{10-8} = Rn;
943   let Inst{7-0}  = imm8;
944 }
945
946 // CMP register
947 def tCMPr :                     // A8.6.36 T1
948   T1pIDPEncode<0b1010, (outs), (ins tGPR:$Rn, tGPR:$Rm),
949                IIC_iCMPr,
950                "cmp", "\t$Rn, $Rm",
951                [(ARMcmp tGPR:$Rn, tGPR:$Rm)]>;
952
953 def tCMPhir : T1pI<(outs), (ins GPR:$Rn, GPR:$Rm), IIC_iCMPr,
954                    "cmp", "\t$Rn, $Rm", []>,
955               T1Special<{0,1,?,?}> {
956   // A8.6.36 T2
957   bits<4> Rm;
958   bits<4> Rn;
959   let Inst{7}   = Rn{3};
960   let Inst{6-3} = Rm;
961   let Inst{2-0} = Rn{2-0};
962 }
963 } // isCompare = 1, Defs = [CPSR]
964
965
966 // XOR register
967 let isCommutable = 1 in
968 def tEOR :                      // A8.6.45
969   T1sItDPEncode<0b0001, (outs tGPR:$Rdn), (ins tGPR:$Rn, tGPR:$Rm),
970                 IIC_iBITr,
971                 "eor", "\t$Rdn, $Rm",
972                 [(set tGPR:$Rdn, (xor tGPR:$Rn, tGPR:$Rm))]>;
973
974 // LSL immediate
975 def tLSLri :                    // A8.6.88
976   T1sIGenEncodeImm<{0,0,0,?,?}, (outs tGPR:$Rd), (ins tGPR:$Rm, i32imm:$imm5),
977                    IIC_iMOVsi,
978                    "lsl", "\t$Rd, $Rm, $imm5",
979                    [(set tGPR:$Rd, (shl tGPR:$Rm, (i32 imm:$imm5)))]> {
980   bits<5> imm5;
981   let Inst{10-6} = imm5;
982 }
983
984 // LSL register
985 def tLSLrr :                    // A8.6.89
986   T1sItDPEncode<0b0010, (outs tGPR:$Rdn), (ins tGPR:$Rn, tGPR:$Rm),
987                 IIC_iMOVsr,
988                 "lsl", "\t$Rdn, $Rm",
989                 [(set tGPR:$Rdn, (shl tGPR:$Rn, tGPR:$Rm))]>;
990
991 // LSR immediate
992 def tLSRri :                    // A8.6.90
993   T1sIGenEncodeImm<{0,0,1,?,?}, (outs tGPR:$Rd), (ins tGPR:$Rm, i32imm:$imm5),
994                    IIC_iMOVsi,
995                    "lsr", "\t$Rd, $Rm, $imm5",
996                    [(set tGPR:$Rd, (srl tGPR:$Rm, (i32 imm:$imm5)))]> {
997   bits<5> imm5;
998   let Inst{10-6} = imm5;
999 }
1000
1001 // LSR register
1002 def tLSRrr :                    // A8.6.91
1003   T1sItDPEncode<0b0011, (outs tGPR:$Rdn), (ins tGPR:$Rn, tGPR:$Rm),
1004                 IIC_iMOVsr,
1005                 "lsr", "\t$Rdn, $Rm",
1006                 [(set tGPR:$Rdn, (srl tGPR:$Rn, tGPR:$Rm))]>;
1007
1008 // Move register
1009 let isMoveImm = 1 in
1010 def tMOVi8 : T1sI<(outs tGPR:$Rd), (ins imm0_255:$imm8), IIC_iMOVi,
1011                   "mov", "\t$Rd, $imm8",
1012                   [(set tGPR:$Rd, imm0_255:$imm8)]>,
1013              T1General<{1,0,0,?,?}> {
1014   // A8.6.96
1015   bits<3> Rd;
1016   bits<8> imm8;
1017   let Inst{10-8} = Rd;
1018   let Inst{7-0}  = imm8;
1019 }
1020
1021 // A7-73: MOV(2) - mov setting flag.
1022
1023 let neverHasSideEffects = 1 in {
1024 def tMOVr : Thumb1pI<(outs GPR:$Rd), (ins GPR:$Rm), AddrModeNone,
1025                       2, IIC_iMOVr,
1026                       "mov", "\t$Rd, $Rm", "", []>,
1027                   T1Special<{1,0,?,?}> {
1028   // A8.6.97
1029   bits<4> Rd;
1030   bits<4> Rm;
1031   let Inst{7}   = Rd{3};
1032   let Inst{6-3} = Rm;
1033   let Inst{2-0} = Rd{2-0};
1034 }
1035 let Defs = [CPSR] in
1036 def tMOVSr      : T1I<(outs tGPR:$Rd), (ins tGPR:$Rm), IIC_iMOVr,
1037                       "movs\t$Rd, $Rm", []>, Encoding16 {
1038   // A8.6.97
1039   bits<3> Rd;
1040   bits<3> Rm;
1041   let Inst{15-6} = 0b0000000000;
1042   let Inst{5-3}  = Rm;
1043   let Inst{2-0}  = Rd;
1044 }
1045 } // neverHasSideEffects
1046
1047 // Multiply register
1048 let isCommutable = 1 in
1049 def tMUL :                      // A8.6.105 T1
1050   T1sItDPEncode<0b1101, (outs tGPR:$Rdn), (ins tGPR:$Rn, tGPR:$Rm),
1051                 IIC_iMUL32,
1052                 "mul", "\t$Rdn, $Rm, $Rdn",
1053                 [(set tGPR:$Rdn, (mul tGPR:$Rn, tGPR:$Rm))]>;
1054
1055 // Move inverse register
1056 def tMVN :                      // A8.6.107
1057   T1sIDPEncode<0b1111, (outs tGPR:$Rd), (ins tGPR:$Rn), IIC_iMVNr,
1058                "mvn", "\t$Rd, $Rn",
1059                [(set tGPR:$Rd, (not tGPR:$Rn))]>;
1060
1061 // Bitwise or register
1062 let isCommutable = 1 in
1063 def tORR :                      // A8.6.114
1064   T1sItDPEncode<0b1100, (outs tGPR:$Rdn), (ins tGPR:$Rn, tGPR:$Rm),
1065                 IIC_iBITr,
1066                 "orr", "\t$Rdn, $Rm",
1067                 [(set tGPR:$Rdn, (or tGPR:$Rn, tGPR:$Rm))]>;
1068
1069 // Swaps
1070 def tREV :                      // A8.6.134
1071   T1pIMiscEncode<{1,0,1,0,0,0,?}, (outs tGPR:$Rd), (ins tGPR:$Rm),
1072                  IIC_iUNAr,
1073                  "rev", "\t$Rd, $Rm",
1074                  [(set tGPR:$Rd, (bswap tGPR:$Rm))]>,
1075                  Requires<[IsThumb, IsThumb1Only, HasV6]>;
1076
1077 def tREV16 :                    // A8.6.135
1078   T1pIMiscEncode<{1,0,1,0,0,1,?}, (outs tGPR:$Rd), (ins tGPR:$Rm),
1079                  IIC_iUNAr,
1080                  "rev16", "\t$Rd, $Rm",
1081              [(set tGPR:$Rd, (rotr (bswap tGPR:$Rm), (i32 16)))]>,
1082                 Requires<[IsThumb, IsThumb1Only, HasV6]>;
1083
1084 def tREVSH :                    // A8.6.136
1085   T1pIMiscEncode<{1,0,1,0,1,1,?}, (outs tGPR:$Rd), (ins tGPR:$Rm),
1086                  IIC_iUNAr,
1087                  "revsh", "\t$Rd, $Rm",
1088                  [(set tGPR:$Rd, (sra (bswap tGPR:$Rm), (i32 16)))]>,
1089                  Requires<[IsThumb, IsThumb1Only, HasV6]>;
1090
1091 // Rotate right register
1092 def tROR :                      // A8.6.139
1093   T1sItDPEncode<0b0111, (outs tGPR:$Rdn), (ins tGPR:$Rn, tGPR:$Rm),
1094                 IIC_iMOVsr,
1095                 "ror", "\t$Rdn, $Rm",
1096                 [(set tGPR:$Rdn, (rotr tGPR:$Rn, tGPR:$Rm))]>;
1097
1098 // Negate register
1099 def tRSB :                      // A8.6.141
1100   T1sIDPEncode<0b1001, (outs tGPR:$Rd), (ins tGPR:$Rn),
1101                IIC_iALUi,
1102                "rsb", "\t$Rd, $Rn, #0",
1103                [(set tGPR:$Rd, (ineg tGPR:$Rn))]>;
1104
1105 // Subtract with carry register
1106 let Uses = [CPSR] in
1107 def tSBC :                      // A8.6.151
1108   T1sItDPEncode<0b0110, (outs tGPR:$Rdn), (ins tGPR:$Rn, tGPR:$Rm),
1109                 IIC_iALUr,
1110                 "sbc", "\t$Rdn, $Rm",
1111                 [(set tGPR:$Rdn, (sube tGPR:$Rn, tGPR:$Rm))]>;
1112
1113 // Subtract immediate
1114 def tSUBi3 :                    // A8.6.210 T1
1115   T1sIGenEncodeImm<0b01111, (outs tGPR:$Rd), (ins tGPR:$Rm, i32imm:$imm3),
1116                    IIC_iALUi,
1117                    "sub", "\t$Rd, $Rm, $imm3",
1118                    [(set tGPR:$Rd, (add tGPR:$Rm, imm0_7_neg:$imm3))]> {
1119   bits<3> imm3;
1120   let Inst{8-6} = imm3;
1121 }
1122
1123 def tSUBi8 :                    // A8.6.210 T2
1124   T1sItGenEncodeImm<{1,1,1,?,?}, (outs tGPR:$Rdn), (ins tGPR:$Rn, i32imm:$imm8),
1125                     IIC_iALUi,
1126                     "sub", "\t$Rdn, $imm8",
1127                     [(set tGPR:$Rdn, (add tGPR:$Rn, imm8_255_neg:$imm8))]>;
1128
1129 // Subtract register
1130 def tSUBrr :                    // A8.6.212
1131   T1sIGenEncode<0b01101, (outs tGPR:$Rd), (ins tGPR:$Rn, tGPR:$Rm),
1132                 IIC_iALUr,
1133                 "sub", "\t$Rd, $Rn, $Rm",
1134                 [(set tGPR:$Rd, (sub tGPR:$Rn, tGPR:$Rm))]>;
1135
1136 // TODO: A7-96: STMIA - store multiple.
1137
1138 // Sign-extend byte
1139 def tSXTB :                     // A8.6.222
1140   T1pIMiscEncode<{0,0,1,0,0,1,?}, (outs tGPR:$Rd), (ins tGPR:$Rm),
1141                  IIC_iUNAr,
1142                  "sxtb", "\t$Rd, $Rm",
1143                  [(set tGPR:$Rd, (sext_inreg tGPR:$Rm, i8))]>,
1144                  Requires<[IsThumb, IsThumb1Only, HasV6]>;
1145
1146 // Sign-extend short
1147 def tSXTH :                     // A8.6.224
1148   T1pIMiscEncode<{0,0,1,0,0,0,?}, (outs tGPR:$Rd), (ins tGPR:$Rm),
1149                  IIC_iUNAr,
1150                  "sxth", "\t$Rd, $Rm",
1151                  [(set tGPR:$Rd, (sext_inreg tGPR:$Rm, i16))]>,
1152                  Requires<[IsThumb, IsThumb1Only, HasV6]>;
1153
1154 // Test
1155 let isCompare = 1, isCommutable = 1, Defs = [CPSR] in
1156 def tTST :                      // A8.6.230
1157   T1pIDPEncode<0b1000, (outs), (ins tGPR:$Rn, tGPR:$Rm), IIC_iTSTr,
1158                "tst", "\t$Rn, $Rm",
1159                [(ARMcmpZ (and_su tGPR:$Rn, tGPR:$Rm), 0)]>;
1160
1161 // Zero-extend byte
1162 def tUXTB :                     // A8.6.262
1163   T1pIMiscEncode<{0,0,1,0,1,1,?}, (outs tGPR:$Rd), (ins tGPR:$Rm),
1164                  IIC_iUNAr,
1165                  "uxtb", "\t$Rd, $Rm",
1166                  [(set tGPR:$Rd, (and tGPR:$Rm, 0xFF))]>,
1167                  Requires<[IsThumb, IsThumb1Only, HasV6]>;
1168
1169 // Zero-extend short
1170 def tUXTH :                     // A8.6.264
1171   T1pIMiscEncode<{0,0,1,0,1,0,?}, (outs tGPR:$Rd), (ins tGPR:$Rm),
1172                  IIC_iUNAr,
1173                  "uxth", "\t$Rd, $Rm",
1174                  [(set tGPR:$Rd, (and tGPR:$Rm, 0xFFFF))]>,
1175                  Requires<[IsThumb, IsThumb1Only, HasV6]>;
1176
1177 // Conditional move tMOVCCr - Used to implement the Thumb SELECT_CC operation.
1178 // Expanded after instruction selection into a branch sequence.
1179 let usesCustomInserter = 1 in  // Expanded after instruction selection.
1180   def tMOVCCr_pseudo :
1181   PseudoInst<(outs tGPR:$dst), (ins tGPR:$false, tGPR:$true, pred:$cc),
1182               NoItinerary,
1183              [/*(set tGPR:$dst, (ARMcmov tGPR:$false, tGPR:$true, imm:$cc))*/]>;
1184
1185 // tLEApcrel - Load a pc-relative address into a register without offending the
1186 // assembler.
1187
1188 def tADR : T1I<(outs tGPR:$Rd), (ins t_adrlabel:$addr, pred:$p),
1189                IIC_iALUi, "adr{$p}\t$Rd, #$addr", []>,
1190                T1Encoding<{1,0,1,0,0,?}> {
1191   bits<3> Rd;
1192   bits<8> addr;
1193   let Inst{10-8} = Rd;
1194   let Inst{7-0} = addr;
1195 }
1196
1197 let neverHasSideEffects = 1, isReMaterializable = 1 in
1198 def tLEApcrel   : tPseudoInst<(outs tGPR:$Rd), (ins i32imm:$label, pred:$p),
1199                               2, IIC_iALUi, []>;
1200
1201 def tLEApcrelJT : tPseudoInst<(outs tGPR:$Rd),
1202                               (ins i32imm:$label, nohash_imm:$id, pred:$p),
1203                               2, IIC_iALUi, []>;
1204
1205 //===----------------------------------------------------------------------===//
1206 // TLS Instructions
1207 //
1208
1209 // __aeabi_read_tp preserves the registers r1-r3.
1210 // This is a pseudo inst so that we can get the encoding right,
1211 // complete with fixup for the aeabi_read_tp function.
1212 let isCall = 1, Defs = [R0, R12, LR, CPSR], Uses = [SP] in
1213 def tTPsoft : tPseudoInst<(outs), (ins), 4, IIC_Br,
1214                           [(set R0, ARMthread_pointer)]>;
1215
1216 //===----------------------------------------------------------------------===//
1217 // SJLJ Exception handling intrinsics
1218 //
1219
1220 // eh_sjlj_setjmp() is an instruction sequence to store the return address and
1221 // save #0 in R0 for the non-longjmp case.  Since by its nature we may be coming
1222 // from some other function to get here, and we're using the stack frame for the
1223 // containing function to save/restore registers, we can't keep anything live in
1224 // regs across the eh_sjlj_setjmp(), else it will almost certainly have been
1225 // tromped upon when we get here from a longjmp(). We force everything out of
1226 // registers except for our own input by listing the relevant registers in
1227 // Defs. By doing so, we also cause the prologue/epilogue code to actively
1228 // preserve all of the callee-saved resgisters, which is exactly what we want.
1229 // $val is a scratch register for our use.
1230 let Defs = [ R0,  R1,  R2,  R3,  R4,  R5,  R6,  R7, R12, CPSR ],
1231     hasSideEffects = 1, isBarrier = 1, isCodeGenOnly = 1 in
1232 def tInt_eh_sjlj_setjmp : ThumbXI<(outs),(ins tGPR:$src, tGPR:$val),
1233                                   AddrModeNone, 0, NoItinerary, "","",
1234                           [(set R0, (ARMeh_sjlj_setjmp tGPR:$src, tGPR:$val))]>;
1235
1236 // FIXME: Non-Darwin version(s)
1237 let isBarrier = 1, hasSideEffects = 1, isTerminator = 1, isCodeGenOnly = 1,
1238     Defs = [ R7, LR, SP ] in
1239 def tInt_eh_sjlj_longjmp : XI<(outs), (ins GPR:$src, GPR:$scratch),
1240                               AddrModeNone, 0, IndexModeNone,
1241                               Pseudo, NoItinerary, "", "",
1242                               [(ARMeh_sjlj_longjmp GPR:$src, GPR:$scratch)]>,
1243                              Requires<[IsThumb, IsDarwin]>;
1244
1245 //===----------------------------------------------------------------------===//
1246 // Non-Instruction Patterns
1247 //
1248
1249 // Comparisons
1250 def : T1Pat<(ARMcmpZ tGPR:$Rn, imm0_255:$imm8),
1251             (tCMPi8  tGPR:$Rn, imm0_255:$imm8)>;
1252 def : T1Pat<(ARMcmpZ tGPR:$Rn, tGPR:$Rm),
1253             (tCMPr   tGPR:$Rn, tGPR:$Rm)>;
1254
1255 // Add with carry
1256 def : T1Pat<(addc   tGPR:$lhs, imm0_7:$rhs),
1257             (tADDi3 tGPR:$lhs, imm0_7:$rhs)>;
1258 def : T1Pat<(addc   tGPR:$lhs, imm8_255:$rhs),
1259             (tADDi8 tGPR:$lhs, imm8_255:$rhs)>;
1260 def : T1Pat<(addc   tGPR:$lhs, tGPR:$rhs),
1261             (tADDrr tGPR:$lhs, tGPR:$rhs)>;
1262
1263 // Subtract with carry
1264 def : T1Pat<(addc   tGPR:$lhs, imm0_7_neg:$rhs),
1265             (tSUBi3 tGPR:$lhs, imm0_7_neg:$rhs)>;
1266 def : T1Pat<(addc   tGPR:$lhs, imm8_255_neg:$rhs),
1267             (tSUBi8 tGPR:$lhs, imm8_255_neg:$rhs)>;
1268 def : T1Pat<(subc   tGPR:$lhs, tGPR:$rhs),
1269             (tSUBrr tGPR:$lhs, tGPR:$rhs)>;
1270
1271 // ConstantPool, GlobalAddress
1272 def : T1Pat<(ARMWrapper  tglobaladdr :$dst), (tLEApcrel tglobaladdr :$dst)>;
1273 def : T1Pat<(ARMWrapper  tconstpool  :$dst), (tLEApcrel tconstpool  :$dst)>;
1274
1275 // JumpTable
1276 def : T1Pat<(ARMWrapperJT tjumptable:$dst, imm:$id),
1277             (tLEApcrelJT tjumptable:$dst, imm:$id)>;
1278
1279 // Direct calls
1280 def : T1Pat<(ARMtcall texternalsym:$func), (tBL texternalsym:$func)>,
1281       Requires<[IsThumb, IsNotDarwin]>;
1282 def : T1Pat<(ARMtcall texternalsym:$func), (tBLr9 texternalsym:$func)>,
1283       Requires<[IsThumb, IsDarwin]>;
1284
1285 def : Tv5Pat<(ARMcall texternalsym:$func), (tBLXi texternalsym:$func)>,
1286       Requires<[IsThumb, HasV5T, IsNotDarwin]>;
1287 def : Tv5Pat<(ARMcall texternalsym:$func), (tBLXi_r9 texternalsym:$func)>,
1288       Requires<[IsThumb, HasV5T, IsDarwin]>;
1289
1290 // Indirect calls to ARM routines
1291 def : Tv5Pat<(ARMcall GPR:$dst), (tBLXr GPR:$dst)>,
1292       Requires<[IsThumb, HasV5T, IsNotDarwin]>;
1293 def : Tv5Pat<(ARMcall GPR:$dst), (tBLXr_r9 GPR:$dst)>,
1294       Requires<[IsThumb, HasV5T, IsDarwin]>;
1295
1296 // zextload i1 -> zextload i8
1297 def : T1Pat<(zextloadi1 t_addrmode_rrs1:$addr),
1298             (tLDRBr t_addrmode_rrs1:$addr)>;
1299 def : T1Pat<(zextloadi1 t_addrmode_is1:$addr),
1300             (tLDRBi t_addrmode_is1:$addr)>;
1301
1302 // extload -> zextload
1303 def : T1Pat<(extloadi1  t_addrmode_rrs1:$addr), (tLDRBr t_addrmode_rrs1:$addr)>;
1304 def : T1Pat<(extloadi1  t_addrmode_is1:$addr),  (tLDRBi t_addrmode_is1:$addr)>;
1305 def : T1Pat<(extloadi8  t_addrmode_rrs1:$addr), (tLDRBr t_addrmode_rrs1:$addr)>;
1306 def : T1Pat<(extloadi8  t_addrmode_is1:$addr),  (tLDRBi t_addrmode_is1:$addr)>;
1307 def : T1Pat<(extloadi16 t_addrmode_rrs2:$addr), (tLDRHr t_addrmode_rrs2:$addr)>;
1308 def : T1Pat<(extloadi16 t_addrmode_is2:$addr),  (tLDRHi t_addrmode_is2:$addr)>;
1309
1310 // If it's impossible to use [r,r] address mode for sextload, select to
1311 // ldr{b|h} + sxt{b|h} instead.
1312 def : T1Pat<(sextloadi8 t_addrmode_is1:$addr),
1313             (tSXTB (tLDRBi t_addrmode_is1:$addr))>,
1314       Requires<[IsThumb, IsThumb1Only, HasV6]>;
1315 def : T1Pat<(sextloadi8 t_addrmode_rrs1:$addr),
1316             (tSXTB (tLDRBr t_addrmode_rrs1:$addr))>,
1317       Requires<[IsThumb, IsThumb1Only, HasV6]>;
1318 def : T1Pat<(sextloadi16 t_addrmode_is2:$addr),
1319             (tSXTH (tLDRHi t_addrmode_is2:$addr))>,
1320       Requires<[IsThumb, IsThumb1Only, HasV6]>;
1321 def : T1Pat<(sextloadi16 t_addrmode_rrs2:$addr),
1322             (tSXTH (tLDRHr t_addrmode_rrs2:$addr))>,
1323       Requires<[IsThumb, IsThumb1Only, HasV6]>;
1324
1325 def : T1Pat<(sextloadi8 t_addrmode_rrs1:$addr),
1326             (tASRri (tLSLri (tLDRBr t_addrmode_rrs1:$addr), 24), 24)>;
1327 def : T1Pat<(sextloadi8 t_addrmode_is1:$addr),
1328             (tASRri (tLSLri (tLDRBi t_addrmode_is1:$addr), 24), 24)>;
1329 def : T1Pat<(sextloadi16 t_addrmode_rrs2:$addr),
1330             (tASRri (tLSLri (tLDRHr t_addrmode_rrs2:$addr), 16), 16)>;
1331 def : T1Pat<(sextloadi16 t_addrmode_is2:$addr),
1332             (tASRri (tLSLri (tLDRHi t_addrmode_is2:$addr), 16), 16)>;
1333
1334 // Large immediate handling.
1335
1336 // Two piece imms.
1337 def : T1Pat<(i32 thumb_immshifted:$src),
1338             (tLSLri (tMOVi8 (thumb_immshifted_val imm:$src)),
1339                     (thumb_immshifted_shamt imm:$src))>;
1340
1341 def : T1Pat<(i32 imm0_255_comp:$src),
1342             (tMVN (tMOVi8 (imm_comp_XFORM imm:$src)))>;
1343
1344 // Pseudo instruction that combines ldr from constpool and add pc. This should
1345 // be expanded into two instructions late to allow if-conversion and
1346 // scheduling.
1347 let isReMaterializable = 1 in
1348 def tLDRpci_pic : PseudoInst<(outs GPR:$dst), (ins i32imm:$addr, pclabel:$cp),
1349                              NoItinerary,
1350                [(set GPR:$dst, (ARMpic_add (load (ARMWrapper tconstpool:$addr)),
1351                                            imm:$cp))]>,
1352                Requires<[IsThumb, IsThumb1Only]>;
1353
1354 // Pseudo-instruction for merged POP and return.
1355 // FIXME: remove when we have a way to marking a MI with these properties.
1356 let isReturn = 1, isTerminator = 1, isBarrier = 1, mayLoad = 1,
1357     hasExtraDefRegAllocReq = 1 in
1358 def tPOP_RET : tPseudoExpand<(outs), (ins pred:$p, reglist:$regs, variable_ops),
1359                            2, IIC_iPop_Br, [],
1360                            (tPOP pred:$p, reglist:$regs)>;
1361
1362 // Indirect branch using "mov pc, $Rm"
1363 let isBranch = 1, isTerminator = 1, isBarrier = 1, isIndirectBranch = 1 in {
1364   def tBRIND : tPseudoExpand<(outs), (ins GPR:$Rm, pred:$p),
1365                   2, IIC_Br, [(brind GPR:$Rm)],
1366                   (tMOVr PC, GPR:$Rm, pred:$p)>;
1367 }