Revert " [LoongArch][ISel] Check the number of sign bits in `PatGprGpr_32` (#107432)"
[llvm-project.git] / llvm / lib / Target / AVR / AVRInstrInfo.td
blob6cfbf9c83dc329cbad27a1e5845188fe9394ffec
1 //===-- AVRInstrInfo.td - AVR Instruction defs -------------*- tablegen -*-===//
2 //
3 // Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4 // See https://llvm.org/LICENSE.txt for license information.
5 // SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
6 //
7 //===----------------------------------------------------------------------===//
8 //
9 // This file describes the AVR instructions in TableGen format.
11 //===----------------------------------------------------------------------===//
13 include "AVRInstrFormats.td"
15 //===----------------------------------------------------------------------===//
16 // AVR Type Profiles
17 //===----------------------------------------------------------------------===//
19 def SDT_AVRCallSeqStart : SDCallSeqStart<[SDTCisVT<0, i16>, SDTCisVT<1, i16>]>;
20 def SDT_AVRCallSeqEnd : SDCallSeqEnd<[SDTCisVT<0, i16>, SDTCisVT<1, i16>]>;
21 def SDT_AVRCall : SDTypeProfile<0, -1, [SDTCisVT<0, iPTR>]>;
22 def SDT_AVRWrapper : SDTypeProfile<1, 1, [SDTCisSameAs<0, 1>, SDTCisPtrTy<0>]>;
23 def SDT_AVRBrcond
24     : SDTypeProfile<0, 2, [SDTCisVT<0, OtherVT>, SDTCisVT<1, i8>]>;
25 def SDT_AVRCmp : SDTypeProfile<0, 2, [SDTCisSameAs<0, 1>]>;
26 def SDT_AVRTst : SDTypeProfile<0, 1, [SDTCisInt<0>]>;
27 def SDT_AVRSelectCC
28     : SDTypeProfile<1, 3,
29                     [SDTCisSameAs<0, 1>, SDTCisSameAs<1, 2>, SDTCisVT<3, i8>]>;
31 //===----------------------------------------------------------------------===//
32 // AVR Specific Node Definitions
33 //===----------------------------------------------------------------------===//
35 def AVRretglue : SDNode<"AVRISD::RET_GLUE", SDTNone,
36                         [SDNPHasChain, SDNPOptInGlue, SDNPVariadic]>;
37 def AVRretiglue : SDNode<"AVRISD::RETI_GLUE", SDTNone,
38                          [SDNPHasChain, SDNPOptInGlue, SDNPVariadic]>;
40 def AVRcallseq_start : SDNode<"ISD::CALLSEQ_START", SDT_AVRCallSeqStart,
41                               [SDNPHasChain, SDNPOutGlue]>;
42 def AVRcallseq_end : SDNode<"ISD::CALLSEQ_END", SDT_AVRCallSeqEnd,
43                             [SDNPHasChain, SDNPOptInGlue, SDNPOutGlue]>;
45 def AVRcall : SDNode<"AVRISD::CALL", SDT_AVRCall,
46                      [SDNPHasChain, SDNPOutGlue, SDNPOptInGlue, SDNPVariadic]>;
48 def AVRWrapper : SDNode<"AVRISD::WRAPPER", SDT_AVRWrapper>;
50 def AVRbrcond
51     : SDNode<"AVRISD::BRCOND", SDT_AVRBrcond, [SDNPHasChain, SDNPInGlue]>;
52 def AVRcmp : SDNode<"AVRISD::CMP", SDT_AVRCmp, [SDNPOutGlue]>;
53 def AVRcmpc : SDNode<"AVRISD::CMPC", SDT_AVRCmp, [SDNPInGlue, SDNPOutGlue]>;
54 def AVRtst : SDNode<"AVRISD::TST", SDT_AVRTst, [SDNPOutGlue]>;
55 def AVRselectcc : SDNode<"AVRISD::SELECT_CC", SDT_AVRSelectCC, [SDNPInGlue]>;
57 // Shift nodes.
58 def AVRlsl : SDNode<"AVRISD::LSL", SDTIntUnaryOp>;
59 def AVRlsr : SDNode<"AVRISD::LSR", SDTIntUnaryOp>;
60 def AVRrol : SDNode<"AVRISD::ROL", SDTIntUnaryOp>;
61 def AVRror : SDNode<"AVRISD::ROR", SDTIntUnaryOp>;
62 def AVRasr : SDNode<"AVRISD::ASR", SDTIntUnaryOp>;
63 def AVRlslhi : SDNode<"AVRISD::LSLHI", SDTIntUnaryOp>;
64 def AVRlsrlo : SDNode<"AVRISD::LSRLO", SDTIntUnaryOp>;
65 def AVRasrlo : SDNode<"AVRISD::ASRLO", SDTIntUnaryOp>;
66 def AVRlslbn : SDNode<"AVRISD::LSLBN", SDTIntBinOp>;
67 def AVRlsrbn : SDNode<"AVRISD::LSRBN", SDTIntBinOp>;
68 def AVRasrbn : SDNode<"AVRISD::ASRBN", SDTIntBinOp>;
69 def AVRlslwn : SDNode<"AVRISD::LSLWN", SDTIntBinOp>;
70 def AVRlsrwn : SDNode<"AVRISD::LSRWN", SDTIntBinOp>;
71 def AVRasrwn : SDNode<"AVRISD::ASRWN", SDTIntBinOp>;
72 def AVRlslw : SDNode<"AVRISD::LSLW", SDTIntShiftDOp>;
73 def AVRlsrw : SDNode<"AVRISD::LSRW", SDTIntShiftDOp>;
74 def AVRasrw : SDNode<"AVRISD::ASRW", SDTIntShiftDOp>;
76 // Pseudo shift nodes for non-constant shift amounts.
77 def AVRlslLoop : SDNode<"AVRISD::LSLLOOP", SDTIntShiftOp>;
78 def AVRlsrLoop : SDNode<"AVRISD::LSRLOOP", SDTIntShiftOp>;
79 def AVRrolLoop : SDNode<"AVRISD::ROLLOOP", SDTIntShiftOp>;
80 def AVRrorLoop : SDNode<"AVRISD::RORLOOP", SDTIntShiftOp>;
81 def AVRasrLoop : SDNode<"AVRISD::ASRLOOP", SDTIntShiftOp>;
83 // SWAP node.
84 def AVRSwap : SDNode<"AVRISD::SWAP", SDTIntUnaryOp>;
86 //===----------------------------------------------------------------------===//
87 // AVR Operands, Complex Patterns and Transformations Definitions.
88 //===----------------------------------------------------------------------===//
90 def imm8_neg_XFORM : SDNodeXForm<imm, [{
91   return CurDAG->getTargetConstant(-N->getAPIntValue(), SDLoc(N), MVT::i8);
92 }]>;
94 def imm16_neg_XFORM : SDNodeXForm<imm, [{
95   return CurDAG->getTargetConstant(-N->getAPIntValue(), SDLoc(N), MVT::i16);
96 }]>;
98 def imm0_63_neg : PatLeaf<(imm), [{
99   int64_t val = -N->getSExtValue();
100   return val >= 0 && val < 64;
101 }], imm16_neg_XFORM>;
103 def uimm6 : PatLeaf<(imm), [{ return isUInt<6>(N->getZExtValue()); }]>;
105 // imm_com8_XFORM - Return the complement of a imm_com8 value
106 def imm_com8_XFORM : SDNodeXForm<imm, [{
107   return CurDAG->getTargetConstant(
108       ~((uint8_t) N->getZExtValue()), SDLoc(N), MVT::i8);
109 }]>;
111 // imm_com8 - Match an immediate that is a complement
112 // of a 8-bit immediate.
113 // Note: this pattern doesn't require an encoder method and such, as it's
114 // only used on aliases (Pat<> and InstAlias<>). The actual encoding
115 // is handled by the destination instructions, which use imm_com8.
116 def imm_com8_asmoperand : AsmOperandClass { let Name = "ImmCom8"; }
117 def imm_com8 : Operand<i8> { let ParserMatchClass = imm_com8_asmoperand; }
119 def ioaddr_XFORM : SDNodeXForm<imm, [{
120   uint8_t offset = Subtarget->getIORegisterOffset();
121   return CurDAG->getTargetConstant(
122       uint8_t(N->getZExtValue()) - offset, SDLoc(N), MVT::i8);
123 }]>;
125 def iobitpos8_XFORM : SDNodeXForm<imm, [{
126   return CurDAG->getTargetConstant(
127       Log2_32(uint8_t(N->getZExtValue())), SDLoc(N), MVT::i8);
128 }]>;
130 def iobitposn8_XFORM : SDNodeXForm<imm, [{
131   return CurDAG->getTargetConstant(
132       Log2_32(uint8_t(~N->getZExtValue())), SDLoc(N), MVT::i8);
133 }]>;
135 def ioaddr8 : PatLeaf<(imm), [{
136   uint8_t offset = Subtarget->getIORegisterOffset();
137   uint64_t val = N->getZExtValue() - offset;
138   return val < 0x40;
139 }], ioaddr_XFORM>;
141 def lowioaddr8 : PatLeaf<(imm), [{
142   uint8_t offset = Subtarget->getIORegisterOffset();
143   uint64_t val = N->getZExtValue() - offset;
144   return val < 0x20;
145 }], ioaddr_XFORM>;
147 def ioaddr16 : PatLeaf<(imm), [{
148   uint8_t offset = Subtarget->getIORegisterOffset();
149   uint64_t val = N->getZExtValue() - offset;
150   return val < 0x3f;
151 }], ioaddr_XFORM>;
153 def iobitpos8 : PatLeaf<(imm), [{
154   return isPowerOf2_32(uint8_t(N->getZExtValue()));
155 }], iobitpos8_XFORM>;
157 def iobitposn8 : PatLeaf<(imm), [{
158   return isPowerOf2_32(uint8_t(~N->getZExtValue()));
159 }], iobitposn8_XFORM>;
161 def MemriAsmOperand : AsmOperandClass {
162   let Name = "Memri";
163   let ParserMethod = "parseMemriOperand";
166 /// Address operand for `reg+imm` used by STD and LDD.
167 def memri : Operand<iPTR> {
168   let MIOperandInfo = (ops PTRDISPREGS, i16imm);
170   let PrintMethod = "printMemri";
171   let EncoderMethod = "encodeMemri";
172   let DecoderMethod = "decodeMemri";
174   let ParserMatchClass = MemriAsmOperand;
177 // Address operand for `SP+imm` used by STD{W}SPQRr
178 def memspi : Operand<iPTR> {
179   let MIOperandInfo = (ops GPRSP, i16imm);
180   let PrintMethod = "printMemspi";
183 def relbrtarget_7 : Operand<OtherVT> {
184   let PrintMethod = "printPCRelImm";
185   let EncoderMethod = "encodeRelCondBrTarget<AVR::fixup_7_pcrel>";
188 def brtarget_13 : Operand<OtherVT> {
189   let PrintMethod = "printPCRelImm";
190   let EncoderMethod = "encodeRelCondBrTarget<AVR::fixup_13_pcrel>";
193 def rcalltarget_13 : Operand<i16> {
194   let PrintMethod = "printPCRelImm";
195   let EncoderMethod = "encodeRelCondBrTarget<AVR::fixup_13_pcrel>";
198 // The target of a 22 or 16-bit call/jmp instruction.
199 def call_target : Operand<iPTR> {
200   let EncoderMethod = "encodeCallTarget";
201   let DecoderMethod = "decodeCallTarget";
204 // A 16-bit address (which can lead to an R_AVR_16 relocation).
205 def imm16 : Operand<i16> { let EncoderMethod = "encodeImm<AVR::fixup_16, 2>"; }
207 // A 7-bit address (which can lead to an R_AVR_LDS_STS_16 relocation).
208 def imm7tiny : Operand<i16> {
209   let EncoderMethod = "encodeImm<AVR::fixup_lds_sts_16, 0>";
212 /// A 6-bit immediate used in the ADIW/SBIW instructions.
213 def imm_arith6 : Operand<i16> {
214   let EncoderMethod = "encodeImm<AVR::fixup_6_adiw, 0>";
217 /// An 8-bit immediate inside an instruction with the same format
218 /// as the `LDI` instruction (the `FRdK` format).
219 def imm_ldi8 : Operand<i8> {
220   let EncoderMethod = "encodeImm<AVR::fixup_ldi, 0>";
223 /// A 5-bit port number used in SBIC and friends (the `FIOBIT` format).
224 def imm_port5 : Operand<i8> {
225   let EncoderMethod = "encodeImm<AVR::fixup_port5, 0>";
228 /// A 6-bit port number used in the `IN` instruction and friends (the
229 /// `FIORdA` format.
230 def imm_port6 : Operand<i8> {
231   let EncoderMethod = "encodeImm<AVR::fixup_port6, 0>";
234 // Addressing mode pattern reg+imm6
235 def addr : ComplexPattern<iPTR, 2, "SelectAddr", [], [SDNPWantRoot]>;
237 // AsmOperand class for a pointer register.
238 // Used with the LD/ST family of instructions.
239 // See FSTLD in AVRInstrFormats.td
240 def PtrRegAsmOperand : AsmOperandClass { let Name = "Reg"; }
242 // A special operand type for the LD/ST instructions.
243 // It converts the pointer register number into a two-bit field used in the
244 // instruction.
245 def LDSTPtrReg : Operand<i16> {
246   let MIOperandInfo = (ops PTRREGS);
247   let EncoderMethod = "encodeLDSTPtrReg";
249   let ParserMatchClass = PtrRegAsmOperand;
252 // A special operand type for the LDD/STD instructions.
253 // It behaves identically to the LD/ST version, except restricts
254 // the pointer registers to Y and Z.
255 def LDDSTDPtrReg : Operand<i16> {
256   let MIOperandInfo = (ops PTRDISPREGS);
257   let EncoderMethod = "encodeLDSTPtrReg";
259   let ParserMatchClass = PtrRegAsmOperand;
262 //===----------------------------------------------------------------------===//
263 // AVR predicates for subtarget features
264 //===----------------------------------------------------------------------===//
266 def HasSRAM : Predicate<"Subtarget->hasSRAM()">,
267               AssemblerPredicate<(all_of FeatureSRAM)>;
269 def HasJMPCALL : Predicate<"Subtarget->hasJMPCALL()">,
270                  AssemblerPredicate<(all_of FeatureJMPCALL)>;
272 def HasIJMPCALL : Predicate<"Subtarget->hasIJMPCALL()">,
273                   AssemblerPredicate<(all_of FeatureIJMPCALL)>;
275 def HasEIJMPCALL : Predicate<"Subtarget->hasEIJMPCALL()">,
276                    AssemblerPredicate<(all_of FeatureEIJMPCALL)>;
278 def HasADDSUBIW : Predicate<"Subtarget->hasADDSUBIW()">,
279                   AssemblerPredicate<(all_of FeatureADDSUBIW)>;
281 def HasSmallStack : Predicate<"Subtarget->HasSmallStack()">,
282                     AssemblerPredicate<(all_of FeatureSmallStack)>;
284 def HasMOVW : Predicate<"Subtarget->hasMOVW()">,
285               AssemblerPredicate<(all_of FeatureMOVW)>;
287 def HasLPM : Predicate<"Subtarget->hasLPM()">,
288              AssemblerPredicate<(all_of FeatureLPM)>;
290 def HasLPMX : Predicate<"Subtarget->hasLPMX()">,
291               AssemblerPredicate<(all_of FeatureLPMX)>;
293 def HasELPM : Predicate<"Subtarget->hasELPM()">,
294               AssemblerPredicate<(all_of FeatureELPM)>;
296 def HasELPMX : Predicate<"Subtarget->hasELPMX()">,
297                AssemblerPredicate<(all_of FeatureELPMX)>;
299 def HasSPM : Predicate<"Subtarget->hasSPM()">,
300              AssemblerPredicate<(all_of FeatureSPM)>;
302 def HasSPMX : Predicate<"Subtarget->hasSPMX()">,
303               AssemblerPredicate<(all_of FeatureSPMX)>;
305 def HasDES : Predicate<"Subtarget->hasDES()">,
306              AssemblerPredicate<(all_of FeatureDES)>;
308 def SupportsRMW : Predicate<"Subtarget->supportsRMW()">,
309                   AssemblerPredicate<(all_of FeatureRMW)>;
311 def SupportsMultiplication : Predicate<"Subtarget->supportsMultiplication()">,
312                              AssemblerPredicate<(all_of FeatureMultiplication)>;
314 def HasBREAK : Predicate<"Subtarget->hasBREAK()">,
315                AssemblerPredicate<(all_of FeatureBREAK)>;
317 def HasTinyEncoding : Predicate<"Subtarget->hasTinyEncoding()">,
318                       AssemblerPredicate<(all_of FeatureTinyEncoding)>;
320 def HasNonTinyEncoding : Predicate<"!Subtarget->hasTinyEncoding()">,
321                          AssemblerPredicate<(any_of (not FeatureTinyEncoding))>;
323 // AVR specific condition code. These correspond to AVR_*_COND in
324 // AVRInstrInfo.td. They must be kept in synch.
325 def AVR_COND_EQ : PatLeaf<(i8 0)>;
326 def AVR_COND_NE : PatLeaf<(i8 1)>;
327 def AVR_COND_GE : PatLeaf<(i8 2)>;
328 def AVR_COND_LT : PatLeaf<(i8 3)>;
329 def AVR_COND_SH : PatLeaf<(i8 4)>;
330 def AVR_COND_LO : PatLeaf<(i8 5)>;
331 def AVR_COND_MI : PatLeaf<(i8 6)>;
332 def AVR_COND_PL : PatLeaf<(i8 7)>;
334 //===----------------------------------------------------------------------===//
335 //===----------------------------------------------------------------------===//
336 // AVR Instruction list
337 //===----------------------------------------------------------------------===//
338 //===----------------------------------------------------------------------===//
340 // ADJCALLSTACKDOWN/UP implicitly use/def SP because they may be expanded into
341 // a stack adjustment and the codegen must know that they may modify the stack
342 // pointer before prolog-epilog rewriting occurs.
343 // Pessimistically assume ADJCALLSTACKDOWN / ADJCALLSTACKUP will become
344 // sub / add which can clobber SREG.
345 let Defs = [SP, SREG], Uses = [SP] in {
346   def ADJCALLSTACKDOWN : Pseudo<(outs), (ins i16imm:$amt, i16imm:$amt2),
347                                 "#ADJCALLSTACKDOWN",
348                                 [(AVRcallseq_start timm:$amt, timm:$amt2)]>;
350   // R31R30 is used to update SP. It is normally free because it is a
351   // call-clobbered register but it is necessary to set it as a def as the
352   // register allocator might use it in rare cases (for rematerialization, it
353   // seems). hasSideEffects needs to be set to true so this instruction isn't
354   // considered dead.
355   let Defs = [R31R30], hasSideEffects = 1 in def ADJCALLSTACKUP
356       : Pseudo<(outs), (ins i16imm:$amt1, i16imm:$amt2),
357                "#ADJCALLSTACKUP", [(AVRcallseq_end timm:$amt1, timm:$amt2)]>;
360 //===----------------------------------------------------------------------===//
361 // Addition
362 //===----------------------------------------------------------------------===//
363 let isCommutable = 1, Constraints = "$src = $rd", Defs = [SREG] in {
364   // ADD Rd, Rr
365   // Adds two 8-bit registers.
366   def ADDRdRr : FRdRr<0b0000, 0b11, (outs GPR8:$rd),(ins GPR8:$src, GPR8:$rr),
367                       "add\t$rd, $rr",
368                       [(set i8:$rd, (add i8:$src, i8:$rr)), (implicit SREG)]>;
370   // ADDW Rd+1:Rd, Rr+1:Rr
371   // Pseudo instruction to add four 8-bit registers as two 16-bit values.
372   //
373   // Expands to:
374   // add Rd,    Rr
375   // adc Rd+1, Rr+1
376   def ADDWRdRr : Pseudo<(outs DREGS:$rd), (ins DREGS:$src, DREGS:$rr),
377                         "addw\t$rd, $rr",
378                         [(set i16:$rd, (add i16:$src, i16:$rr)),
379                          (implicit SREG)]>;
381   // ADC Rd, Rr
382   // Adds two 8-bit registers with carry.
383   let Uses = [SREG] in
384   def ADCRdRr : FRdRr<0b0001, 0b11, (outs GPR8:$rd), (ins GPR8:$src, GPR8:$rr),
385                       "adc\t$rd, $rr",
386                       [(set i8:$rd, (adde i8:$src, i8:$rr)), (implicit SREG)]>;
388   // ADCW Rd+1:Rd, Rr+1:Rr
389   // Pseudo instruction to add four 8-bit registers as two 16-bit values with
390   // carry.
391   //
392   // Expands to:
393   // adc Rd,   Rr
394   // adc Rd+1, Rr+1
395   let Uses = [SREG] in
396   def ADCWRdRr : Pseudo<(outs DREGS:$rd), (ins DREGS:$src, DREGS:$rr),
397                         "adcw\t$rd, $rr",
398                         [(set i16:$rd, (adde i16:$src, i16:$rr)),
399                          (implicit SREG)]>;
401   // AIDW Rd, k
402   // Adds an immediate 6-bit value K to Rd, placing the result in Rd.
403   def ADIWRdK : FWRdK<0b0, (outs IWREGS:$rd), (ins IWREGS :$src, imm_arith6:$k),
404                       "adiw\t$rd, $k",
405                       [(set i16:$rd, (add i16:$src, uimm6:$k)),
406                        (implicit SREG)]>,
407                 Requires<[HasADDSUBIW]>;
410 //===----------------------------------------------------------------------===//
411 // Subtraction
412 //===----------------------------------------------------------------------===//
413 let Constraints = "$rs = $rd", Defs = [SREG] in {
414   // SUB Rd, Rr
415   // Subtracts the 8-bit value of Rr from Rd and places the value in Rd.
416   def SUBRdRr : FRdRr<0b0001, 0b10, (outs GPR8:$rd), (ins GPR8:$rs, GPR8:$rr),
417                       "sub\t$rd, $rr",
418                       [(set i8:$rd, (sub i8:$rs, i8:$rr)), (implicit SREG)]>;
420   // SUBW Rd+1:Rd, Rr+1:Rr
421   // Subtracts two 16-bit values and places the result into Rd.
422   //
423   // Expands to:
424   // sub Rd,   Rr
425   // sbc Rd+1, Rr+1
426   def SUBWRdRr : Pseudo<(outs DREGS:$rd), (ins DREGS:$rs, DREGS:$rr),
427                         "subw\t$rd, $rr",
428                         [(set i16:$rd, (sub i16:$rs, i16:$rr)),
429                          (implicit SREG)]>;
431   def SUBIRdK : FRdK<0b0101, (outs LD8:$rd), (ins LD8:$rs, imm_ldi8:$k),
432                      "subi\t$rd, $k",
433                      [(set i8:$rd, (sub i8:$rs, imm:$k)), (implicit SREG)]>;
435   // SUBIW Rd+1:Rd, K+1:K
436   //
437   // Expands to:
438   // subi Rd,   K
439   // sbci Rd+1, K+1
440   def SUBIWRdK : Pseudo<(outs DLDREGS:$rd), (ins DLDREGS:$rs, i16imm:$rr),
441                         "subiw\t$rd, $rr",
442                         [(set i16:$rd, (sub i16:$rs, imm:$rr)),
443                          (implicit SREG)]>;
445   def SBIWRdK : FWRdK<0b1, (outs IWREGS:$rd), (ins IWREGS:$rs, imm_arith6:$k),
446                       "sbiw\t$rd, $k",
447                       [(set i16:$rd, (sub i16:$rs, uimm6:$k)),
448                        (implicit SREG)]>,
449                 Requires<[HasADDSUBIW]>;
451   // Subtract with carry operations which must read the carry flag in SREG.
452   let Uses = [SREG] in {
453     def SBCRdRr : FRdRr<0b0000, 0b10, (outs GPR8:$rd), (ins GPR8:$rs, GPR8:$rr),
454                         "sbc\t$rd, $rr",
455                         [(set i8:$rd, (sube i8:$rs, i8:$rr)), (implicit SREG)]>;
457     // SBCW Rd+1:Rd, Rr+1:Rr
458     //
459     // Expands to:
460     // sbc Rd,   Rr
461     // sbc Rd+1, Rr+1
462     def SBCWRdRr : Pseudo<(outs DREGS:$rd), (ins DREGS:$rs, DREGS:$rr),
463                           "sbcw\t$rd, $rr",
464                           [(set i16:$rd, (sube i16:$rs, i16:$rr)),
465                            (implicit SREG)]>;
467     def SBCIRdK : FRdK<0b0100, (outs LD8:$rd), (ins LD8:$rs, imm_ldi8:$k),
468                        "sbci\t$rd, $k",
469                        [(set i8:$rd, (sube i8:$rs, imm:$k)), (implicit SREG)]>;
471     // SBCIW Rd+1:Rd, K+1:K
472     // sbci Rd,   K
473     // sbci Rd+1, K+1
474     def SBCIWRdK : Pseudo<(outs DLDREGS:$rd), (ins DLDREGS:$rs, i16imm:$rr),
475                           "sbciw\t$rd, $rr",
476                           [(set i16:$rd, (sube i16:$rs, imm:$rr)),
477                            (implicit SREG)]>;
478   }
481 //===----------------------------------------------------------------------===//
482 // Increment and Decrement
483 //===----------------------------------------------------------------------===//
484 let Constraints = "$src = $rd", Defs = [SREG] in {
485   def INCRd : FRd<0b1001, 0b0100011, (outs GPR8:$rd), (ins GPR8:$src),
486                   "inc\t$rd",
487                   [(set i8:$rd, (add i8:$src, 1)), (implicit SREG)]>;
489   def DECRd : FRd<0b1001, 0b0101010, (outs GPR8:$rd), (ins GPR8:$src),
490                   "dec\t$rd",
491                   [(set i8:$rd, (add i8:$src, -1)), (implicit SREG)]>;
494 //===----------------------------------------------------------------------===//
495 // Multiplication
496 //===----------------------------------------------------------------------===//
498 let isCommutable = 1, Defs = [R1, R0, SREG] in {
499   // MUL Rd, Rr
500   // Multiplies Rd by Rr and places the result into R1:R0.
501   let usesCustomInserter = 1 in {
502     def MULRdRr : FRdRr<0b1001, 0b11, (outs), (ins GPR8:$rd, GPR8:$rr),
503                         "mul\t$rd, $rr", []>,
504                   Requires<[SupportsMultiplication]>;
506     def MULSRdRr : FMUL2RdRr<0, (outs), (ins LD8:$rd, LD8:$rr),
507                              "muls\t$rd, $rr", []>,
508                    Requires<[SupportsMultiplication]>;
509   }
511   def MULSURdRr : FMUL2RdRr<1, (outs), (ins LD8lo:$rd, LD8lo:$rr),
512                             "mulsu\t$rd, $rr", []>,
513                   Requires<[SupportsMultiplication]>;
515   def FMUL : FFMULRdRr<0b01, (outs), (ins LD8lo:$rd, LD8lo:$rr),
516                        "fmul\t$rd, $rr", []>,
517              Requires<[SupportsMultiplication]>;
519   def FMULS : FFMULRdRr<0b10, (outs), (ins LD8lo:$rd, LD8lo:$rr),
520                         "fmuls\t$rd, $rr", []>,
521               Requires<[SupportsMultiplication]>;
523   def FMULSU : FFMULRdRr<0b11, (outs), (ins LD8lo:$rd, LD8lo:$rr),
524                          "fmulsu\t$rd, $rr", []>,
525                Requires<[SupportsMultiplication]>;
528 let Defs =
529     [R15, R14, R13, R12, R11, R10, R9, R8, R7, R6, R5, R4, R3, R2, R1, R0] in
530 def DESK : FDES<(outs), (ins i8imm:$k), "des\t$k", []>, Requires<[HasDES]>;
532 //===----------------------------------------------------------------------===//
533 // Logic
534 //===----------------------------------------------------------------------===//
535 let Constraints = "$src = $rd", Defs = [SREG] in {
536   // Register-Register logic instructions (which have the
537   // property of commutativity).
538   let isCommutable = 1 in {
539     def ANDRdRr : FRdRr<0b0010, 0b00, (outs GPR8:$rd),
540                         (ins GPR8:$src, GPR8:$rr), "and\t$rd, $rr",
541                         [(set i8:$rd, (and i8:$src, i8:$rr)), (implicit SREG)]>;
543     // ANDW Rd+1:Rd, Rr+1:Rr
544     //
545     // Expands to:
546     // and Rd,   Rr
547     // and Rd+1, Rr+1
548     def ANDWRdRr : Pseudo<(outs DREGS:$rd), (ins DREGS:$src, DREGS:$rr),
549                           "andw\t$rd, $rr",
550                           [(set i16:$rd, (and i16:$src, i16:$rr)),
551                            (implicit SREG)]>;
553     def ORRdRr : FRdRr<0b0010, 0b10, (outs GPR8:$rd), (ins GPR8:$src, GPR8:$rr),
554                        "or\t$rd, $rr",
555                        [(set i8:$rd, (or i8:$src, i8:$rr)), (implicit SREG)]>;
557     // ORW Rd+1:Rd, Rr+1:Rr
558     //
559     // Expands to:
560     // or Rd,   Rr
561     // or Rd+1, Rr+1
562     def ORWRdRr : Pseudo<(outs DREGS:$rd), (ins DREGS:$src, DREGS:$rr),
563                          "orw\t$rd, $rr",
564                          [(set i16:$rd, (or i16:$src, i16:$rr)),
565                           (implicit SREG)]>;
567     def EORRdRr : FRdRr<0b0010, 0b01, (outs GPR8:$rd),
568                         (ins GPR8:$src, GPR8:$rr), "eor\t$rd, $rr",
569                         [(set i8:$rd, (xor i8:$src, i8:$rr)), (implicit SREG)]>;
571     // EORW Rd+1:Rd, Rr+1:Rr
572     //
573     // Expands to:
574     // eor Rd,   Rr
575     // eor Rd+1, Rr+1
576     def EORWRdRr : Pseudo<(outs DREGS:$rd), (ins DREGS:$src, DREGS:$rr),
577                           "eorw\t$rd, $rr",
578                           [(set i16:$rd, (xor i16:$src, i16:$rr)),
579                            (implicit SREG)]>;
580   }
582   def ANDIRdK : FRdK<0b0111, (outs LD8:$rd), (ins LD8:$src, imm_ldi8:$k),
583                      "andi\t$rd, $k",
584                      [(set i8:$rd, (and i8:$src, imm:$k)), (implicit SREG)]>;
586   // ANDI Rd+1:Rd, K+1:K
587   //
588   // Expands to:
589   // andi Rd,   K
590   // andi Rd+1, K+1
591   def ANDIWRdK : Pseudo<(outs DLDREGS:$rd), (ins DLDREGS:$src, i16imm:$k),
592                         "andiw\t$rd, $k",
593                         [(set i16:$rd, (and i16:$src, imm:$k)),
594                          (implicit SREG)]>;
596   def ORIRdK : FRdK<0b0110, (outs LD8:$rd), (ins LD8:$src, imm_ldi8:$k),
597                     "ori\t$rd, $k",
598                     [(set i8:$rd, (or i8:$src, imm:$k)), (implicit SREG)]>;
600   // ORIW Rd+1:Rd, K+1,K
601   //
602   // Expands to:
603   // ori Rd,   K
604   // ori Rd+1, K+1
605   def ORIWRdK : Pseudo<(outs DLDREGS:$rd), (ins DLDREGS:$src, i16imm:$rr),
606                        "oriw\t$rd, $rr",
607                        [(set i16:$rd, (or i16:$src, imm:$rr)),
608                         (implicit SREG)]>;
611 //===----------------------------------------------------------------------===//
612 // One's/Two's Complement
613 //===----------------------------------------------------------------------===//
614 let Constraints = "$src = $rd", Defs = [SREG] in {
615   def COMRd : FRd<0b1001, 0b0100000, (outs GPR8:$rd), (ins GPR8:$src),
616                   "com\t$rd", [(set i8:$rd, (not i8:$src)), (implicit SREG)]>;
618   // COMW Rd+1:Rd
619   //
620   // Expands to:
621   // com Rd
622   // com Rd+1
623   def COMWRd : Pseudo<(outs DREGS:$rd), (ins DREGS:$src), "comw\t$rd",
624                       [(set i16:$rd, (not i16:$src)), (implicit SREG)]>;
626   def NEGRd : FRd<0b1001, 0b0100001, (outs GPR8:$rd), (ins GPR8:$src),
627                   "neg\t$rd", [(set i8:$rd, (ineg i8:$src)), (implicit SREG)]>;
629   // NEGW Rd+1:Rd
630   //
631   // Expands to:
632   // neg Rd+1
633   // neg Rd
634   // sbc Rd+1, r1
635   let hasSideEffects=0 in
636   def NEGWRd : Pseudo<(outs DREGS:$rd), (ins DREGS:$src, GPR8:$zero),
637                       "negw\t$rd", []>;
640 // TST Rd
641 // Test for zero of minus.
642 // This operation is identical to a `Rd AND Rd`.
643 def : InstAlias<"tst\t$rd", (ANDRdRr GPR8:$rd, GPR8:$rd)>;
645 // SBR Rd, K
647 // Mnemonic alias to 'ORI Rd, K'. Same bit pattern, same operands,
648 // same everything.
649 def : InstAlias<"sbr\t$rd, $k", (ORIRdK LD8:$rd, imm_ldi8:$k),
650                 /* Disable display, so we don't override ORI */ 0>;
652 //===----------------------------------------------------------------------===//
653 // Jump instructions
654 //===----------------------------------------------------------------------===//
655 let isBarrier = 1, isBranch = 1, isTerminator = 1 in {
656   def RJMPk : FBRk<0, (outs), (ins brtarget_13:$k), "rjmp\t$k", [(br bb:$k)]>;
658   let isIndirectBranch = 1, Uses = [R31R30] in
659   def IJMP : F16<0b1001010000001001, (outs), (ins), "ijmp", []>,
660              Requires<[HasIJMPCALL]>;
662   let isIndirectBranch = 1, Uses = [R31R30] in
663   def EIJMP : F16<0b1001010000011001, (outs), (ins), "eijmp", []>,
664               Requires<[HasEIJMPCALL]>;
666   def JMPk : F32BRk<0b110, (outs), (ins call_target:$k), "jmp\t$k", []>,
667              Requires<[HasJMPCALL]>;
670 //===----------------------------------------------------------------------===//
671 // Call instructions
672 //===----------------------------------------------------------------------===//
673 let isCall = 1 in {
674   // SP is marked as a use to prevent stack-pointer assignments that appear
675   // immediately before calls from potentially appearing dead.
676   let Uses = [SP] in
677   def RCALLk : FBRk<1, (outs), (ins rcalltarget_13:$k), "rcall\t$k",
678                     [(AVRcall imm:$k)]>;
680   // SP is marked as a use to prevent stack-pointer assignments that appear
681   // immediately before calls from potentially appearing dead.
682   let Uses = [SP, R31R30] in
683   def ICALL : F16<0b1001010100001001, (outs), (ins variable_ops), "icall", []>,
684               Requires<[HasIJMPCALL]>;
686   // SP is marked as a use to prevent stack-pointer assignments that appear
687   // immediately before calls from potentially appearing dead.
688   let Uses = [SP, R31R30] in
689   def EICALL : F16<0b1001010100011001, (outs), (ins variable_ops), "eicall",
690                    []>,
691       Requires<[HasEIJMPCALL]>;
693   // SP is marked as a use to prevent stack-pointer assignments that appear
694   // immediately before calls from potentially appearing dead.
695   //
696   // TODO: the imm field can be either 16 or 22 bits in devices with more
697   // than 64k of ROM, fix it once we support the largest devices.
698   let Uses = [SP] in
699   def CALLk : F32BRk<0b111, (outs), (ins call_target:$k), "call\t$k",
700                      [(AVRcall imm:$k)]>,
701               Requires<[HasJMPCALL]>;
704 //===----------------------------------------------------------------------===//
705 // Return instructions.
706 //===----------------------------------------------------------------------===//
707 let isTerminator = 1, isReturn = 1, isBarrier = 1 in {
708   def RET : F16<0b1001010100001000, (outs), (ins), "ret", [(AVRretglue)]>;
710   def RETI : F16<0b1001010100011000, (outs), (ins), "reti", [(AVRretiglue)]>;
713 //===----------------------------------------------------------------------===//
714 // Compare operations.
715 //===----------------------------------------------------------------------===//
716 let Defs = [SREG] in {
717   // CPSE Rd, Rr
718   // Compare Rd and Rr, skipping the next instruction if they are equal.
719   let isBarrier = 1, isBranch = 1, isTerminator = 1 in
720   def CPSE : FRdRr<0b0001, 0b00, (outs), (ins GPR8:$rd, GPR8:$rr),
721                    "cpse\t$rd, $rr", []>;
723   def CPRdRr : FRdRr<0b0001, 0b01, (outs), (ins GPR8:$rd, GPR8:$rr),
724                      "cp\t$rd, $rr",
725                      [(AVRcmp i8:$rd, i8:$rr), (implicit SREG)]>;
727   // CPW Rd+1:Rd, Rr+1:Rr
728   //
729   // Expands to:
730   // cp  Rd,   Rr
731   // cpc Rd+1, Rr+1
732   def CPWRdRr : Pseudo<(outs), (ins DREGS:$src, DREGS:$src2),
733                        "cpw\t$src, $src2",
734                        [(AVRcmp i16:$src, i16:$src2), (implicit SREG)]>;
736   let Uses = [SREG] in
737   def CPCRdRr : FRdRr<0b0000, 0b01, (outs), (ins GPR8:$rd, GPR8:$rr),
738                       "cpc\t$rd, $rr",
739                       [(AVRcmpc i8:$rd, i8:$rr), (implicit SREG)]>;
741   // CPCW Rd+1:Rd. Rr+1:Rr
742   //
743   // Expands to:
744   // cpc Rd,   Rr
745   // cpc Rd+1, Rr+1
746   let Uses = [SREG] in
747   def CPCWRdRr : Pseudo<(outs), (ins DREGS:$src, DREGS:$src2),
748                         "cpcw\t$src, $src2",
749                         [(AVRcmpc i16:$src, i16:$src2), (implicit SREG)]>;
751   // CPI Rd, K
752   // Compares a register with an 8 bit immediate.
753   def CPIRdK : FRdK<0b0011, (outs), (ins LD8:$rd, imm_ldi8:$k), "cpi\t$rd, $k",
754                     [(AVRcmp i8:$rd, imm:$k), (implicit SREG)]>;
757 //===----------------------------------------------------------------------===//
758 // Register conditional skipping/branching operations.
759 //===----------------------------------------------------------------------===//
760 let isBranch = 1, isTerminator = 1 in {
761   // Conditional skipping on GPR register bits, and
762   // conditional skipping on IO register bits.
763   let isBarrier = 1 in {
764     def SBRCRrB : FRdB<0b10, (outs), (ins GPR8:$rd, i8imm:$b), "sbrc\t$rd, $b",
765                        []>;
767     def SBRSRrB : FRdB<0b11, (outs), (ins GPR8:$rd, i8imm:$b), "sbrs\t$rd, $b",
768                        []>;
770     def SBICAb : FIOBIT<0b01, (outs), (ins imm_port5:$addr, i8imm:$b),
771                         "sbic\t$addr, $b", []>;
773     def SBISAb : FIOBIT<0b11, (outs), (ins imm_port5:$addr, i8imm:$b),
774                         "sbis\t$addr, $b", []>;
775   }
777   // Relative branches on status flag bits.
778   let Uses = [SREG] in {
779     // BRBS s, k
780     // Branch if `s` flag in status register is set.
781     def BRBSsk : FSK<0, (outs), (ins i8imm:$s, relbrtarget_7:$k),
782                      "brbs\t$s, $k", []>;
784     // BRBC s, k
785     // Branch if `s` flag in status register is clear.
786     def BRBCsk : FSK<1, (outs), (ins i8imm:$s, relbrtarget_7:$k),
787                      "brbc\t$s, $k", []>;
788   }
791 // BRCS k
792 // Branch if carry flag is set
793 def : InstAlias<"brcs\t$k", (BRBSsk 0, relbrtarget_7 : $k)>;
795 // BRCC k
796 // Branch if carry flag is clear
797 def : InstAlias<"brcc\t$k", (BRBCsk 0, relbrtarget_7 : $k)>;
799 // BRHS k
800 // Branch if half carry flag is set
801 def : InstAlias<"brhs\t$k", (BRBSsk 5, relbrtarget_7 : $k)>;
803 // BRHC k
804 // Branch if half carry flag is clear
805 def : InstAlias<"brhc\t$k", (BRBCsk 5, relbrtarget_7 : $k)>;
807 // BRTS k
808 // Branch if the T flag is set
809 def : InstAlias<"brts\t$k", (BRBSsk 6, relbrtarget_7 : $k)>;
811 // BRTC k
812 // Branch if the T flag is clear
813 def : InstAlias<"brtc\t$k", (BRBCsk 6, relbrtarget_7 : $k)>;
815 // BRVS k
816 // Branch if the overflow flag is set
817 def : InstAlias<"brvs\t$k", (BRBSsk 3, relbrtarget_7 : $k)>;
819 // BRVC k
820 // Branch if the overflow flag is clear
821 def : InstAlias<"brvc\t$k", (BRBCsk 3, relbrtarget_7 : $k)>;
823 // BRIE k
824 // Branch if the global interrupt flag is enabled
825 def : InstAlias<"brie\t$k", (BRBSsk 7, relbrtarget_7 : $k)>;
827 // BRID k
828 // Branch if the global interrupt flag is disabled
829 def : InstAlias<"brid\t$k", (BRBCsk 7, relbrtarget_7 : $k)>;
831 //===----------------------------------------------------------------------===//
832 // PC-relative conditional branches
833 //===----------------------------------------------------------------------===//
834 // Based on status register. We cannot simplify these into instruction aliases
835 // because we also need to be able to specify a pattern to match for ISel.
836 let isBranch = 1, isTerminator = 1, Uses = [SREG] in {
837   def BREQk : FBRsk<0, 0b001, (outs), (ins relbrtarget_7:$k), "breq\t$k",
838                     [(AVRbrcond bb:$k, AVR_COND_EQ)]>;
840   def BRNEk : FBRsk<1, 0b001, (outs), (ins relbrtarget_7:$k), "brne\t$k",
841                     [(AVRbrcond bb:$k, AVR_COND_NE)]>;
843   def BRSHk : FBRsk<1, 0b000, (outs), (ins relbrtarget_7:$k), "brsh\t$k",
844                     [(AVRbrcond bb:$k, AVR_COND_SH)]>;
846   def BRLOk : FBRsk<0, 0b000, (outs), (ins relbrtarget_7:$k), "brlo\t$k",
847                     [(AVRbrcond bb:$k, AVR_COND_LO)]>;
849   def BRMIk : FBRsk<0, 0b010, (outs), (ins relbrtarget_7:$k), "brmi\t$k",
850                     [(AVRbrcond bb:$k, AVR_COND_MI)]>;
852   def BRPLk : FBRsk<1, 0b010, (outs), (ins relbrtarget_7:$k), "brpl\t$k",
853                     [(AVRbrcond bb:$k, AVR_COND_PL)]>;
855   def BRGEk : FBRsk<1, 0b100, (outs), (ins relbrtarget_7:$k), "brge\t$k",
856                     [(AVRbrcond bb:$k, AVR_COND_GE)]>;
858   def BRLTk : FBRsk<0, 0b100, (outs), (ins relbrtarget_7:$k), "brlt\t$k",
859                     [(AVRbrcond bb:$k, AVR_COND_LT)]>;
862 //===----------------------------------------------------------------------===//
863 // Data transfer instructions
864 //===----------------------------------------------------------------------===//
865 // 8 and 16-bit register move instructions.
866 let hasSideEffects = 0 in {
867   def MOVRdRr : FRdRr<0b0010, 0b11, (outs GPR8:$rd), (ins GPR8:$rr),
868                       "mov\t$rd, $rr", []>;
870   def MOVWRdRr : FMOVWRdRr<(outs DREGS:$rd), (ins DREGS:$rr), "movw\t$rd, $rr",
871                            []>,
872                  Requires<[HasMOVW]>;
875 // Load immediate values into registers.
876 let isReMaterializable = 1 in {
877   def LDIRdK : FRdK<0b1110, (outs LD8:$rd), (ins imm_ldi8:$k), "ldi\t$rd, $k",
878                     [(set i8:$rd, imm:$k)]>;
880   // LDIW Rd+1:Rd, K+1:K
881   //
882   // Expands to:
883   // ldi Rd,   K
884   // ldi Rd+1, K+1
885   def LDIWRdK : Pseudo<(outs DLDREGS:$dst), (ins i16imm:$src),
886                        "ldiw\t$dst, $src", [(set i16:$dst, imm:$src)]>;
889 // Load from data space into register.
890 let canFoldAsLoad = 1, isReMaterializable = 1 in {
891   def LDSRdK : F32DM<0b0, (outs GPR8:$rd), (ins imm16:$k), "lds\t$rd, $k",
892                      [(set i8:$rd, (load imm:$k))]>,
893                Requires<[HasSRAM, HasNonTinyEncoding]>;
895   // Load from data space into register, which is only available on AVRTiny.
896   def LDSRdKTiny : FLDSSTSTINY<0b0, (outs LD8:$rd), (ins imm7tiny:$k),
897                                "lds\t$rd, $k", [(set i8:$rd, (load imm:$k))]>,
898                    Requires<[HasSRAM, HasTinyEncoding]>;
900   // LDSW Rd+1:Rd, K+1:K
901   //
902   // Expands to:
903   // lds Rd,  (K+1:K)
904   // lds Rd+1 (K+1:K) + 1
905   def LDSWRdK : Pseudo<(outs DREGS:$dst), (ins i16imm:$src), "ldsw\t$dst, $src",
906                        [(set i16:$dst, (load imm:$src))]>,
907                 Requires<[HasSRAM, HasNonTinyEncoding]>;
910 // Indirect loads.
911 let canFoldAsLoad = 1, isReMaterializable = 1 in {
912   def LDRdPtr : FSTLD<0, 0b00, (outs GPR8:$reg), (ins LDSTPtrReg:$ptrreg),
913                       "ld\t$reg, $ptrreg",
914                       [(set GPR8:$reg, (load i16:$ptrreg))]>,
915                 Requires<[HasSRAM]>;
917   // LDW Rd+1:Rd, P
918   //
919   // Expands to:
920   //   ld  Rd,   P
921   //   ldd Rd+1, P+1
922   // On reduced tiny cores, this instruction expands to:
923   //   ld    Rd,   P+
924   //   ld    Rd+1, P+
925   //   subiw P,    2
926   let Constraints = "@earlyclobber $reg" in def LDWRdPtr
927       : Pseudo<(outs DREGS:$reg), (ins PTRDISPREGS:$ptrreg),
928                 "ldw\t$reg, $ptrreg", [(set i16:$reg, (load i16:$ptrreg))]>,
929       Requires<[HasSRAM]>;
932 // Indirect loads (with postincrement or predecrement).
933 let mayLoad = 1, hasSideEffects = 0,
934     Constraints = "$ptrreg = $base_wb,@earlyclobber $reg" in {
935   def LDRdPtrPi : FSTLD<0, 0b01,
936                         (outs GPR8
937                          : $reg, PTRREGS
938                          : $base_wb),
939                         (ins LDSTPtrReg
940                          : $ptrreg),
941                         "ld\t$reg, $ptrreg+", []>,
942                   Requires<[HasSRAM]>;
944   // LDW Rd+1:Rd, P+
945   // Expands to:
946   // ld Rd,   P+
947   // ld Rd+1, P+
948   def LDWRdPtrPi : Pseudo<(outs DREGS:$reg, PTRREGS:$base_wb),
949                           (ins PTRREGS:$ptrreg), "ldw\t$reg, $ptrreg+", []>,
950                    Requires<[HasSRAM]>;
952   def LDRdPtrPd : FSTLD<0, 0b10, (outs GPR8:$reg, PTRREGS:$base_wb),
953                         (ins LDSTPtrReg:$ptrreg), "ld\t$reg, -$ptrreg", []>,
954                   Requires<[HasSRAM]>;
956   // LDW Rd+1:Rd, -P
957   //
958   // Expands to:
959   // ld Rd+1, -P
960   // ld Rd,   -P
961   def LDWRdPtrPd : Pseudo<(outs DREGS:$reg, PTRREGS:$base_wb),
962                           (ins PTRREGS:$ptrreg), "ldw\t$reg, -$ptrreg", []>,
963                    Requires<[HasSRAM]>;
966 // Load indirect with displacement operations.
967 let canFoldAsLoad = 1, isReMaterializable = 1 in {
968   def LDDRdPtrQ : FSTDLDD<0, (outs GPR8:$reg), (ins memri:$memri),
969                           "ldd\t$reg, $memri",
970                           [(set i8:$reg, (load addr:$memri))]>,
971                   Requires<[HasSRAM, HasNonTinyEncoding]>;
973   // LDDW Rd+1:Rd, P+q
974   //
975   // Expands to:
976   //   ldd Rd,   P+q
977   //   ldd Rd+1, P+q+1
978   // On reduced tiny cores, this instruction expands to:
979   //   subiw P,    -q
980   //   ld    Rd,   P+
981   //   ld    Rd+1, P+
982   //   subiw P,    q+2
983   let Constraints = "@earlyclobber $dst" in
984   def LDDWRdPtrQ : Pseudo<(outs DREGS:$dst), (ins memri:$memri),
985                           "lddw\t$dst, $memri",
986                           [(set i16:$dst, (load addr:$memri))]>,
987                    Requires<[HasSRAM]>;
989   // An identical pseudo instruction to LDDWRdPtrQ, expect restricted to the Y
990   // register and without the @earlyclobber flag.
991   //
992   // Used to work around a bug caused by the register allocator not
993   // being able to handle the expansion of a COPY into an machine instruction
994   // that has an earlyclobber flag. This is because the register allocator will
995   // try expand a copy from a register slot into an earlyclobber instruction.
996   // Instructions that are earlyclobber need to be in a dedicated earlyclobber
997   // slot.
998   //
999   // This pseudo instruction can be used pre-AVR pseudo expansion in order to
1000   // get a frame index load without directly using earlyclobber instructions.
1001   //
1002   // The pseudo expansion pass trivially expands this into LDDWRdPtrQ.
1003   //
1004   // This instruction may be removed once PR13375 is fixed.
1005   let mayLoad = 1, hasSideEffects = 0 in
1006   def LDDWRdYQ : Pseudo<(outs DREGS:$dst), (ins memri:$memri),
1007                         "lddw\t$dst, $memri", []>,
1008                  Requires<[HasSRAM]>;
1011 class AtomicLoad<PatFrag Op, RegisterClass DRC, RegisterClass PTRRC>
1012     : Pseudo<(outs DRC:$rd), (ins PTRRC:$rr), "atomic_op",
1013              [(set DRC:$rd, (Op i16:$rr))]>;
1015 class AtomicStore<PatFrag Op, RegisterClass DRC, RegisterClass PTRRC>
1016     : Pseudo<(outs), (ins PTRRC:$rd, DRC:$rr), "atomic_op",
1017              [(Op DRC:$rr, i16:$rd)]>;
1019 class AtomicLoadOp<PatFrag Op, RegisterClass DRC, RegisterClass PTRRC>
1020     : Pseudo<(outs DRC:$rd), (ins PTRRC:$rr, DRC:$operand), "atomic_op",
1021              [(set DRC:$rd, (Op i16:$rr, DRC:$operand))]>;
1023 // Atomic instructions
1024 // ===================
1026 // 8-bit operations can use any pointer register because
1027 // they are expanded directly into an LD/ST instruction.
1029 // 16-bit operations use 16-bit load/store postincrement instructions,
1030 // which require PTRDISPREGS.
1032 def AtomicLoad8 : AtomicLoad<atomic_load_8, GPR8, PTRREGS>;
1033 def AtomicLoad16 : AtomicLoad<atomic_load_16, DREGS, PTRDISPREGS>;
1035 def AtomicStore8 : AtomicStore<atomic_store_8, GPR8, PTRREGS>;
1036 def AtomicStore16 : AtomicStore<atomic_store_16, DREGS, PTRDISPREGS>;
1038 class AtomicLoadOp8<PatFrag Op> : AtomicLoadOp<Op, GPR8, PTRREGS>;
1039 class AtomicLoadOp16<PatFrag Op> : AtomicLoadOp<Op, DREGS, PTRDISPREGS>;
1041 let usesCustomInserter=1 in {
1042   def AtomicLoadAdd8 : AtomicLoadOp8<atomic_load_add_i8>;
1043   def AtomicLoadAdd16 : AtomicLoadOp16<atomic_load_add_i16>;
1044   def AtomicLoadSub8 : AtomicLoadOp8<atomic_load_sub_i8>;
1045   def AtomicLoadSub16 : AtomicLoadOp16<atomic_load_sub_i16>;
1046   def AtomicLoadAnd8 : AtomicLoadOp8<atomic_load_and_i8>;
1047   def AtomicLoadAnd16 : AtomicLoadOp16<atomic_load_and_i16>;
1048   def AtomicLoadOr8 : AtomicLoadOp8<atomic_load_or_i8>;
1049   def AtomicLoadOr16 : AtomicLoadOp16<atomic_load_or_i16>;
1050   def AtomicLoadXor8 : AtomicLoadOp8<atomic_load_xor_i8>;
1051   def AtomicLoadXor16 : AtomicLoadOp16<atomic_load_xor_i16>;
1054 def AtomicFence
1055     : Pseudo<(outs), (ins), "atomic_fence", [(atomic_fence timm, timm)]>;
1057 // Indirect store from register to data space.
1058 def STSKRr : F32DM<0b1, (outs), (ins imm16:$k, GPR8:$rd), "sts\t$k, $rd",
1059                    [(store i8:$rd, imm:$k)]>,
1060              Requires<[HasSRAM, HasNonTinyEncoding]>;
1062 // Store from register to data space, which is only available on AVRTiny.
1063 def STSKRrTiny : FLDSSTSTINY<0b1, (outs), (ins imm7tiny:$k, LD8:$rd),
1064                              "sts\t$k, $rd", [(store i8:$rd, imm:$k)]>,
1065                  Requires<[HasSRAM, HasTinyEncoding]>;
1067 // STSW K+1:K, Rr+1:Rr
1069 // Expands to:
1070 // sts Rr+1, (K+1:K) + 1
1071 // sts Rr,   (K+1:K)
1072 def STSWKRr : Pseudo<(outs), (ins i16imm:$dst, DREGS:$src),
1073                      "stsw\t$dst, $src", [(store i16:$src, imm:$dst)]>,
1074               Requires<[HasSRAM, HasNonTinyEncoding]>;
1076 // Indirect stores.
1077 // ST P, Rr
1078 // Stores the value of Rr into the location addressed by pointer P.
1079 def STPtrRr : FSTLD<1, 0b00, (outs), (ins LDSTPtrReg:$ptrreg, GPR8:$reg),
1080                     "st\t$ptrreg, $reg", [(store GPR8:$reg, i16:$ptrreg)]>,
1081               Requires<[HasSRAM]>;
1083 // STW P, Rr+1:Rr
1084 // Stores the value of Rr into the location addressed by pointer P.
1086 // Expands to:
1087 //   st P, Rr
1088 //   std P+1, Rr+1
1089 // On reduced tiny cores, this instruction expands to:
1090 //   st    P+, Rr
1091 //   st    P+, Rr+1
1092 //   subiw P,  q+2
1093 def STWPtrRr : Pseudo<(outs), (ins PTRDISPREGS:$ptrreg, DREGS:$reg),
1094                       "stw\t$ptrreg, $reg", [(store i16:$reg, i16:$ptrreg)]>,
1095                Requires<[HasSRAM]>;
1097 // Indirect stores (with postincrement or predecrement).
1098 let Constraints = "$ptrreg = $base_wb,@earlyclobber $base_wb" in {
1100   // ST P+, Rr
1101   // Stores the value of Rr into the location addressed by pointer P.
1102   // Post increments P.
1103   def STPtrPiRr : FSTLD<1, 0b01, (outs LDSTPtrReg:$base_wb),
1104                         (ins LDSTPtrReg:$ptrreg, GPR8:$reg, i8imm:$offs),
1105                         "st\t$ptrreg+, $reg",
1106                         [(set i16:$base_wb, (post_store GPR8:$reg, i16:$ptrreg,
1107                          imm:$offs))]>,
1108                   Requires<[HasSRAM]>;
1110   // STW P+, Rr+1:Rr
1111   // Stores the value of Rr into the location addressed by pointer P.
1112   // Post increments P.
1113   //
1114   // Expands to:
1115   // st P+, Rr
1116   // st P+, Rr+1
1117   def STWPtrPiRr : Pseudo<(outs PTRREGS:$base_wb),
1118                           (ins PTRREGS:$ptrreg, DREGS:$trh, i8imm:$offs),
1119                           "stw\t$ptrreg+, $trh",
1120                           [(set PTRREGS:$base_wb,
1121                            (post_store DREGS:$trh, PTRREGS:$ptrreg,
1122                             imm:$offs))]>,
1123                    Requires<[HasSRAM]>;
1125   // ST -P, Rr
1126   // Stores the value of Rr into the location addressed by pointer P.
1127   // Pre decrements P.
1128   def STPtrPdRr : FSTLD<1, 0b10, (outs LDSTPtrReg:$base_wb),
1129                         (ins LDSTPtrReg:$ptrreg, GPR8:$reg, i8imm:$offs),
1130                         "st\t-$ptrreg, $reg",
1131                         [(set i16: $base_wb,
1132                          (pre_store GPR8:$reg, i16:$ptrreg, imm:$offs))]>,
1133                   Requires<[HasSRAM]>;
1135   // STW -P, Rr+1:Rr
1136   // Stores the value of Rr into the location addressed by pointer P.
1137   // Pre decrements P.
1138   //
1139   // Expands to:
1140   // st -P, Rr+1
1141   // st -P, Rr
1142   def STWPtrPdRr : Pseudo<(outs PTRREGS:$base_wb),
1143                           (ins PTRREGS:$ptrreg, DREGS:$reg, i8imm:$offs),
1144                           "stw\t-$ptrreg, $reg",
1145                           [(set PTRREGS:$base_wb,
1146                            (pre_store i16:$reg, i16:$ptrreg, imm:$offs))]>,
1147                    Requires<[HasSRAM]>;
1150 // Store indirect with displacement operations.
1151 // STD P+q, Rr
1152 // Stores the value of Rr into the location addressed by pointer P with a
1153 // displacement of q. Does not modify P.
1154 def STDPtrQRr : FSTDLDD<1, (outs), (ins memri:$memri, GPR8:$reg),
1155                         "std\t$memri, $reg", [(store i8:$reg, addr:$memri)]>,
1156                 Requires<[HasSRAM, HasNonTinyEncoding]>;
1158 // STDW P+q, Rr+1:Rr
1159 // Stores the value of Rr into the location addressed by pointer P with a
1160 // displacement of q. Does not modify P.
1162 // Expands to:
1163 //   std P+q,   Rr
1164 //   std P+q+1, Rr+1
1165 // On reduced tiny cores, this instruction expands to:
1166 //   subiw P,  -q
1167 //   st    P+, Rr
1168 //   st    P+, Rr+1
1169 //   subiw P,  q+2
1170 def STDWPtrQRr : Pseudo<(outs), (ins memri:$memri, DREGS:$src),
1171                         "stdw\t$memri, $src", [(store i16:$src, addr:$memri)]>,
1172                  Requires<[HasSRAM]>;
1174 // Load program memory operations.
1175 let canFoldAsLoad = 1, isReMaterializable = 1, mayLoad = 1,
1176     hasSideEffects = 0 in {
1177   let Defs = [R0],
1178       Uses = [R31R30] in def LPM
1179       : F16<0b1001010111001000, (outs), (ins), "lpm", []>,
1180       Requires<[HasLPM]>;
1182   // These pseudo instructions are combination of the OUT and LPM instructions.
1183   let Defs = [R0] in {
1184     def LPMBRdZ : Pseudo<(outs GPR8:$dst), (ins ZREG:$z), "lpmb\t$dst, $z", []>,
1185                   Requires<[HasLPM]>;
1187     let Constraints = "@earlyclobber $dst" in
1188     def LPMWRdZ : Pseudo<(outs DREGS:$dst), (ins ZREG:$z), "lpmw\t$dst, $z", []>,
1189                   Requires<[HasLPM]>;
1190   }
1192   def LPMRdZ : FLPMX<0, 0,
1193                      (outs GPR8
1194                       : $rd),
1195                      (ins ZREG
1196                       : $z),
1197                      "lpm\t$rd, $z", []>,
1198                Requires<[HasLPMX]>;
1200   // Load program memory, while postincrementing the Z register.
1201   let Defs = [R31R30] in {
1202     def LPMRdZPi : FLPMX<0, 1,
1203                          (outs GPR8
1204                           : $rd),
1205                          (ins ZREG
1206                           : $z),
1207                          "lpm\t$rd, $z+", []>,
1208                    Requires<[HasLPMX]>;
1210     def LPMWRdZPi : Pseudo<(outs DREGS
1211                             : $dst),
1212                            (ins ZREG
1213                             : $z),
1214                            "lpmw\t$dst, $z+", []>,
1215                     Requires<[HasLPMX]>;
1216   }
1219 // Extended load program memory operations.
1220 let mayLoad = 1, hasSideEffects = 0 in {
1221   let Defs = [R0],
1222       Uses = [R31R30] in def ELPM
1223       : F16<0b1001010111011000, (outs), (ins), "elpm", []>,
1224       Requires<[HasELPM]>;
1226   def ELPMRdZ : FLPMX<1, 0, (outs GPR8:$rd), (ins ZREG:$z),
1227                       "elpm\t$rd, $z", []>,
1228                 Requires<[HasELPMX]>;
1230   let Defs = [R31R30] in {
1231     def ELPMRdZPi : FLPMX<1, 1, (outs GPR8:$rd), (ins ZREG:$z),
1232                           "elpm\t$rd, $z+", []>,
1233                     Requires<[HasELPMX]>;
1234   }
1236   // These pseudo instructions are combination of the OUT and ELPM instructions.
1237   let Defs = [R0] in {
1238     def ELPMBRdZ : Pseudo<(outs GPR8:$dst), (ins ZREG:$z, LD8:$p),
1239                           "elpmb\t$dst, $z, $p", []>,
1240                    Requires<[HasELPM]>;
1242     let Constraints = "@earlyclobber $dst" in
1243     def ELPMWRdZ : Pseudo<(outs DREGS:$dst), (ins ZREG:$z, LD8:$p),
1244                           "elpmw\t$dst, $z, $p", []>,
1245                    Requires<[HasELPM]>;
1246   }
1248   // These pseudos are combination of the OUT and ELPM instructions.
1249   let Defs = [R31R30], hasSideEffects = 1 in {
1250     def ELPMBRdZPi : Pseudo<(outs GPR8:$dst), (ins ZREG:$z, LD8:$p),
1251                             "elpmb\t$dst, $z+, $p", []>,
1252                      Requires<[HasELPMX]>;
1254     def ELPMWRdZPi : Pseudo<(outs DREGS:$dst), (ins ZREG:$z, LD8:$p),
1255                             "elpmw\t$dst, $z+, $p", []>,
1256                      Requires<[HasELPMX]>;
1257   }
1260 // Store program memory operations.
1261 let Uses = [R1, R0] in {
1262   let Uses = [R31R30, R1, R0] in def SPM
1263       : F16<0b1001010111101000, (outs), (ins), "spm", []>,
1264       Requires<[HasSPM]>;
1266   let Defs = [R31R30] in def SPMZPi : F16<0b1001010111111000, (outs),
1267                                           (ins ZREG
1268                                            : $z),
1269                                           "spm $z+", []>,
1270       Requires<[HasSPMX]>;
1273 // Read data from IO location operations.
1274 let canFoldAsLoad = 1, isReMaterializable = 1 in {
1275   def INRdA : FIORdA<(outs GPR8
1276                       : $rd),
1277                      (ins imm_port6
1278                       : $A),
1279                      "in\t$rd, $A", [(set i8
1280                                          : $rd, (load ioaddr8
1281                                                   : $A))]>;
1283   def INWRdA : Pseudo<(outs DREGS
1284                        : $dst),
1285                       (ins imm_port6
1286                        : $src),
1287                       "inw\t$dst, $src", [(set i16
1288                                            : $dst, (load ioaddr16
1289                                                     : $src))]>;
1292 // Write data to IO location operations.
1293 def OUTARr : FIOARr<(outs),
1294                     (ins imm_port6
1295                      : $A, GPR8
1296                      : $rr),
1297                     "out\t$A, $rr", [(store i8
1298                                          : $rr, ioaddr8
1299                                          : $A)]>;
1301 def OUTWARr : Pseudo<(outs),
1302                      (ins imm_port6
1303                       : $dst, DREGS
1304                       : $src),
1305                      "outw\t$dst, $src", [(store i16
1306                                            : $src, ioaddr16
1307                                            : $dst)]>;
1309 // Stack push/pop operations.
1310 let Defs = [SP], Uses = [SP], hasSideEffects = 0 in {
1311   // Stack push operations.
1312   let mayStore = 1 in {
1313     def PUSHRr : FRd<0b1001, 0b0011111, (outs),
1314                      (ins GPR8
1315                       : $rd),
1316                      "push\t$rd", []>,
1317                  Requires<[HasSRAM]>;
1319     def PUSHWRr : Pseudo<(outs),
1320                          (ins DREGS
1321                           : $reg),
1322                          "pushw\t$reg", []>,
1323                   Requires<[HasSRAM]>;
1324   }
1326   // Stack pop operations.
1327   let mayLoad = 1 in {
1328     def POPRd : FRd<0b1001, 0b0001111,
1329                     (outs GPR8
1330                      : $rd),
1331                     (ins), "pop\t$rd", []>,
1332                 Requires<[HasSRAM]>;
1334     def POPWRd : Pseudo<(outs DREGS
1335                          : $reg),
1336                         (ins), "popw\t$reg", []>,
1337                  Requires<[HasSRAM]>;
1338   }
1341 // Read-Write-Modify (RMW) instructions.
1342 def XCHZRd : FZRd<0b100,
1343                   (outs GPR8
1344                    : $rd),
1345                   (ins ZREG
1346                    : $z),
1347                   "xch\t$z, $rd", []>,
1348              Requires<[SupportsRMW]>;
1350 def LASZRd : FZRd<0b101,
1351                   (outs GPR8
1352                    : $rd),
1353                   (ins ZREG
1354                    : $z),
1355                   "las\t$z, $rd", []>,
1356              Requires<[SupportsRMW]>;
1358 def LACZRd : FZRd<0b110,
1359                   (outs GPR8
1360                    : $rd),
1361                   (ins ZREG
1362                    : $z),
1363                   "lac\t$z, $rd", []>,
1364              Requires<[SupportsRMW]>;
1366 def LATZRd : FZRd<0b111,
1367                   (outs GPR8
1368                    : $rd),
1369                   (ins ZREG
1370                    : $z),
1371                   "lat\t$z, $rd", []>,
1372              Requires<[SupportsRMW]>;
1374 //===----------------------------------------------------------------------===//
1375 // Bit and bit-test instructions
1376 //===----------------------------------------------------------------------===//
1378 // Bit shift/rotate operations.
1379 let Constraints = "$src = $rd", Defs = [SREG] in {
1380   // 8-bit LSL is an alias of ADD Rd, Rd
1382   def LSLWRd : Pseudo<(outs DREGS
1383                        : $rd),
1384                       (ins DREGS
1385                        : $src),
1386                       "lslw\t$rd",
1387                       [(set i16
1388                         : $rd, (AVRlsl i16
1389                                 : $src)),
1390                        (implicit SREG)]>;
1392   def LSLWHiRd : Pseudo<(outs DREGS:$rd), (ins DREGS:$src), "lslwhi\t$rd",
1393                         [(set i16:$rd, (AVRlslhi i16:$src)), (implicit SREG)]>;
1395   def LSLWNRd : Pseudo<(outs DLDREGS
1396                         : $rd),
1397                        (ins DREGS
1398                         : $src, imm16
1399                         : $bits),
1400                        "lslwn\t$rd, $bits", [
1401                          (set i16
1402                           : $rd, (AVRlslwn i16
1403                                   : $src, imm
1404                                   : $bits)),
1405                          (implicit SREG)
1406                        ]>;
1408   def LSLBNRd : Pseudo<(outs LD8
1409                         : $rd),
1410                        (ins GPR8
1411                         : $src, imm_ldi8
1412                         : $bits),
1413                        "lslbn\t$rd, $bits", [
1414                          (set i8
1415                           : $rd, (AVRlslbn i8
1416                                   : $src, imm
1417                                   : $bits)),
1418                          (implicit SREG)
1419                        ]>;
1421   def LSRRd
1422       : FRd<0b1001, 0b0100110,
1423             (outs GPR8
1424              : $rd),
1425             (ins GPR8
1426              : $src),
1427             "lsr\t$rd", [(set i8
1428                           : $rd, (AVRlsr i8
1429                                   : $src)),
1430                          (implicit SREG)]>;
1432   def LSRWRd : Pseudo<(outs DREGS
1433                        : $rd),
1434                       (ins DREGS
1435                        : $src),
1436                       "lsrw\t$rd",
1437                       [(set i16
1438                         : $rd, (AVRlsr i16
1439                                 : $src)),
1440                        (implicit SREG)]>;
1442   def LSRWLoRd : Pseudo<(outs DREGS:$rd), (ins DREGS:$src), "lsrwlo\t$rd",
1443                         [(set i16:$rd, (AVRlsrlo i16:$src)), (implicit SREG)]>;
1445   def LSRWNRd : Pseudo<(outs DLDREGS
1446                         : $rd),
1447                        (ins DREGS
1448                         : $src, imm16
1449                         : $bits),
1450                        "lsrwn\t$rd, $bits", [
1451                          (set i16
1452                           : $rd, (AVRlsrwn i16
1453                                   : $src, imm
1454                                   : $bits)),
1455                          (implicit SREG)
1456                        ]>;
1458   def LSRBNRd : Pseudo<(outs LD8
1459                         : $rd),
1460                        (ins GPR8
1461                         : $src, imm_ldi8
1462                         : $bits),
1463                        "lsrbn\t$rd, $bits", [
1464                          (set i8
1465                           : $rd, (AVRlsrbn i8
1466                                   : $src, imm
1467                                   : $bits)),
1468                          (implicit SREG)
1469                        ]>;
1471   def ASRRd
1472       : FRd<0b1001, 0b0100101,
1473             (outs GPR8
1474              : $rd),
1475             (ins GPR8
1476              : $src),
1477             "asr\t$rd", [(set i8
1478                           : $rd, (AVRasr i8
1479                                   : $src)),
1480                          (implicit SREG)]>;
1482   def ASRWNRd : Pseudo<(outs DREGS
1483                         : $rd),
1484                        (ins DREGS
1485                         : $src, imm16
1486                         : $bits),
1487                        "asrwn\t$rd, $bits", [
1488                          (set i16
1489                           : $rd, (AVRasrwn i16
1490                                   : $src, imm
1491                                   : $bits)),
1492                          (implicit SREG)
1493                        ]>;
1495   def ASRBNRd : Pseudo<(outs LD8
1496                         : $rd),
1497                        (ins GPR8
1498                         : $src, imm_ldi8
1499                         : $bits),
1500                        "asrbn\t$rd, $bits", [
1501                          (set i8
1502                           : $rd, (AVRasrbn i8
1503                                   : $src, imm
1504                                   : $bits)),
1505                          (implicit SREG)
1506                        ]>;
1508   def ASRWRd : Pseudo<(outs DREGS
1509                        : $rd),
1510                       (ins DREGS
1511                        : $src),
1512                       "asrw\t$rd",
1513                       [(set i16
1514                         : $rd, (AVRasr i16
1515                                 : $src)),
1516                        (implicit SREG)]>;
1518   def ASRWLoRd : Pseudo<(outs DREGS:$rd), (ins DREGS:$src), "asrwlo\t$rd",
1519                         [(set i16:$rd, (AVRasrlo i16:$src)), (implicit SREG)]>;
1520   let Uses = [R1] in
1521   def ROLBRdR1 : Pseudo<(outs GPR8:$rd),
1522                         (ins GPR8:$src),
1523                         "rolb\t$rd",
1524                         [(set i8:$rd, (AVRrol i8:$src)),
1525                         (implicit SREG)]>,
1526                  Requires<[HasNonTinyEncoding]>;
1528   let Uses = [R17] in
1529   def ROLBRdR17 : Pseudo<(outs GPR8:$rd),
1530                          (ins GPR8:$src),
1531                          "rolb\t$rd",
1532                          [(set i8:$rd, (AVRrol i8:$src)),
1533                          (implicit SREG)]>,
1534                   Requires<[HasTinyEncoding]>;
1536   def RORBRd : Pseudo<(outs GPR8
1537                        : $rd),
1538                       (ins GPR8
1539                        : $src),
1540                       "rorb\t$rd",
1541                       [(set i8
1542                         : $rd, (AVRror i8
1543                                 : $src)),
1544                        (implicit SREG)]>;
1546   // Bit rotate operations.
1547   let Uses = [SREG] in {
1549     def ROLWRd
1550         : Pseudo<(outs DREGS
1551                   : $rd),
1552                  (ins DREGS
1553                   : $src),
1554                  "rolw\t$rd",
1555                  [(set i16
1556                    : $rd, (AVRrol i16
1557                            : $src)),
1558                   (implicit SREG)]>;
1560     def RORRd : FRd<0b1001, 0b0100111,
1561                     (outs GPR8
1562                      : $rd),
1563                     (ins GPR8
1564                      : $src),
1565                     "ror\t$rd", []>;
1567     def RORWRd
1568         : Pseudo<(outs DREGS
1569                   : $rd),
1570                  (ins DREGS
1571                   : $src),
1572                  "rorw\t$rd",
1573                  [(set i16
1574                    : $rd, (AVRror i16
1575                            : $src)),
1576                   (implicit SREG)]>;
1577   }
1580 // SWAP Rd
1581 // Swaps the high and low nibbles in a register.
1582 let Constraints =
1583     "$src = $rd" in def SWAPRd : FRd<0b1001, 0b0100010,
1584                                      (outs GPR8
1585                                       : $rd),
1586                                      (ins GPR8
1587                                       : $src),
1588                                      "swap\t$rd", [(set i8
1589                                                     : $rd, (AVRSwap i8
1590                                                             : $src))]>;
1592 // IO register bit set/clear operations.
1593 //: TODO: add patterns when popcount(imm)==2 to be expanded with 2 sbi/cbi
1594 // instead of in+ori+out which requires one more instr.
1595 def SBIAb : FIOBIT<0b10, (outs),
1596                    (ins imm_port5
1597                     : $addr, i8imm
1598                     : $b),
1599                    "sbi\t$addr, $b", [(store(or(i8(load lowioaddr8
1600                                                      : $addr)),
1601                                                iobitpos8
1602                                                : $b),
1603                                          lowioaddr8
1604                                          : $addr)]>;
1606 def CBIAb : FIOBIT<0b00, (outs),
1607                    (ins imm_port5
1608                     : $addr, i8imm
1609                     : $b),
1610                    "cbi\t$addr, $b", [(store(and(i8(load lowioaddr8
1611                                                       : $addr)),
1612                                                iobitposn8
1613                                                : $b),
1614                                          lowioaddr8
1615                                          : $addr)]>;
1617 // Status register bit load/store operations.
1618 let Defs = [SREG] in def BST : FRdB<0b01, (outs),
1619                                     (ins GPR8
1620                                      : $rd, i8imm
1621                                      : $b),
1622                                     "bst\t$rd, $b", []>;
1624 let Constraints = "$src = $rd",
1625     Uses = [SREG] in def BLD : FRdB<0b00,
1626                                     (outs GPR8
1627                                      : $rd),
1628                                     (ins GPR8
1629                                      : $src, i8imm
1630                                      : $b),
1631                                     "bld\t$rd, $b", []>;
1633 def CBR : InstAlias<"cbr\t$rd, $k", (ANDIRdK LD8 : $rd, imm_com8 : $k), 0>;
1635 // CLR Rd
1636 // Alias for EOR Rd, Rd
1637 // -------------
1638 // Clears all bits in a register.
1639 def CLR : InstAlias<"clr\t$rd", (EORRdRr GPR8 : $rd, GPR8 : $rd)>;
1641 // LSL Rd
1642 // Alias for ADD Rd, Rd
1643 // --------------
1644 // Logical shift left one bit.
1645 def LSL : InstAlias<"lsl\t$rd", (ADDRdRr GPR8 : $rd, GPR8 : $rd)>;
1647 def ROL : InstAlias<"rol\t$rd", (ADCRdRr GPR8 : $rd, GPR8 : $rd)>;
1649 // SER Rd
1650 // Alias for LDI Rd, 0xff
1651 // ---------
1652 // Sets all bits in a register.
1653 def : InstAlias<"ser\t$rd", (LDIRdK LD8 : $rd, 0xff), 0>;
1655 let hasSideEffects=1 in {
1656   let Defs = [SREG] in def BSETs : FS<0,
1657                                       (outs),
1658                                       (ins i8imm:$s),
1659                                       "bset\t$s", []>;
1661   let Defs = [SREG] in def BCLRs : FS<1,
1662                                       (outs),
1663                                       (ins i8imm:$s),
1664                                       "bclr\t$s", []>;
1667 // Set/clear aliases for the carry (C) status flag (bit 0).
1668 def : InstAlias<"sec", (BSETs 0)>;
1669 def : InstAlias<"clc", (BCLRs 0)>;
1671 // Set/clear aliases for the zero (Z) status flag (bit 1).
1672 def : InstAlias<"sez", (BSETs 1)>;
1673 def : InstAlias<"clz", (BCLRs 1)>;
1675 // Set/clear aliases for the negative (N) status flag (bit 2).
1676 def : InstAlias<"sen", (BSETs 2)>;
1677 def : InstAlias<"cln", (BCLRs 2)>;
1679 // Set/clear aliases for the overflow (V) status flag (bit 3).
1680 def : InstAlias<"sev", (BSETs 3)>;
1681 def : InstAlias<"clv", (BCLRs 3)>;
1683 // Set/clear aliases for the signed (S) status flag (bit 4).
1684 def : InstAlias<"ses", (BSETs 4)>;
1685 def : InstAlias<"cls", (BCLRs 4)>;
1687 // Set/clear aliases for the half-carry (H) status flag (bit 5).
1688 def : InstAlias<"seh", (BSETs 5)>;
1689 def : InstAlias<"clh", (BCLRs 5)>;
1691 // Set/clear aliases for the T status flag (bit 6).
1692 def : InstAlias<"set", (BSETs 6)>;
1693 def : InstAlias<"clt", (BCLRs 6)>;
1695 // Set/clear aliases for the interrupt (I) status flag (bit 7).
1696 def : InstAlias<"sei", (BSETs 7)>;
1697 def : InstAlias<"cli", (BCLRs 7)>;
1699 //===----------------------------------------------------------------------===//
1700 // Special/Control instructions
1701 //===----------------------------------------------------------------------===//
1703 // BREAK
1704 // Breakpoint instruction
1705 // ---------
1706 // <|1001|0101|1001|1000>
1707 def BREAK : F16<0b1001010110011000, (outs), (ins), "break", []>,
1708             Requires<[HasBREAK]>;
1710 // NOP
1711 // No-operation instruction
1712 // ---------
1713 // <|0000|0000|0000|0000>
1714 def NOP : F16<0b0000000000000000, (outs), (ins), "nop", []>;
1716 // SLEEP
1717 // Sleep instruction
1718 // ---------
1719 // <|1001|0101|1000|1000>
1720 def SLEEP : F16<0b1001010110001000, (outs), (ins), "sleep", []>;
1722 // WDR
1723 // Watchdog reset
1724 // ---------
1725 // <|1001|0101|1010|1000>
1726 def WDR : F16<0b1001010110101000, (outs), (ins), "wdr", []>;
1728 //===----------------------------------------------------------------------===//
1729 // Pseudo instructions for later expansion
1730 //===----------------------------------------------------------------------===//
1732 //: TODO: Optimize this for wider types AND optimize the following code
1733 //       compile int foo(char a, char b, char c, char d) {return d+b;}
1734 //       looks like a missed sext_inreg opportunity.
1735 def SEXT
1736     : ExtensionPseudo<(outs DREGS
1737                        : $dst),
1738                       (ins GPR8
1739                        : $src),
1740                       "sext\t$dst, $src",
1741                       [(set i16
1742                         : $dst, (sext i8
1743                                  : $src)),
1744                        (implicit SREG)]>;
1746 def ZEXT
1747     : ExtensionPseudo<(outs DREGS
1748                        : $dst),
1749                       (ins GPR8
1750                        : $src),
1751                       "zext\t$dst, $src",
1752                       [(set i16
1753                         : $dst, (zext i8
1754                                  : $src)),
1755                        (implicit SREG)]>;
1757 // This pseudo gets expanded into a movw+adiw thus it clobbers SREG.
1758 let Defs = [SREG],
1759     hasSideEffects = 0 in def FRMIDX : Pseudo<(outs DLDREGS
1760                                                : $dst),
1761                                               (ins DLDREGS
1762                                                : $src, i16imm
1763                                                : $src2),
1764                                               "frmidx\t$dst, $src, $src2", []>;
1766 // This pseudo is either converted to a regular store or a push which clobbers
1767 // SP.
1768 def STDSPQRr : StorePseudo<(outs),
1769                            (ins memspi
1770                             : $dst, GPR8
1771                             : $src),
1772                            "stdstk\t$dst, $src", [(store i8
1773                                                    : $src, addr
1774                                                    : $dst)]>;
1776 // This pseudo is either converted to a regular store or a push which clobbers
1777 // SP.
1778 def STDWSPQRr : StorePseudo<(outs),
1779                             (ins memspi
1780                              : $dst, DREGS
1781                              : $src),
1782                             "stdwstk\t$dst, $src", [(store i16
1783                                                      : $src, addr
1784                                                      : $dst)]>;
1786 // SP read/write pseudos.
1787 let hasSideEffects = 0 in {
1788   let Uses = [SP] in def SPREAD : Pseudo<(outs DREGS
1789                                           : $dst),
1790                                          (ins GPRSP
1791                                           : $src),
1792                                          "spread\t$dst, $src", []>;
1794   let Defs = [SP] in def SPWRITE : Pseudo<(outs GPRSP
1795                                            : $dst),
1796                                           (ins DREGS
1797                                            : $src),
1798                                           "spwrite\t$dst, $src", []>;
1801 def Select8 : SelectPseudo<(outs GPR8
1802                             : $dst),
1803                            (ins GPR8
1804                             : $src, GPR8
1805                             : $src2, i8imm
1806                             : $cc),
1807                            "# Select8 PSEUDO", [(set i8
1808                                                  : $dst, (AVRselectcc i8
1809                                                           : $src, i8
1810                                                           : $src2, imm
1811                                                           : $cc))]>;
1813 def Select16 : SelectPseudo<(outs DREGS
1814                              : $dst),
1815                             (ins DREGS
1816                              : $src, DREGS
1817                              : $src2, i8imm
1818                              : $cc),
1819                             "# Select16 PSEUDO", [(set i16
1820                                                    : $dst, (AVRselectcc i16
1821                                                             : $src, i16
1822                                                             : $src2, imm
1823                                                             : $cc))]>;
1825 def Lsl8 : ShiftPseudo<(outs GPR8
1826                         : $dst),
1827                        (ins GPR8
1828                         : $src, GPR8
1829                         : $cnt),
1830                        "# Lsl8 PSEUDO", [(set i8
1831                                           : $dst, (AVRlslLoop i8
1832                                                    : $src, i8
1833                                                    : $cnt))]>;
1835 def Lsl16 : ShiftPseudo<(outs DREGS
1836                          : $dst),
1837                         (ins DREGS
1838                          : $src, GPR8
1839                          : $cnt),
1840                         "# Lsl16 PSEUDO", [(set i16
1841                                             : $dst, (AVRlslLoop i16
1842                                                      : $src, i8
1843                                                      : $cnt))]>;
1845 def Lsl32 : ShiftPseudo<(outs DREGS:$dstlo, DREGS:$dsthi),
1846                         (ins DREGS:$srclo, DREGS:$srchi, i8imm:$cnt),
1847                         "# Lsl32 PSEUDO",
1848                         [(set i16:$dstlo, i16:$dsthi, (AVRlslw i16:$srclo, i16:$srchi, i8:$cnt))]>;
1850 def Lsr8 : ShiftPseudo<(outs GPR8
1851                         : $dst),
1852                        (ins GPR8
1853                         : $src, GPR8
1854                         : $cnt),
1855                        "# Lsr8 PSEUDO", [(set i8
1856                                           : $dst, (AVRlsrLoop i8
1857                                                    : $src, i8
1858                                                    : $cnt))]>;
1860 def Lsr16 : ShiftPseudo<(outs DREGS
1861                          : $dst),
1862                         (ins DREGS
1863                          : $src, GPR8
1864                          : $cnt),
1865                         "# Lsr16 PSEUDO", [(set i16
1866                                             : $dst, (AVRlsrLoop i16
1867                                                      : $src, i8
1868                                                      : $cnt))]>;
1870 def Lsr32 : ShiftPseudo<(outs DREGS:$dstlo, DREGS:$dsthi),
1871                         (ins DREGS:$srclo, DREGS:$srchi, i8imm:$cnt),
1872                         "# Lsr32 PSEUDO",
1873                         [(set i16:$dstlo, i16:$dsthi, (AVRlsrw i16:$srclo, i16:$srchi, i8:$cnt))]>;
1875 def Rol8 : ShiftPseudo<(outs GPR8
1876                         : $dst),
1877                        (ins GPR8
1878                         : $src, GPR8
1879                         : $cnt),
1880                        "# Rol8 PSEUDO", [(set i8
1881                                           : $dst, (AVRrolLoop i8
1882                                                    : $src, i8
1883                                                    : $cnt))]>;
1885 def Rol16 : ShiftPseudo<(outs DREGS
1886                          : $dst),
1887                         (ins DREGS
1888                          : $src, GPR8
1889                          : $cnt),
1890                         "# Rol16 PSEUDO", [(set i16
1891                                             : $dst, (AVRrolLoop i16
1892                                                      : $src, i8
1893                                                      : $cnt))]>;
1895 def Ror8 : ShiftPseudo<(outs GPR8
1896                         : $dst),
1897                        (ins GPR8
1898                         : $src, GPR8
1899                         : $cnt),
1900                        "# Ror8 PSEUDO", [(set i8
1901                                           : $dst, (AVRrorLoop i8
1902                                                    : $src, i8
1903                                                    : $cnt))]>;
1905 def Ror16 : ShiftPseudo<(outs DREGS
1906                          : $dst),
1907                         (ins DREGS
1908                          : $src, GPR8
1909                          : $cnt),
1910                         "# Ror16 PSEUDO", [(set i16
1911                                             : $dst, (AVRrorLoop i16
1912                                                      : $src, i8
1913                                                      : $cnt))]>;
1915 def Asr8 : ShiftPseudo<(outs GPR8
1916                         : $dst),
1917                        (ins GPR8
1918                         : $src, GPR8
1919                         : $cnt),
1920                        "# Asr8 PSEUDO", [(set i8
1921                                           : $dst, (AVRasrLoop i8
1922                                                    : $src, i8
1923                                                    : $cnt))]>;
1925 def Asr16 : ShiftPseudo<(outs DREGS
1926                          : $dst),
1927                         (ins DREGS
1928                          : $src, GPR8
1929                          : $cnt),
1930                         "# Asr16 PSEUDO", [(set i16
1931                                             : $dst, (AVRasrLoop i16
1932                                                      : $src, i8
1933                                                      : $cnt))]>;
1935 def Asr32 : ShiftPseudo<(outs DREGS:$dstlo, DREGS:$dsthi),
1936                         (ins DREGS:$srclo, DREGS:$srchi, i8imm:$cnt),
1937                         "# Asr32 PSEUDO",
1938                         [(set i16:$dstlo, i16:$dsthi, (AVRasrw i16:$srclo, i16:$srchi, i8:$cnt))]>;
1940 // lowered to a copy from the zero register.
1941 let usesCustomInserter=1 in
1942 def CopyZero : Pseudo<(outs GPR8:$rd), (ins), "clrz\t$rd", [(set i8:$rd, 0)]>;
1944 //===----------------------------------------------------------------------===//
1945 // Non-Instruction Patterns
1946 //===----------------------------------------------------------------------===//
1948 //: TODO: look in x86InstrCompiler.td for odd encoding trick related to
1949 // add x, 128 -> sub x, -128. Clang is emitting an eor for this (ldi+eor)
1951 // the add instruction always writes the carry flag
1952 def : Pat<(addc i8 : $src, i8 : $src2), (ADDRdRr i8 : $src, i8 : $src2)>;
1953 def : Pat<(addc DREGS
1954            : $src, DREGS
1955            : $src2),
1956           (ADDWRdRr DREGS
1957            : $src, DREGS
1958            : $src2)>;
1960 // all sub instruction variants always writes the carry flag
1961 def : Pat<(subc i8 : $src, i8 : $src2), (SUBRdRr i8 : $src, i8 : $src2)>;
1962 def : Pat<(subc i16 : $src, i16 : $src2), (SUBWRdRr i16 : $src, i16 : $src2)>;
1963 def : Pat<(subc i8 : $src, imm : $src2), (SUBIRdK i8 : $src, imm : $src2)>;
1964 def : Pat<(subc i16 : $src, imm : $src2), (SUBIWRdK i16 : $src, imm : $src2)>;
1966 // These patterns convert add (x, -imm) to sub (x, imm) since we dont have
1967 // any add with imm instructions. Also take care of the adiw/sbiw instructions.
1968 def : Pat<(add i16
1969            : $src1, imm0_63_neg
1970            : $src2),
1971           (SBIWRdK i16
1972            : $src1, (imm0_63_neg
1973                      : $src2))>,
1974           Requires<[HasADDSUBIW]>;
1975 def : Pat<(add i16
1976            : $src1, imm
1977            : $src2),
1978           (SUBIWRdK i16
1979            : $src1, (imm16_neg_XFORM imm
1980                      : $src2))>;
1981 def : Pat<(addc i16
1982            : $src1, imm
1983            : $src2),
1984           (SUBIWRdK i16
1985            : $src1, (imm16_neg_XFORM imm
1986                      : $src2))>;
1988 def : Pat<(add i8
1989            : $src1, imm
1990            : $src2),
1991           (SUBIRdK i8
1992            : $src1, (imm8_neg_XFORM imm
1993                      : $src2))>;
1994 def : Pat<(addc i8
1995            : $src1, imm
1996            : $src2),
1997           (SUBIRdK i8
1998            : $src1, (imm8_neg_XFORM imm
1999                      : $src2))>;
2000 def : Pat<(adde i8
2001            : $src1, imm
2002            : $src2),
2003           (SBCIRdK i8
2004            : $src1, (imm8_neg_XFORM imm
2005                      : $src2))>;
2007 // Emit NEGWRd with an extra zero register operand.
2008 def : Pat<(ineg i16:$src),
2009           (NEGWRd i16:$src, (CopyZero))>;
2011 // Calls.
2012 let Predicates = [HasJMPCALL] in {
2013   def : Pat<(AVRcall(i16 tglobaladdr:$dst)), (CALLk tglobaladdr:$dst)>;
2014   def : Pat<(AVRcall(i16 texternalsym:$dst)), (CALLk texternalsym:$dst)>;
2016 def : Pat<(AVRcall(i16 tglobaladdr:$dst)), (RCALLk tglobaladdr:$dst)>;
2017 def : Pat<(AVRcall(i16 texternalsym:$dst)), (RCALLk texternalsym:$dst)>;
2019 // `anyext`
2020 def : Pat<(i16(anyext i8
2021                : $src)),
2022           (INSERT_SUBREG(i16(IMPLICIT_DEF)), i8
2023            : $src, sub_lo)>;
2025 // `trunc`
2026 def : Pat<(i8(trunc i16 : $src)), (EXTRACT_SUBREG i16 : $src, sub_lo)>;
2028 // sext_inreg
2029 def : Pat<(sext_inreg i16
2030            : $src, i8),
2031           (SEXT(i8(EXTRACT_SUBREG i16
2032                    : $src, sub_lo)))>;
2034 // GlobalAddress
2035 def : Pat<(i16(AVRWrapper tglobaladdr : $dst)), (LDIWRdK tglobaladdr : $dst)>;
2036 def : Pat<(add i16
2037            : $src, (AVRWrapper tglobaladdr
2038                     : $src2)),
2039           (SUBIWRdK i16
2040            : $src, tglobaladdr
2041            : $src2)>;
2042 def : Pat<(i8(load(AVRWrapper tglobaladdr:$dst))),
2043           (LDSRdK tglobaladdr:$dst)>,
2044           Requires<[HasSRAM, HasNonTinyEncoding]>;
2045 def : Pat<(i8(load(AVRWrapper tglobaladdr:$dst))),
2046           (LDSRdKTiny tglobaladdr:$dst)>,
2047           Requires<[HasSRAM, HasTinyEncoding]>;
2048 def : Pat<(i16(load(AVRWrapper tglobaladdr:$dst))),
2049           (LDSWRdK tglobaladdr:$dst)>,
2050           Requires<[HasSRAM, HasNonTinyEncoding]>;
2051 def : Pat<(store i8:$src, (i16(AVRWrapper tglobaladdr:$dst))),
2052           (STSKRr tglobaladdr:$dst, i8:$src)>,
2053           Requires<[HasSRAM, HasNonTinyEncoding]>;
2054 def : Pat<(store i8:$src, (i16(AVRWrapper tglobaladdr:$dst))),
2055           (STSKRrTiny tglobaladdr:$dst, i8:$src)>,
2056           Requires<[HasSRAM, HasTinyEncoding]>;
2057 def : Pat<(store i16:$src, (i16(AVRWrapper tglobaladdr:$dst))),
2058           (STSWKRr tglobaladdr:$dst, i16:$src)>,
2059           Requires<[HasSRAM, HasNonTinyEncoding]>;
2061 // BlockAddress
2062 def : Pat<(i16(AVRWrapper tblockaddress
2063                : $dst)),
2064           (LDIWRdK tblockaddress
2065            : $dst)>;
2067 def : Pat<(i8(trunc(AVRlsrwn DLDREGS
2068                     : $src, (i16 8)))),
2069           (EXTRACT_SUBREG DREGS
2070            : $src, sub_hi)>;
2072 // :FIXME: DAGCombiner produces an shl node after legalization from these seq:
2073 // BR_JT -> (mul x, 2) -> (shl x, 1)
2074 def : Pat<(shl i16 : $src1, (i8 1)), (LSLWRd i16 : $src1)>;
2076 // Lowering of 'tst' node to 'TST' instruction.
2077 // TST is an alias of AND Rd, Rd.
2078 def : Pat<(AVRtst i8 : $rd), (ANDRdRr GPR8 : $rd, GPR8 : $rd)>;
2080 // Lowering of 'lsl' node to 'LSL' instruction.
2081 // LSL is an alias of 'ADD Rd, Rd'
2082 def : Pat<(AVRlsl i8 : $rd), (ADDRdRr GPR8 : $rd, GPR8 : $rd)>;