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.
10//
11//===----------------------------------------------------------------------===//
12
13include "AVRInstrFormats.td"
14
15//===----------------------------------------------------------------------===//
16// AVR Type Profiles
17//===----------------------------------------------------------------------===//
18
19def SDT_AVRCallSeqStart : SDCallSeqStart<[SDTCisVT<0, i16>, SDTCisVT<1, i16>]>;
20def SDT_AVRCallSeqEnd : SDCallSeqEnd<[SDTCisVT<0, i16>, SDTCisVT<1, i16>]>;
21def SDT_AVRCall : SDTypeProfile<0, -1, [SDTCisVT<0, iPTR>]>;
22def SDT_AVRWrapper : SDTypeProfile<1, 1, [SDTCisSameAs<0, 1>, SDTCisPtrTy<0>]>;
23def SDT_AVRBrcond
24    : SDTypeProfile<0, 2, [SDTCisVT<0, OtherVT>, SDTCisVT<1, i8>]>;
25def SDT_AVRCmp : SDTypeProfile<0, 2, [SDTCisSameAs<0, 1>]>;
26def SDT_AVRTst : SDTypeProfile<0, 1, [SDTCisInt<0>]>;
27def SDT_AVRSelectCC
28    : SDTypeProfile<1, 3,
29                    [SDTCisSameAs<0, 1>, SDTCisSameAs<1, 2>, SDTCisVT<3, i8>]>;
30
31//===----------------------------------------------------------------------===//
32// AVR Specific Node Definitions
33//===----------------------------------------------------------------------===//
34
35def AVRretflag : SDNode<"AVRISD::RET_FLAG", SDTNone,
36                        [SDNPHasChain, SDNPOptInGlue, SDNPVariadic]>;
37def AVRretiflag : SDNode<"AVRISD::RETI_FLAG", SDTNone,
38                         [SDNPHasChain, SDNPOptInGlue, SDNPVariadic]>;
39
40def AVRcallseq_start : SDNode<"ISD::CALLSEQ_START", SDT_AVRCallSeqStart,
41                              [SDNPHasChain, SDNPOutGlue]>;
42def AVRcallseq_end : SDNode<"ISD::CALLSEQ_END", SDT_AVRCallSeqEnd,
43                            [SDNPHasChain, SDNPOptInGlue, SDNPOutGlue]>;
44
45def AVRcall : SDNode<"AVRISD::CALL", SDT_AVRCall,
46                     [SDNPHasChain, SDNPOutGlue, SDNPOptInGlue, SDNPVariadic]>;
47
48def AVRWrapper : SDNode<"AVRISD::WRAPPER", SDT_AVRWrapper>;
49
50def AVRbrcond
51    : SDNode<"AVRISD::BRCOND", SDT_AVRBrcond, [SDNPHasChain, SDNPInGlue]>;
52def AVRcmp : SDNode<"AVRISD::CMP", SDT_AVRCmp, [SDNPOutGlue]>;
53def AVRcmpc : SDNode<"AVRISD::CMPC", SDT_AVRCmp, [SDNPInGlue, SDNPOutGlue]>;
54def AVRtst : SDNode<"AVRISD::TST", SDT_AVRTst, [SDNPOutGlue]>;
55def AVRselectcc : SDNode<"AVRISD::SELECT_CC", SDT_AVRSelectCC, [SDNPInGlue]>;
56
57// Shift nodes.
58def AVRlsl : SDNode<"AVRISD::LSL", SDTIntUnaryOp>;
59def AVRlsr : SDNode<"AVRISD::LSR", SDTIntUnaryOp>;
60def AVRrol : SDNode<"AVRISD::ROL", SDTIntUnaryOp>;
61def AVRror : SDNode<"AVRISD::ROR", SDTIntUnaryOp>;
62def AVRasr : SDNode<"AVRISD::ASR", SDTIntUnaryOp>;
63def AVRlslhi : SDNode<"AVRISD::LSLHI", SDTIntUnaryOp>;
64def AVRlsrlo : SDNode<"AVRISD::LSRLO", SDTIntUnaryOp>;
65def AVRasrlo : SDNode<"AVRISD::ASRLO", SDTIntUnaryOp>;
66def AVRlslbn : SDNode<"AVRISD::LSLBN", SDTIntBinOp>;
67def AVRlsrbn : SDNode<"AVRISD::LSRBN", SDTIntBinOp>;
68def AVRasrbn : SDNode<"AVRISD::ASRBN", SDTIntBinOp>;
69def AVRlslwn : SDNode<"AVRISD::LSLWN", SDTIntBinOp>;
70def AVRlsrwn : SDNode<"AVRISD::LSRWN", SDTIntBinOp>;
71def AVRasrwn : SDNode<"AVRISD::ASRWN", SDTIntBinOp>;
72def AVRlslw : SDNode<"AVRISD::LSLW", SDTIntShiftDOp>;
73def AVRlsrw : SDNode<"AVRISD::LSRW", SDTIntShiftDOp>;
74def AVRasrw : SDNode<"AVRISD::ASRW", SDTIntShiftDOp>;
75
76// Pseudo shift nodes for non-constant shift amounts.
77def AVRlslLoop : SDNode<"AVRISD::LSLLOOP", SDTIntShiftOp>;
78def AVRlsrLoop : SDNode<"AVRISD::LSRLOOP", SDTIntShiftOp>;
79def AVRrolLoop : SDNode<"AVRISD::ROLLOOP", SDTIntShiftOp>;
80def AVRrorLoop : SDNode<"AVRISD::RORLOOP", SDTIntShiftOp>;
81def AVRasrLoop : SDNode<"AVRISD::ASRLOOP", SDTIntShiftOp>;
82
83// SWAP node.
84def AVRSwap : SDNode<"AVRISD::SWAP", SDTIntUnaryOp>;
85
86//===----------------------------------------------------------------------===//
87// AVR Operands, Complex Patterns and Transformations Definitions.
88//===----------------------------------------------------------------------===//
89
90def imm8_neg_XFORM : SDNodeXForm<imm, [{
91                                   return CurDAG->getTargetConstant(
92                                       -N->getAPIntValue(), SDLoc(N), MVT::i8);
93                                 }]>;
94
95def imm16_neg_XFORM
96    : SDNodeXForm<imm, [{
97                    return CurDAG->getTargetConstant(-N->getAPIntValue(),
98                                                     SDLoc(N), MVT::i16);
99                  }]>;
100
101def imm0_63_neg : PatLeaf<(imm), [{
102                            int64_t val = -N->getSExtValue();
103                            return val >= 0 && val < 64;
104                          }],
105                          imm16_neg_XFORM>;
106
107def uimm6 : PatLeaf<(imm), [{ return isUInt<6>(N->getZExtValue()); }]>;
108
109// imm_com8_XFORM - Return the complement of a imm_com8 value
110def imm_com8_XFORM
111    : SDNodeXForm<imm, [{
112                    return CurDAG->getTargetConstant(
113                        ~((uint8_t) N->getZExtValue()), SDLoc(N), MVT::i8);
114                  }]>;
115
116// imm_com8 - Match an immediate that is a complement
117// of a 8-bit immediate.
118// Note: this pattern doesn't require an encoder method and such, as it's
119// only used on aliases (Pat<> and InstAlias<>). The actual encoding
120// is handled by the destination instructions, which use imm_com8.
121def imm_com8_asmoperand : AsmOperandClass { let Name = "ImmCom8"; }
122def imm_com8 : Operand<i8> { let ParserMatchClass = imm_com8_asmoperand; }
123
124def ioaddr_XFORM
125    : SDNodeXForm<imm, [{
126                    uint8_t offset = Subtarget->getIORegisterOffset();
127                    return CurDAG->getTargetConstant(
128                        uint8_t(N->getZExtValue()) - offset, SDLoc(N), MVT::i8);
129                  }]>;
130
131def iobitpos8_XFORM
132    : SDNodeXForm<imm, [{
133                    return CurDAG->getTargetConstant(
134                        Log2_32(uint8_t(N->getZExtValue())), SDLoc(N), MVT::i8);
135                  }]>;
136
137def iobitposn8_XFORM : SDNodeXForm<imm, [{
138                                     return CurDAG->getTargetConstant(
139                                         Log2_32(uint8_t(~N->getZExtValue())),
140                                         SDLoc(N), MVT::i8);
141                                   }]>;
142
143def ioaddr8 : PatLeaf<(imm), [{
144                        uint8_t offset = Subtarget->getIORegisterOffset();
145                        uint64_t val = N->getZExtValue() - offset;
146                        return val < 0x40;
147                      }],
148                      ioaddr_XFORM>;
149
150def lowioaddr8 : PatLeaf<(imm), [{
151                           uint8_t offset = Subtarget->getIORegisterOffset();
152                           uint64_t val = N->getZExtValue() - offset;
153                           return val < 0x20;
154                         }],
155                         ioaddr_XFORM>;
156
157def ioaddr16 : PatLeaf<(imm), [{
158                         uint8_t offset = Subtarget->getIORegisterOffset();
159                         uint64_t val = N->getZExtValue() - offset;
160                         return val < 0x3f;
161                       }],
162                       ioaddr_XFORM>;
163
164def iobitpos8
165    : PatLeaf<(imm), [{ return isPowerOf2_32(uint8_t(N->getZExtValue())); }],
166              iobitpos8_XFORM>;
167
168def iobitposn8
169    : PatLeaf<(imm), [{ return isPowerOf2_32(uint8_t(~N->getZExtValue())); }],
170              iobitposn8_XFORM>;
171
172def MemriAsmOperand : AsmOperandClass {
173  let Name = "Memri";
174  let ParserMethod = "parseMemriOperand";
175}
176
177/// Address operand for `reg+imm` used by STD and LDD.
178def memri : Operand<iPTR> {
179  let MIOperandInfo = (ops PTRDISPREGS, i16imm);
180
181  let PrintMethod = "printMemri";
182  let EncoderMethod = "encodeMemri";
183  let DecoderMethod = "decodeMemri";
184
185  let ParserMatchClass = MemriAsmOperand;
186}
187
188// Address operand for `SP+imm` used by STD{W}SPQRr
189def memspi : Operand<iPTR> {
190  let MIOperandInfo = (ops GPRSP, i16imm);
191  let PrintMethod = "printMemspi";
192}
193
194def relbrtarget_7 : Operand<OtherVT> {
195  let PrintMethod = "printPCRelImm";
196  let EncoderMethod = "encodeRelCondBrTarget<AVR::fixup_7_pcrel>";
197}
198
199def brtarget_13 : Operand<OtherVT> {
200  let PrintMethod = "printPCRelImm";
201  let EncoderMethod = "encodeRelCondBrTarget<AVR::fixup_13_pcrel>";
202}
203
204def rcalltarget_13 : Operand<i16> {
205  let PrintMethod = "printPCRelImm";
206  let EncoderMethod = "encodeRelCondBrTarget<AVR::fixup_13_pcrel>";
207}
208
209// The target of a 22 or 16-bit call/jmp instruction.
210def call_target : Operand<iPTR> {
211  let EncoderMethod = "encodeCallTarget";
212  let DecoderMethod = "decodeCallTarget";
213}
214
215// A 16-bit address (which can lead to an R_AVR_16 relocation).
216def imm16 : Operand<i16> { let EncoderMethod = "encodeImm<AVR::fixup_16, 2>"; }
217
218// A 7-bit address (which can lead to an R_AVR_LDS_STS_16 relocation).
219def imm7tiny : Operand<i16> {
220  let EncoderMethod = "encodeImm<AVR::fixup_lds_sts_16, 0>";
221}
222
223/// A 6-bit immediate used in the ADIW/SBIW instructions.
224def imm_arith6 : Operand<i16> {
225  let EncoderMethod = "encodeImm<AVR::fixup_6_adiw, 0>";
226}
227
228/// An 8-bit immediate inside an instruction with the same format
229/// as the `LDI` instruction (the `FRdK` format).
230def imm_ldi8 : Operand<i8> {
231  let EncoderMethod = "encodeImm<AVR::fixup_ldi, 0>";
232}
233
234/// A 5-bit port number used in SBIC and friends (the `FIOBIT` format).
235def imm_port5 : Operand<i8> {
236  let EncoderMethod = "encodeImm<AVR::fixup_port5, 0>";
237}
238
239/// A 6-bit port number used in the `IN` instruction and friends (the
240/// `FIORdA` format.
241def imm_port6 : Operand<i8> {
242  let EncoderMethod = "encodeImm<AVR::fixup_port6, 0>";
243}
244
245// Addressing mode pattern reg+imm6
246def addr : ComplexPattern<iPTR, 2, "SelectAddr", [], [SDNPWantRoot]>;
247
248// AsmOperand class for a pointer register.
249// Used with the LD/ST family of instructions.
250// See FSTLD in AVRInstrFormats.td
251def PtrRegAsmOperand : AsmOperandClass { let Name = "Reg"; }
252
253// A special operand type for the LD/ST instructions.
254// It converts the pointer register number into a two-bit field used in the
255// instruction.
256def LDSTPtrReg : Operand<i16> {
257  let MIOperandInfo = (ops PTRREGS);
258  let EncoderMethod = "encodeLDSTPtrReg";
259
260  let ParserMatchClass = PtrRegAsmOperand;
261}
262
263// A special operand type for the LDD/STD instructions.
264// It behaves identically to the LD/ST version, except restricts
265// the pointer registers to Y and Z.
266def LDDSTDPtrReg : Operand<i16> {
267  let MIOperandInfo = (ops PTRDISPREGS);
268  let EncoderMethod = "encodeLDSTPtrReg";
269
270  let ParserMatchClass = PtrRegAsmOperand;
271}
272
273//===----------------------------------------------------------------------===//
274// AVR predicates for subtarget features
275//===----------------------------------------------------------------------===//
276
277def HasSRAM : Predicate<"Subtarget->hasSRAM()">,
278              AssemblerPredicate<(all_of FeatureSRAM)>;
279
280def HasJMPCALL : Predicate<"Subtarget->hasJMPCALL()">,
281                 AssemblerPredicate<(all_of FeatureJMPCALL)>;
282
283def HasIJMPCALL : Predicate<"Subtarget->hasIJMPCALL()">,
284                  AssemblerPredicate<(all_of FeatureIJMPCALL)>;
285
286def HasEIJMPCALL : Predicate<"Subtarget->hasEIJMPCALL()">,
287                   AssemblerPredicate<(all_of FeatureEIJMPCALL)>;
288
289def HasADDSUBIW : Predicate<"Subtarget->hasADDSUBIW()">,
290                  AssemblerPredicate<(all_of FeatureADDSUBIW)>;
291
292def HasSmallStack : Predicate<"Subtarget->HasSmallStack()">,
293                    AssemblerPredicate<(all_of FeatureSmallStack)>;
294
295def HasMOVW : Predicate<"Subtarget->hasMOVW()">,
296              AssemblerPredicate<(all_of FeatureMOVW)>;
297
298def HasLPM : Predicate<"Subtarget->hasLPM()">,
299             AssemblerPredicate<(all_of FeatureLPM)>;
300
301def HasLPMX : Predicate<"Subtarget->hasLPMX()">,
302              AssemblerPredicate<(all_of FeatureLPMX)>;
303
304def HasELPM : Predicate<"Subtarget->hasELPM()">,
305              AssemblerPredicate<(all_of FeatureELPM)>;
306
307def HasELPMX : Predicate<"Subtarget->hasELPMX()">,
308               AssemblerPredicate<(all_of FeatureELPMX)>;
309
310def HasSPM : Predicate<"Subtarget->hasSPM()">,
311             AssemblerPredicate<(all_of FeatureSPM)>;
312
313def HasSPMX : Predicate<"Subtarget->hasSPMX()">,
314              AssemblerPredicate<(all_of FeatureSPMX)>;
315
316def HasDES : Predicate<"Subtarget->hasDES()">,
317             AssemblerPredicate<(all_of FeatureDES)>;
318
319def SupportsRMW : Predicate<"Subtarget->supportsRMW()">,
320                  AssemblerPredicate<(all_of FeatureRMW)>;
321
322def SupportsMultiplication : Predicate<"Subtarget->supportsMultiplication()">,
323                             AssemblerPredicate<(all_of FeatureMultiplication)>;
324
325def HasBREAK : Predicate<"Subtarget->hasBREAK()">,
326               AssemblerPredicate<(all_of FeatureBREAK)>;
327
328def HasTinyEncoding : Predicate<"Subtarget->hasTinyEncoding()">,
329                      AssemblerPredicate<(all_of FeatureTinyEncoding)>;
330
331def HasNonTinyEncoding : Predicate<"!Subtarget->hasTinyEncoding()">,
332                         AssemblerPredicate<(any_of (not FeatureTinyEncoding))>;
333
334// AVR specific condition code. These correspond to AVR_*_COND in
335// AVRInstrInfo.td. They must be kept in synch.
336def AVR_COND_EQ : PatLeaf<(i8 0)>;
337def AVR_COND_NE : PatLeaf<(i8 1)>;
338def AVR_COND_GE : PatLeaf<(i8 2)>;
339def AVR_COND_LT : PatLeaf<(i8 3)>;
340def AVR_COND_SH : PatLeaf<(i8 4)>;
341def AVR_COND_LO : PatLeaf<(i8 5)>;
342def AVR_COND_MI : PatLeaf<(i8 6)>;
343def AVR_COND_PL : PatLeaf<(i8 7)>;
344
345//===----------------------------------------------------------------------===//
346//===----------------------------------------------------------------------===//
347// AVR Instruction list
348//===----------------------------------------------------------------------===//
349//===----------------------------------------------------------------------===//
350
351// ADJCALLSTACKDOWN/UP implicitly use/def SP because they may be expanded into
352// a stack adjustment and the codegen must know that they may modify the stack
353// pointer before prolog-epilog rewriting occurs.
354// Pessimistically assume ADJCALLSTACKDOWN / ADJCALLSTACKUP will become
355// sub / add which can clobber SREG.
356let Defs = [SP, SREG], Uses = [SP] in {
357  def ADJCALLSTACKDOWN : Pseudo<(outs),
358                                (ins i16imm
359                                 : $amt, i16imm
360                                 : $amt2),
361                                "#ADJCALLSTACKDOWN", [(AVRcallseq_start timm
362                                                       : $amt, timm
363                                                       : $amt2)]>;
364
365  // R31R30 is used to update SP. It is normally free because it is a
366  // call-clobbered register but it is necessary to set it as a def as the
367  // register allocator might use it in rare cases (for rematerialization, it
368  // seems). hasSideEffects needs to be set to true so this instruction isn't
369  // considered dead.
370  let Defs = [R31R30], hasSideEffects = 1 in def ADJCALLSTACKUP
371      : Pseudo<(outs),
372               (ins i16imm
373                : $amt1, i16imm
374                : $amt2),
375               "#ADJCALLSTACKUP", [(AVRcallseq_end timm
376                                    : $amt1, timm
377                                    : $amt2)]>;
378}
379
380//===----------------------------------------------------------------------===//
381// Addition
382//===----------------------------------------------------------------------===//
383let isCommutable = 1, Constraints = "$src = $rd", Defs = [SREG] in {
384  // ADD Rd, Rr
385  // Adds two 8-bit registers.
386  def ADDRdRr
387      : FRdRr<0b0000, 0b11,
388              (outs GPR8
389               : $rd),
390              (ins GPR8
391               : $src, GPR8
392               : $rr),
393              "add\t$rd, $rr",
394              [(set i8
395                : $rd, (add i8
396                        : $src, i8
397                        : $rr)),
398               (implicit SREG)]>;
399
400  // ADDW Rd+1:Rd, Rr+1:Rr
401  // Pseudo instruction to add four 8-bit registers as two 16-bit values.
402  //
403  // Expands to:
404  // add Rd,    Rr
405  // adc Rd+1, Rr+1
406  def ADDWRdRr
407      : Pseudo<(outs DREGS
408                : $rd),
409               (ins DREGS
410                : $src, DREGS
411                : $rr),
412               "addw\t$rd, $rr",
413               [(set i16
414                 : $rd, (add i16
415                         : $src, i16
416                         : $rr)),
417                (implicit SREG)]>;
418
419  // ADC Rd, Rr
420  // Adds two 8-bit registers with carry.
421  let Uses = [SREG] in def ADCRdRr
422      : FRdRr<0b0001, 0b11,
423              (outs GPR8
424               : $rd),
425              (ins GPR8
426               : $src, GPR8
427               : $rr),
428              "adc\t$rd, $rr",
429              [(set i8
430                : $rd, (adde i8
431                        : $src, i8
432                        : $rr)),
433               (implicit SREG)]>;
434
435  // ADCW Rd+1:Rd, Rr+1:Rr
436  // Pseudo instruction to add four 8-bit registers as two 16-bit values with
437  // carry.
438  //
439  // Expands to:
440  // adc Rd,   Rr
441  // adc Rd+1, Rr+1
442  let Uses = [SREG] in def ADCWRdRr : Pseudo<(outs DREGS
443                                              : $rd),
444                                             (ins DREGS
445                                              : $src, DREGS
446                                              : $rr),
447                                             "adcw\t$rd, $rr", [
448                                               (set i16
449                                                : $rd, (adde i16
450                                                        : $src, i16
451                                                        : $rr)),
452                                               (implicit SREG)
453                                             ]>;
454
455  // AIDW Rd, k
456  // Adds an immediate 6-bit value K to Rd, placing the result in Rd.
457  def ADIWRdK
458      : FWRdK<0b0,
459              (outs IWREGS
460               : $rd),
461              (ins IWREGS
462               : $src, imm_arith6
463               : $k),
464              "adiw\t$rd, $k",
465              [(set i16
466                : $rd, (add i16
467                        : $src, uimm6
468                        : $k)),
469               (implicit SREG)]>,
470        Requires<[HasADDSUBIW]>;
471}
472
473//===----------------------------------------------------------------------===//
474// Subtraction
475//===----------------------------------------------------------------------===//
476let Constraints = "$src = $rd", Defs = [SREG] in {
477  // SUB Rd, Rr
478  // Subtracts the 8-bit value of Rr from Rd and places the value in Rd.
479  def SUBRdRr
480      : FRdRr<0b0001, 0b10,
481              (outs GPR8
482               : $rd),
483              (ins GPR8
484               : $src, GPR8
485               : $rr),
486              "sub\t$rd, $rr",
487              [(set i8
488                : $rd, (sub i8
489                        : $src, i8
490                        : $rr)),
491               (implicit SREG)]>;
492
493  // SUBW Rd+1:Rd, Rr+1:Rr
494  // Subtracts two 16-bit values and places the result into Rd.
495  //
496  // Expands to:
497  // sub Rd,   Rr
498  // sbc Rd+1, Rr+1
499  def SUBWRdRr
500      : Pseudo<(outs DREGS
501                : $rd),
502               (ins DREGS
503                : $src, DREGS
504                : $rr),
505               "subw\t$rd, $rr",
506               [(set i16
507                 : $rd, (sub i16
508                         : $src, i16
509                         : $rr)),
510                (implicit SREG)]>;
511
512  def SUBIRdK
513      : FRdK<0b0101,
514             (outs LD8
515              : $rd),
516             (ins LD8
517              : $src, imm_ldi8
518              : $k),
519             "subi\t$rd, $k",
520             [(set i8
521               : $rd, (sub i8
522                       : $src, imm
523                       : $k)),
524              (implicit SREG)]>;
525
526  // SUBIW Rd+1:Rd, K+1:K
527  //
528  // Expands to:
529  // subi Rd,   K
530  // sbci Rd+1, K+1
531  def SUBIWRdK
532      : Pseudo<(outs DLDREGS
533                : $rd),
534               (ins DLDREGS
535                : $src, i16imm
536                : $rr),
537               "subiw\t$rd, $rr",
538               [(set i16
539                 : $rd, (sub i16
540                         : $src, imm
541                         : $rr)),
542                (implicit SREG)]>;
543
544  def SBIWRdK
545      : FWRdK<0b1,
546              (outs IWREGS
547               : $rd),
548              (ins IWREGS
549               : $src, imm_arith6
550               : $k),
551              "sbiw\t$rd, $k",
552              [(set i16
553                : $rd, (sub i16
554                        : $src, uimm6
555                        : $k)),
556               (implicit SREG)]>,
557        Requires<[HasADDSUBIW]>;
558
559  // Subtract with carry operations which must read the carry flag in SREG.
560  let Uses = [SREG] in {
561    def SBCRdRr
562        : FRdRr<0b0000, 0b10,
563                (outs GPR8
564                 : $rd),
565                (ins GPR8
566                 : $src, GPR8
567                 : $rr),
568                "sbc\t$rd, $rr",
569                [(set i8
570                  : $rd, (sube i8
571                          : $src, i8
572                          : $rr)),
573                 (implicit SREG)]>;
574
575    // SBCW Rd+1:Rd, Rr+1:Rr
576    //
577    // Expands to:
578    // sbc Rd,   Rr
579    // sbc Rd+1, Rr+1
580    def SBCWRdRr : Pseudo<(outs DREGS
581                           : $rd),
582                          (ins DREGS
583                           : $src, DREGS
584                           : $rr),
585                          "sbcw\t$rd, $rr", [
586                            (set i16
587                             : $rd, (sube i16
588                                     : $src, i16
589                                     : $rr)),
590                            (implicit SREG)
591                          ]>;
592
593    def SBCIRdK
594        : FRdK<0b0100,
595               (outs LD8
596                : $rd),
597               (ins LD8
598                : $src, imm_ldi8
599                : $k),
600               "sbci\t$rd, $k",
601               [(set i8
602                 : $rd, (sube i8
603                         : $src, imm
604                         : $k)),
605                (implicit SREG)]>;
606
607    // SBCIW Rd+1:Rd, K+1:K
608    // sbci Rd,   K
609    // sbci Rd+1, K+1
610    def SBCIWRdK : Pseudo<(outs DLDREGS
611                           : $rd),
612                          (ins DLDREGS
613                           : $src, i16imm
614                           : $rr),
615                          "sbciw\t$rd, $rr", [
616                            (set i16
617                             : $rd, (sube i16
618                                     : $src, imm
619                                     : $rr)),
620                            (implicit SREG)
621                          ]>;
622  }
623}
624
625//===----------------------------------------------------------------------===//
626// Increment and Decrement
627//===----------------------------------------------------------------------===//
628let Constraints = "$src = $rd", Defs = [SREG] in {
629  def INCRd
630      : FRd<0b1001, 0b0100011,
631            (outs GPR8
632             : $rd),
633            (ins GPR8
634             : $src),
635            "inc\t$rd", [(set i8
636                          : $rd, (add i8
637                                  : $src, 1)),
638                         (implicit SREG)]>;
639
640  def DECRd
641      : FRd<0b1001, 0b0101010,
642            (outs GPR8
643             : $rd),
644            (ins GPR8
645             : $src),
646            "dec\t$rd", [(set i8
647                          : $rd, (add i8
648                                  : $src, -1)),
649                         (implicit SREG)]>;
650}
651
652//===----------------------------------------------------------------------===//
653// Multiplication
654//===----------------------------------------------------------------------===//
655
656let isCommutable = 1, Defs = [R1, R0, SREG] in {
657  // MUL Rd, Rr
658  // Multiplies Rd by Rr and places the result into R1:R0.
659  let usesCustomInserter = 1 in {
660    def MULRdRr : FRdRr<0b1001, 0b11, (outs),
661                        (ins GPR8
662                         : $rd, GPR8
663                         : $rr),
664                        "mul\t$rd, $rr",
665                        [/*(set R1, R0, (smullohi i8:$rd, i8:$rr))*/]>,
666                  Requires<[SupportsMultiplication]>;
667
668    def MULSRdRr : FMUL2RdRr<0, (outs),
669                             (ins LD8
670                              : $rd, LD8
671                              : $rr),
672                             "muls\t$rd, $rr", []>,
673                   Requires<[SupportsMultiplication]>;
674  }
675
676  def MULSURdRr : FMUL2RdRr<1, (outs),
677                            (ins LD8lo
678                             : $rd, LD8lo
679                             : $rr),
680                            "mulsu\t$rd, $rr", []>,
681                  Requires<[SupportsMultiplication]>;
682
683  def FMUL : FFMULRdRr<0b01, (outs),
684                       (ins LD8lo
685                        : $rd, LD8lo
686                        : $rr),
687                       "fmul\t$rd, $rr", []>,
688             Requires<[SupportsMultiplication]>;
689
690  def FMULS : FFMULRdRr<0b10, (outs),
691                        (ins LD8lo
692                         : $rd, LD8lo
693                         : $rr),
694                        "fmuls\t$rd, $rr", []>,
695              Requires<[SupportsMultiplication]>;
696
697  def FMULSU : FFMULRdRr<0b11, (outs),
698                         (ins LD8lo
699                          : $rd, LD8lo
700                          : $rr),
701                         "fmulsu\t$rd, $rr", []>,
702               Requires<[SupportsMultiplication]>;
703}
704
705let Defs =
706    [R15, R14, R13, R12, R11, R10, R9, R8, R7, R6, R5, R4, R3, R2, R1,
707     R0] in def DESK : FDES<(outs),
708                            (ins i8imm
709                             : $k),
710                            "des\t$k", []>,
711    Requires<[HasDES]>;
712
713//===----------------------------------------------------------------------===//
714// Logic
715//===----------------------------------------------------------------------===//
716let Constraints = "$src = $rd", Defs = [SREG] in {
717  // Register-Register logic instructions (which have the
718  // property of commutativity).
719  let isCommutable = 1 in {
720    def ANDRdRr
721        : FRdRr<0b0010, 0b00,
722                (outs GPR8
723                 : $rd),
724                (ins GPR8
725                 : $src, GPR8
726                 : $rr),
727                "and\t$rd, $rr",
728                [(set i8
729                  : $rd, (and i8
730                          : $src, i8
731                          : $rr)),
732                 (implicit SREG)]>;
733
734    // ANDW Rd+1:Rd, Rr+1:Rr
735    //
736    // Expands to:
737    // and Rd,   Rr
738    // and Rd+1, Rr+1
739    def ANDWRdRr : Pseudo<(outs DREGS
740                           : $rd),
741                          (ins DREGS
742                           : $src, DREGS
743                           : $rr),
744                          "andw\t$rd, $rr", [
745                            (set i16
746                             : $rd, (and i16
747                                     : $src, i16
748                                     : $rr)),
749                            (implicit SREG)
750                          ]>;
751
752    def ORRdRr
753        : FRdRr<0b0010, 0b10,
754                (outs GPR8
755                 : $rd),
756                (ins GPR8
757                 : $src, GPR8
758                 : $rr),
759                "or\t$rd, $rr",
760                [(set i8
761                  : $rd, (or i8
762                          : $src, i8
763                          : $rr)),
764                 (implicit SREG)]>;
765
766    // ORW Rd+1:Rd, Rr+1:Rr
767    //
768    // Expands to:
769    // or Rd,   Rr
770    // or Rd+1, Rr+1
771    def ORWRdRr : Pseudo<(outs DREGS
772                          : $rd),
773                         (ins DREGS
774                          : $src, DREGS
775                          : $rr),
776                         "orw\t$rd, $rr", [
777                           (set i16
778                            : $rd, (or i16
779                                    : $src, i16
780                                    : $rr)),
781                           (implicit SREG)
782                         ]>;
783
784    def EORRdRr
785        : FRdRr<0b0010, 0b01,
786                (outs GPR8
787                 : $rd),
788                (ins GPR8
789                 : $src, GPR8
790                 : $rr),
791                "eor\t$rd, $rr",
792                [(set i8
793                  : $rd, (xor i8
794                          : $src, i8
795                          : $rr)),
796                 (implicit SREG)]>;
797
798    // EORW Rd+1:Rd, Rr+1:Rr
799    //
800    // Expands to:
801    // eor Rd,   Rr
802    // eor Rd+1, Rr+1
803    def EORWRdRr : Pseudo<(outs DREGS
804                           : $rd),
805                          (ins DREGS
806                           : $src, DREGS
807                           : $rr),
808                          "eorw\t$rd, $rr", [
809                            (set i16
810                             : $rd, (xor i16
811                                     : $src, i16
812                                     : $rr)),
813                            (implicit SREG)
814                          ]>;
815  }
816
817  def ANDIRdK
818      : FRdK<0b0111,
819             (outs LD8
820              : $rd),
821             (ins LD8
822              : $src, imm_ldi8
823              : $k),
824             "andi\t$rd, $k",
825             [(set i8
826               : $rd, (and i8
827                       : $src, imm
828                       : $k)),
829              (implicit SREG)]>;
830
831  // ANDI Rd+1:Rd, K+1:K
832  //
833  // Expands to:
834  // andi Rd,   K
835  // andi Rd+1, K+1
836  def ANDIWRdK
837      : Pseudo<(outs DLDREGS
838                : $rd),
839               (ins DLDREGS
840                : $src, i16imm
841                : $k),
842               "andiw\t$rd, $k",
843               [(set i16
844                 : $rd, (and i16
845                         : $src, imm
846                         : $k)),
847                (implicit SREG)]>;
848
849  def ORIRdK
850      : FRdK<0b0110,
851             (outs LD8
852              : $rd),
853             (ins LD8
854              : $src, imm_ldi8
855              : $k),
856             "ori\t$rd, $k",
857             [(set i8
858               : $rd, (or i8
859                       : $src, imm
860                       : $k)),
861              (implicit SREG)]>;
862
863  // ORIW Rd+1:Rd, K+1,K
864  //
865  // Expands to:
866  // ori Rd,   K
867  // ori Rd+1, K+1
868  def ORIWRdK
869      : Pseudo<(outs DLDREGS
870                : $rd),
871               (ins DLDREGS
872                : $src, i16imm
873                : $rr),
874               "oriw\t$rd, $rr",
875               [(set i16
876                 : $rd, (or i16
877                         : $src, imm
878                         : $rr)),
879                (implicit SREG)]>;
880}
881
882//===----------------------------------------------------------------------===//
883// One's/Two's Complement
884//===----------------------------------------------------------------------===//
885let Constraints = "$src = $rd", Defs = [SREG] in {
886  def COMRd
887      : FRd<0b1001, 0b0100000,
888            (outs GPR8
889             : $rd),
890            (ins GPR8
891             : $src),
892            "com\t$rd", [(set i8
893                          : $rd, (not i8
894                                  : $src)),
895                         (implicit SREG)]>;
896
897  // COMW Rd+1:Rd
898  //
899  // Expands to:
900  // com Rd
901  // com Rd+1
902  def COMWRd : Pseudo<(outs DREGS
903                       : $rd),
904                      (ins DREGS
905                       : $src),
906                      "comw\t$rd",
907                      [(set i16
908                        : $rd, (not i16
909                                : $src)),
910                       (implicit SREG)]>;
911
912  def NEGRd
913      : FRd<0b1001, 0b0100001,
914            (outs GPR8
915             : $rd),
916            (ins GPR8
917             : $src),
918            "neg\t$rd", [(set i8
919                          : $rd, (ineg i8
920                                  : $src)),
921                         (implicit SREG)]>;
922
923  // NEGW Rd+1:Rd
924  //
925  // Expands to:
926  // neg Rd+1
927  // neg Rd
928  // sbc Rd+1, r1
929  let hasSideEffects=0 in
930  def NEGWRd : Pseudo<(outs DREGS:$rd),
931                      (ins DREGS:$src, GPR8:$zero),
932                      "negw\t$rd",
933                      []>;
934}
935
936// TST Rd
937// Test for zero of minus.
938// This operation is identical to a `Rd AND Rd`.
939def : InstAlias<"tst\t$rd", (ANDRdRr GPR8 : $rd, GPR8 : $rd)>;
940
941// SBR Rd, K
942//
943// Mnemonic alias to 'ORI Rd, K'. Same bit pattern, same operands,
944// same everything.
945def : InstAlias<"sbr\t$rd, $k",
946                (ORIRdK LD8
947                 : $rd, imm_ldi8
948                 : $k),
949                /* Disable display, so we don't override ORI */ 0>;
950
951//===----------------------------------------------------------------------===//
952// Jump instructions
953//===----------------------------------------------------------------------===//
954let isBarrier = 1, isBranch = 1, isTerminator = 1 in {
955  def RJMPk : FBRk<0, (outs),
956                   (ins brtarget_13
957                    : $k),
958                   "rjmp\t$k", [(br bb
959                                 : $k)]>;
960
961  let isIndirectBranch = 1,
962      Uses = [R31R30] in def IJMP
963      : F16<0b1001010000001001, (outs), (ins), "ijmp", []>,
964      Requires<[HasIJMPCALL]>;
965
966  let isIndirectBranch = 1,
967      Uses = [R31R30] in def EIJMP
968      : F16<0b1001010000011001, (outs), (ins), "eijmp", []>,
969      Requires<[HasEIJMPCALL]>;
970
971  def JMPk : F32BRk<0b110, (outs),
972                    (ins call_target
973                     : $k),
974                    "jmp\t$k", []>,
975             Requires<[HasJMPCALL]>;
976}
977
978//===----------------------------------------------------------------------===//
979// Call instructions
980//===----------------------------------------------------------------------===//
981let isCall = 1 in {
982  // SP is marked as a use to prevent stack-pointer assignments that appear
983  // immediately before calls from potentially appearing dead.
984  let Uses = [SP] in def RCALLk : FBRk<1, (outs), (ins rcalltarget_13:$k),
985                                       "rcall\t$k", [(AVRcall imm:$k)]>;
986
987  // SP is marked as a use to prevent stack-pointer assignments that appear
988  // immediately before calls from potentially appearing dead.
989  let Uses = [SP, R31R30] in def ICALL
990      : F16<0b1001010100001001, (outs), (ins variable_ops), "icall", []>,
991      Requires<[HasIJMPCALL]>;
992
993  // SP is marked as a use to prevent stack-pointer assignments that appear
994  // immediately before calls from potentially appearing dead.
995  let Uses = [SP, R31R30] in def EICALL
996      : F16<0b1001010100011001, (outs), (ins variable_ops), "eicall", []>,
997      Requires<[HasEIJMPCALL]>;
998
999  // SP is marked as a use to prevent stack-pointer assignments that appear
1000  // immediately before calls from potentially appearing dead.
1001  //
1002  // TODO: the imm field can be either 16 or 22 bits in devices with more
1003  // than 64k of ROM, fix it once we support the largest devices.
1004  let Uses = [SP] in def CALLk : F32BRk<0b111, (outs), (ins call_target:$k),
1005                                        "call\t$k", [(AVRcall imm:$k)]>,
1006      Requires<[HasJMPCALL]>;
1007}
1008
1009//===----------------------------------------------------------------------===//
1010// Return instructions.
1011//===----------------------------------------------------------------------===//
1012let isTerminator = 1, isReturn = 1, isBarrier = 1 in {
1013  def RET : F16<0b1001010100001000, (outs), (ins), "ret", [(AVRretflag)]>;
1014
1015  def RETI : F16<0b1001010100011000, (outs), (ins), "reti", [(AVRretiflag)]>;
1016}
1017
1018//===----------------------------------------------------------------------===//
1019// Compare operations.
1020//===----------------------------------------------------------------------===//
1021let Defs = [SREG] in {
1022  // CPSE Rd, Rr
1023  // Compare Rd and Rr, skipping the next instruction if they are equal.
1024  let isBarrier = 1, isBranch = 1,
1025      isTerminator = 1 in def CPSE : FRdRr<0b0001, 0b00, (outs),
1026                                           (ins GPR8
1027                                            : $rd, GPR8
1028                                            : $rr),
1029                                           "cpse\t$rd, $rr", []>;
1030
1031  def CPRdRr
1032      : FRdRr<0b0001, 0b01, (outs),
1033              (ins GPR8
1034               : $rd, GPR8
1035               : $rr),
1036              "cp\t$rd, $rr", [(AVRcmp i8
1037                                : $rd, i8
1038                                : $rr),
1039                               (implicit SREG)]>;
1040
1041  // CPW Rd+1:Rd, Rr+1:Rr
1042  //
1043  // Expands to:
1044  // cp  Rd,   Rr
1045  // cpc Rd+1, Rr+1
1046  def CPWRdRr : Pseudo<(outs),
1047                       (ins DREGS
1048                        : $src, DREGS
1049                        : $src2),
1050                       "cpw\t$src, $src2",
1051                       [(AVRcmp i16
1052                         : $src, i16
1053                         : $src2),
1054                        (implicit SREG)]>;
1055
1056  let Uses = [SREG] in def CPCRdRr
1057      : FRdRr<0b0000, 0b01, (outs),
1058              (ins GPR8
1059               : $rd, GPR8
1060               : $rr),
1061              "cpc\t$rd, $rr", [(AVRcmpc i8
1062                                 : $rd, i8
1063                                 : $rr),
1064                                (implicit SREG)]>;
1065
1066  // CPCW Rd+1:Rd. Rr+1:Rr
1067  //
1068  // Expands to:
1069  // cpc Rd,   Rr
1070  // cpc Rd+1, Rr+1
1071  let Uses = [SREG] in def CPCWRdRr
1072      : Pseudo<(outs),
1073               (ins DREGS
1074                : $src, DREGS
1075                : $src2),
1076               "cpcw\t$src, $src2",
1077               [(AVRcmpc i16
1078                 : $src, i16
1079                 : $src2),
1080                (implicit SREG)]>;
1081
1082  // CPI Rd, K
1083  // Compares a register with an 8 bit immediate.
1084  def CPIRdK
1085      : FRdK<0b0011, (outs),
1086             (ins LD8
1087              : $rd, imm_ldi8
1088              : $k),
1089             "cpi\t$rd, $k", [(AVRcmp i8
1090                               : $rd, imm
1091                               : $k),
1092                              (implicit SREG)]>;
1093}
1094
1095//===----------------------------------------------------------------------===//
1096// Register conditional skipping/branching operations.
1097//===----------------------------------------------------------------------===//
1098let isBranch = 1, isTerminator = 1 in {
1099  // Conditional skipping on GPR register bits, and
1100  // conditional skipping on IO register bits.
1101  let isBarrier = 1 in {
1102    def SBRCRrB : FRdB<0b10, (outs),
1103                       (ins GPR8
1104                        : $rd, i8imm
1105                        : $b),
1106                       "sbrc\t$rd, $b", []>;
1107
1108    def SBRSRrB : FRdB<0b11, (outs),
1109                       (ins GPR8
1110                        : $rd, i8imm
1111                        : $b),
1112                       "sbrs\t$rd, $b", []>;
1113
1114    def SBICAb : FIOBIT<0b01, (outs),
1115                        (ins imm_port5
1116                         : $addr, i8imm
1117                         : $b),
1118                        "sbic\t$addr, $b", []>;
1119
1120    def SBISAb : FIOBIT<0b11, (outs),
1121                        (ins imm_port5
1122                         : $addr, i8imm
1123                         : $b),
1124                        "sbis\t$addr, $b", []>;
1125  }
1126
1127  // Relative branches on status flag bits.
1128  let Uses = [SREG] in {
1129    // BRBS s, k
1130    // Branch if `s` flag in status register is set.
1131    def BRBSsk : FSK<0, (outs),
1132                     (ins i8imm
1133                      : $s, relbrtarget_7
1134                      : $k),
1135                     "brbs\t$s, $k", []>;
1136
1137    // BRBC s, k
1138    // Branch if `s` flag in status register is clear.
1139    def BRBCsk : FSK<1, (outs),
1140                     (ins i8imm
1141                      : $s, relbrtarget_7
1142                      : $k),
1143                     "brbc\t$s, $k", []>;
1144  }
1145}
1146
1147// BRCS k
1148// Branch if carry flag is set
1149def : InstAlias<"brcs\t$k", (BRBSsk 0, relbrtarget_7 : $k)>;
1150
1151// BRCC k
1152// Branch if carry flag is clear
1153def : InstAlias<"brcc\t$k", (BRBCsk 0, relbrtarget_7 : $k)>;
1154
1155// BRHS k
1156// Branch if half carry flag is set
1157def : InstAlias<"brhs\t$k", (BRBSsk 5, relbrtarget_7 : $k)>;
1158
1159// BRHC k
1160// Branch if half carry flag is clear
1161def : InstAlias<"brhc\t$k", (BRBCsk 5, relbrtarget_7 : $k)>;
1162
1163// BRTS k
1164// Branch if the T flag is set
1165def : InstAlias<"brts\t$k", (BRBSsk 6, relbrtarget_7 : $k)>;
1166
1167// BRTC k
1168// Branch if the T flag is clear
1169def : InstAlias<"brtc\t$k", (BRBCsk 6, relbrtarget_7 : $k)>;
1170
1171// BRVS k
1172// Branch if the overflow flag is set
1173def : InstAlias<"brvs\t$k", (BRBSsk 3, relbrtarget_7 : $k)>;
1174
1175// BRVC k
1176// Branch if the overflow flag is clear
1177def : InstAlias<"brvc\t$k", (BRBCsk 3, relbrtarget_7 : $k)>;
1178
1179// BRIE k
1180// Branch if the global interrupt flag is enabled
1181def : InstAlias<"brie\t$k", (BRBSsk 7, relbrtarget_7 : $k)>;
1182
1183// BRID k
1184// Branch if the global interrupt flag is disabled
1185def : InstAlias<"brid\t$k", (BRBCsk 7, relbrtarget_7 : $k)>;
1186
1187//===----------------------------------------------------------------------===//
1188// PC-relative conditional branches
1189//===----------------------------------------------------------------------===//
1190// Based on status register. We cannot simplify these into instruction aliases
1191// because we also need to be able to specify a pattern to match for ISel.
1192let isBranch = 1, isTerminator = 1, Uses = [SREG] in {
1193  def BREQk : FBRsk<0, 0b001, (outs),
1194                    (ins relbrtarget_7
1195                     : $k),
1196                    "breq\t$k", [(AVRbrcond bb
1197                                  : $k, AVR_COND_EQ)]>;
1198
1199  def BRNEk : FBRsk<1, 0b001, (outs),
1200                    (ins relbrtarget_7
1201                     : $k),
1202                    "brne\t$k", [(AVRbrcond bb
1203                                 : $k, AVR_COND_NE)]>;
1204
1205  def BRSHk : FBRsk<1, 0b000, (outs),
1206                    (ins relbrtarget_7
1207                     : $k),
1208                    "brsh\t$k", [(AVRbrcond bb
1209                                 : $k, AVR_COND_SH)]>;
1210
1211  def BRLOk : FBRsk<0, 0b000, (outs),
1212                    (ins relbrtarget_7
1213                     : $k),
1214                    "brlo\t$k", [(AVRbrcond bb
1215                                 : $k, AVR_COND_LO)]>;
1216
1217  def BRMIk : FBRsk<0, 0b010, (outs),
1218                    (ins relbrtarget_7
1219                     : $k),
1220                    "brmi\t$k", [(AVRbrcond bb
1221                                 : $k, AVR_COND_MI)]>;
1222
1223  def BRPLk : FBRsk<1, 0b010, (outs),
1224                    (ins relbrtarget_7
1225                     : $k),
1226                    "brpl\t$k", [(AVRbrcond bb
1227                                 : $k, AVR_COND_PL)]>;
1228
1229  def BRGEk : FBRsk<1, 0b100, (outs),
1230                    (ins relbrtarget_7
1231                     : $k),
1232                    "brge\t$k", [(AVRbrcond bb
1233                                 : $k, AVR_COND_GE)]>;
1234
1235  def BRLTk : FBRsk<0, 0b100, (outs),
1236                    (ins relbrtarget_7
1237                     : $k),
1238                    "brlt\t$k", [(AVRbrcond bb
1239                                 : $k, AVR_COND_LT)]>;
1240}
1241
1242//===----------------------------------------------------------------------===//
1243// Data transfer instructions
1244//===----------------------------------------------------------------------===//
1245// 8 and 16-bit register move instructions.
1246let hasSideEffects = 0 in {
1247  def MOVRdRr : FRdRr<0b0010, 0b11,
1248                      (outs GPR8
1249                       : $rd),
1250                      (ins GPR8
1251                       : $rr),
1252                      "mov\t$rd, $rr", []>;
1253
1254  def MOVWRdRr : FMOVWRdRr<(outs DREGS
1255                            : $rd),
1256                           (ins DREGS
1257                            : $rr),
1258                           "movw\t$rd, $rr", []>,
1259                 Requires<[HasMOVW]>;
1260}
1261
1262// Load immediate values into registers.
1263let isReMaterializable = 1 in {
1264  def LDIRdK : FRdK<0b1110,
1265                    (outs LD8
1266                     : $rd),
1267                    (ins imm_ldi8
1268                     : $k),
1269                    "ldi\t$rd, $k", [(set i8
1270                                      : $rd, imm
1271                                      : $k)]>;
1272
1273  // LDIW Rd+1:Rd, K+1:K
1274  //
1275  // Expands to:
1276  // ldi Rd,   K
1277  // ldi Rd+1, K+1
1278  def LDIWRdK : Pseudo<(outs DLDREGS
1279                        : $dst),
1280                       (ins i16imm
1281                        : $src),
1282                       "ldiw\t$dst, $src", [(set i16
1283                                             : $dst, imm
1284                                             : $src)]>;
1285}
1286
1287// Load from data space into register.
1288let canFoldAsLoad = 1, isReMaterializable = 1 in {
1289  def LDSRdK : F32DM<0b0,
1290                     (outs GPR8
1291                      : $rd),
1292                     (ins imm16
1293                      : $k),
1294                     "lds\t$rd, $k", [(set i8
1295                                       : $rd, (load imm
1296                                               : $k))]>,
1297               Requires<[HasSRAM, HasNonTinyEncoding]>;
1298
1299  // Load from data space into register, which is only available on AVRTiny.
1300  def LDSRdKTiny : FLDSSTSTINY<0b0, (outs LD8:$rd), (ins imm7tiny:$k),
1301                               "lds\t$rd, $k",
1302                               [(set i8:$rd, (load imm:$k))]>,
1303                   Requires<[HasSRAM, HasTinyEncoding]>;
1304
1305  // LDSW Rd+1:Rd, K+1:K
1306  //
1307  // Expands to:
1308  // lds Rd,  (K+1:K)
1309  // lds Rd+1 (K+1:K) + 1
1310  def LDSWRdK : Pseudo<(outs DREGS
1311                        : $dst),
1312                       (ins i16imm
1313                        : $src),
1314                       "ldsw\t$dst, $src", [(set i16
1315                                             : $dst, (load imm
1316                                                      : $src))]>,
1317                Requires<[HasSRAM, HasNonTinyEncoding]>;
1318}
1319
1320// Indirect loads.
1321let canFoldAsLoad = 1, isReMaterializable = 1 in {
1322  def LDRdPtr : FSTLD<0, 0b00,
1323                      (outs GPR8
1324                       : $reg),
1325                      (ins LDSTPtrReg
1326                       : $ptrreg),
1327                      "ld\t$reg, $ptrreg", [(set GPR8
1328                                             : $reg, (load i16
1329                                                      : $ptrreg))]>,
1330                Requires<[HasSRAM]>;
1331
1332  // LDW Rd+1:Rd, P
1333  //
1334  // Expands to:
1335  //   ld  Rd,   P
1336  //   ldd Rd+1, P+1
1337  // On reduced tiny cores, this instruction expands to:
1338  //   ld    Rd,   P+
1339  //   ld    Rd+1, P+
1340  //   subiw P,    2
1341  let Constraints = "@earlyclobber $reg" in def LDWRdPtr
1342      : Pseudo<(outs DREGS
1343                : $reg),
1344               (ins PTRDISPREGS
1345                : $ptrreg),
1346               "ldw\t$reg, $ptrreg", [(set i16
1347                                       : $reg, (load i16
1348                                                : $ptrreg))]>,
1349      Requires<[HasSRAM]>;
1350}
1351
1352// Indirect loads (with postincrement or predecrement).
1353let mayLoad = 1, hasSideEffects = 0,
1354    Constraints = "$ptrreg = $base_wb,@earlyclobber $reg" in {
1355  def LDRdPtrPi : FSTLD<0, 0b01,
1356                        (outs GPR8
1357                         : $reg, PTRREGS
1358                         : $base_wb),
1359                        (ins LDSTPtrReg
1360                         : $ptrreg),
1361                        "ld\t$reg, $ptrreg+", []>,
1362                  Requires<[HasSRAM]>;
1363
1364  // LDW Rd+1:Rd, P+
1365  // Expands to:
1366  // ld Rd,   P+
1367  // ld Rd+1, P+
1368  def LDWRdPtrPi : Pseudo<(outs DREGS
1369                           : $reg, PTRREGS
1370                           : $base_wb),
1371                          (ins PTRREGS
1372                           : $ptrreg),
1373                          "ldw\t$reg, $ptrreg+", []>,
1374                   Requires<[HasSRAM]>;
1375
1376  def LDRdPtrPd : FSTLD<0, 0b10,
1377                        (outs GPR8
1378                         : $reg, PTRREGS
1379                         : $base_wb),
1380                        (ins LDSTPtrReg
1381                         : $ptrreg),
1382                        "ld\t$reg, -$ptrreg", []>,
1383                  Requires<[HasSRAM]>;
1384
1385  // LDW Rd+1:Rd, -P
1386  //
1387  // Expands to:
1388  // ld Rd+1, -P
1389  // ld Rd,   -P
1390  def LDWRdPtrPd : Pseudo<(outs DREGS
1391                           : $reg, PTRREGS
1392                           : $base_wb),
1393                          (ins PTRREGS
1394                           : $ptrreg),
1395                          "ldw\t$reg, -$ptrreg", []>,
1396                   Requires<[HasSRAM]>;
1397}
1398
1399// Load indirect with displacement operations.
1400let canFoldAsLoad = 1, isReMaterializable = 1 in {
1401  let Constraints = "@earlyclobber $reg" in def LDDRdPtrQ
1402      : FSTDLDD<0,
1403                (outs GPR8
1404                 : $reg),
1405                (ins memri
1406                 : $memri),
1407                "ldd\t$reg, $memri", [(set i8
1408                                       : $reg, (load addr
1409                                                : $memri))]>,
1410      Requires<[HasSRAM, HasNonTinyEncoding]>;
1411
1412  // LDDW Rd+1:Rd, P+q
1413  //
1414  // Expands to:
1415  //   ldd Rd,   P+q
1416  //   ldd Rd+1, P+q+1
1417  // On reduced tiny cores, this instruction expands to:
1418  //   subiw P,    -q
1419  //   ld    Rd,   P+
1420  //   ld    Rd+1, P+
1421  //   subiw P,    q+2
1422  let Constraints = "@earlyclobber $dst" in def LDDWRdPtrQ
1423      : Pseudo<(outs DREGS
1424                : $dst),
1425               (ins memri
1426                : $memri),
1427               "lddw\t$dst, $memri", [(set i16
1428                                       : $dst, (load addr
1429                                                : $memri))]>,
1430      Requires<[HasSRAM]>;
1431
1432  // An identical pseudo instruction to LDDWRdPtrQ, expect restricted to the Y
1433  // register and without the @earlyclobber flag.
1434  //
1435  // Used to work around a bug caused by the register allocator not
1436  // being able to handle the expansion of a COPY into an machine instruction
1437  // that has an earlyclobber flag. This is because the register allocator will
1438  // try expand a copy from a register slot into an earlyclobber instruction.
1439  // Instructions that are earlyclobber need to be in a dedicated earlyclobber
1440  // slot.
1441  //
1442  // This pseudo instruction can be used pre-AVR pseudo expansion in order to
1443  // get a frame index load without directly using earlyclobber instructions.
1444  //
1445  // The pseudo expansion pass trivially expands this into LDDWRdPtrQ.
1446  //
1447  // This instruction may be removed once PR13375 is fixed.
1448  let mayLoad = 1,
1449      hasSideEffects = 0 in def LDDWRdYQ : Pseudo<(outs DREGS
1450                                                   : $dst),
1451                                                  (ins memri
1452                                                   : $memri),
1453                                                  "lddw\t$dst, $memri", []>,
1454      Requires<[HasSRAM]>;
1455}
1456
1457class AtomicLoad<PatFrag Op, RegisterClass DRC, RegisterClass PTRRC>
1458    : Pseudo<(outs DRC
1459              : $rd),
1460             (ins PTRRC
1461              : $rr),
1462             "atomic_op", [(set DRC
1463                            : $rd, (Op i16
1464                                    : $rr))]>;
1465
1466class AtomicStore<PatFrag Op, RegisterClass DRC, RegisterClass PTRRC>
1467    : Pseudo<(outs),
1468             (ins PTRRC
1469              : $rd, DRC
1470              : $rr),
1471             "atomic_op", [(Op i16
1472                            : $rd, DRC
1473                            : $rr)]>;
1474
1475class AtomicLoadOp<PatFrag Op, RegisterClass DRC, RegisterClass PTRRC>
1476    : Pseudo<(outs DRC:$rd),
1477             (ins PTRRC:$rr, DRC:$operand),
1478             "atomic_op", [(set DRC:$rd, (Op i16:$rr, DRC:$operand))]>;
1479
1480// Atomic instructions
1481// ===================
1482//
1483// 8-bit operations can use any pointer register because
1484// they are expanded directly into an LD/ST instruction.
1485//
1486// 16-bit operations use 16-bit load/store postincrement instructions,
1487// which require PTRDISPREGS.
1488
1489def AtomicLoad8 : AtomicLoad<atomic_load_8, GPR8, PTRREGS>;
1490def AtomicLoad16 : AtomicLoad<atomic_load_16, DREGS, PTRDISPREGS>;
1491
1492def AtomicStore8 : AtomicStore<atomic_store_8, GPR8, PTRREGS>;
1493def AtomicStore16 : AtomicStore<atomic_store_16, DREGS, PTRDISPREGS>;
1494
1495class AtomicLoadOp8<PatFrag Op> : AtomicLoadOp<Op, GPR8, PTRREGS>;
1496class AtomicLoadOp16<PatFrag Op> : AtomicLoadOp<Op, DREGS, PTRDISPREGS>;
1497
1498let usesCustomInserter=1 in {
1499  def AtomicLoadAdd8 : AtomicLoadOp8<atomic_load_add_8>;
1500  def AtomicLoadAdd16 : AtomicLoadOp16<atomic_load_add_16>;
1501  def AtomicLoadSub8 : AtomicLoadOp8<atomic_load_sub_8>;
1502  def AtomicLoadSub16 : AtomicLoadOp16<atomic_load_sub_16>;
1503  def AtomicLoadAnd8 : AtomicLoadOp8<atomic_load_and_8>;
1504  def AtomicLoadAnd16 : AtomicLoadOp16<atomic_load_and_16>;
1505  def AtomicLoadOr8 : AtomicLoadOp8<atomic_load_or_8>;
1506  def AtomicLoadOr16 : AtomicLoadOp16<atomic_load_or_16>;
1507  def AtomicLoadXor8 : AtomicLoadOp8<atomic_load_xor_8>;
1508  def AtomicLoadXor16 : AtomicLoadOp16<atomic_load_xor_16>;
1509}
1510def AtomicFence
1511    : Pseudo<(outs), (ins), "atomic_fence", [(atomic_fence timm, timm)]>;
1512
1513// Indirect store from register to data space.
1514def STSKRr : F32DM<0b1, (outs),
1515                   (ins imm16
1516                    : $k, GPR8
1517                    : $rd),
1518                   "sts\t$k, $rd", [(store i8
1519                                     : $rd, imm
1520                                     : $k)]>,
1521             Requires<[HasSRAM, HasNonTinyEncoding]>;
1522
1523// Store from register to data space, which is only available on AVRTiny.
1524def STSKRrTiny : FLDSSTSTINY<0b1, (outs), (ins imm7tiny:$k, LD8:$rd),
1525                             "sts\t$k, $rd", [(store i8:$rd, imm:$k)]>,
1526                 Requires<[HasSRAM, HasTinyEncoding]>;
1527
1528// STSW K+1:K, Rr+1:Rr
1529//
1530// Expands to:
1531// sts Rr+1, (K+1:K) + 1
1532// sts Rr,   (K+1:K)
1533def STSWKRr : Pseudo<(outs),
1534                     (ins i16imm
1535                      : $dst, DREGS
1536                      : $src),
1537                     "stsw\t$dst, $src", [(store i16
1538                                           : $src, imm
1539                                           : $dst)]>,
1540              Requires<[HasSRAM, HasNonTinyEncoding]>;
1541
1542// Indirect stores.
1543// ST P, Rr
1544// Stores the value of Rr into the location addressed by pointer P.
1545def STPtrRr : FSTLD<1, 0b00, (outs),
1546                    (ins LDSTPtrReg
1547                     : $ptrreg, GPR8
1548                     : $reg),
1549                    "st\t$ptrreg, $reg", [(store GPR8
1550                                           : $reg, i16
1551                                           : $ptrreg)]>,
1552              Requires<[HasSRAM]>;
1553
1554// STW P, Rr+1:Rr
1555// Stores the value of Rr into the location addressed by pointer P.
1556//
1557// Expands to:
1558//   st P, Rr
1559//   std P+1, Rr+1
1560// On reduced tiny cores, this instruction expands to:
1561//   st    P+, Rr
1562//   st    P+, Rr+1
1563//   subiw P,  q+2
1564def STWPtrRr : Pseudo<(outs),
1565                      (ins PTRDISPREGS
1566                       : $ptrreg, DREGS
1567                       : $reg),
1568                      "stw\t$ptrreg, $reg", [(store i16
1569                                              : $reg, i16
1570                                              : $ptrreg)]>,
1571               Requires<[HasSRAM]>;
1572
1573// Indirect stores (with postincrement or predecrement).
1574let Constraints = "$ptrreg = $base_wb,@earlyclobber $base_wb" in {
1575
1576  // ST P+, Rr
1577  // Stores the value of Rr into the location addressed by pointer P.
1578  // Post increments P.
1579  def STPtrPiRr : FSTLD<1, 0b01,
1580                        (outs LDSTPtrReg
1581                         : $base_wb),
1582                        (ins LDSTPtrReg
1583                         : $ptrreg, GPR8
1584                         : $reg, i8imm
1585                         : $offs),
1586                        "st\t$ptrreg+, $reg", [(set i16
1587                                                : $base_wb, (post_store GPR8
1588                                                             : $reg, i16
1589                                                             : $ptrreg, imm
1590                                                             : $offs))]>,
1591                  Requires<[HasSRAM]>;
1592
1593  // STW P+, Rr+1:Rr
1594  // Stores the value of Rr into the location addressed by pointer P.
1595  // Post increments P.
1596  //
1597  // Expands to:
1598  // st P+, Rr
1599  // st P+, Rr+1
1600  def STWPtrPiRr : Pseudo<(outs PTRREGS
1601                           : $base_wb),
1602                          (ins PTRREGS
1603                           : $ptrreg, DREGS
1604                           : $trh, i8imm
1605                           : $offs),
1606                          "stw\t$ptrreg+, $trh", [(set PTRREGS
1607                                                   : $base_wb, (post_store DREGS
1608                                                                : $trh, PTRREGS
1609                                                                : $ptrreg, imm
1610                                                                : $offs))]>,
1611                   Requires<[HasSRAM]>;
1612
1613  // ST -P, Rr
1614  // Stores the value of Rr into the location addressed by pointer P.
1615  // Pre decrements P.
1616  def STPtrPdRr : FSTLD<1, 0b10,
1617                        (outs LDSTPtrReg
1618                         : $base_wb),
1619                        (ins LDSTPtrReg
1620                         : $ptrreg, GPR8
1621                         : $reg, i8imm
1622                         : $offs),
1623                        "st\t-$ptrreg, $reg", [(set i16
1624                                                : $base_wb, (pre_store GPR8
1625                                                             : $reg, i16
1626                                                             : $ptrreg, imm
1627                                                             : $offs))]>,
1628                  Requires<[HasSRAM]>;
1629
1630  // STW -P, Rr+1:Rr
1631  // Stores the value of Rr into the location addressed by pointer P.
1632  // Pre decrements P.
1633  //
1634  // Expands to:
1635  // st -P, Rr+1
1636  // st -P, Rr
1637  def STWPtrPdRr : Pseudo<(outs PTRREGS
1638                           : $base_wb),
1639                          (ins PTRREGS
1640                           : $ptrreg, DREGS
1641                           : $reg, i8imm
1642                           : $offs),
1643                          "stw\t-$ptrreg, $reg", [(set PTRREGS
1644                                                   : $base_wb, (pre_store i16
1645                                                                : $reg, i16
1646                                                                : $ptrreg, imm
1647                                                                : $offs))]>,
1648                   Requires<[HasSRAM]>;
1649}
1650
1651// Store indirect with displacement operations.
1652// STD P+q, Rr
1653// Stores the value of Rr into the location addressed by pointer P with a
1654// displacement of q. Does not modify P.
1655def STDPtrQRr : FSTDLDD<1, (outs),
1656                        (ins memri
1657                         : $memri, GPR8
1658                         : $reg),
1659                        "std\t$memri, $reg", [(store i8
1660                                               : $reg, addr
1661                                               : $memri)]>,
1662                Requires<[HasSRAM, HasNonTinyEncoding]>;
1663
1664// STDW P+q, Rr+1:Rr
1665// Stores the value of Rr into the location addressed by pointer P with a
1666// displacement of q. Does not modify P.
1667//
1668// Expands to:
1669//   std P+q,   Rr
1670//   std P+q+1, Rr+1
1671// On reduced tiny cores, this instruction expands to:
1672//   subiw P,  -q
1673//   st    P+, Rr
1674//   st    P+, Rr+1
1675//   subiw P,  q+2
1676def STDWPtrQRr : Pseudo<(outs),
1677                        (ins memri
1678                         : $memri, DREGS
1679                         : $src),
1680                        "stdw\t$memri, $src", [(store i16
1681                                                : $src, addr
1682                                                : $memri)]>,
1683                 Requires<[HasSRAM]>;
1684
1685// Load program memory operations.
1686let canFoldAsLoad = 1, isReMaterializable = 1, mayLoad = 1,
1687    hasSideEffects = 0 in {
1688  let Defs = [R0],
1689      Uses = [R31R30] in def LPM
1690      : F16<0b1001010111001000, (outs), (ins), "lpm", []>,
1691      Requires<[HasLPM]>;
1692
1693  def LPMRdZ : FLPMX<0, 0,
1694                     (outs GPR8
1695                      : $rd),
1696                     (ins ZREG
1697                      : $z),
1698                     "lpm\t$rd, $z", []>,
1699               Requires<[HasLPMX]>;
1700
1701  // Load program memory, while postincrementing the Z register.
1702  let Defs = [R31R30] in {
1703    def LPMRdZPi : FLPMX<0, 1,
1704                         (outs GPR8
1705                          : $rd),
1706                         (ins ZREG
1707                          : $z),
1708                         "lpm\t$rd, $z+", []>,
1709                   Requires<[HasLPMX]>;
1710
1711    let Constraints = "@earlyclobber $dst" in
1712    def LPMWRdZ : Pseudo<(outs DREGS
1713                          : $dst),
1714                         (ins ZREG
1715                          : $z),
1716                         "lpmw\t$dst, $z", []>,
1717                  Requires<[HasLPMX]>;
1718
1719    def LPMWRdZPi : Pseudo<(outs DREGS
1720                            : $dst),
1721                           (ins ZREG
1722                            : $z),
1723                           "lpmw\t$dst, $z+", []>,
1724                    Requires<[HasLPMX]>;
1725  }
1726}
1727
1728// Extended load program memory operations.
1729let mayLoad = 1, hasSideEffects = 0 in {
1730  let Defs = [R0],
1731      Uses = [R31R30] in def ELPM
1732      : F16<0b1001010111011000, (outs), (ins), "elpm", []>,
1733      Requires<[HasELPM]>;
1734
1735  def ELPMRdZ : FLPMX<1, 0, (outs GPR8:$rd), (ins ZREG:$z),
1736                      "elpm\t$rd, $z", []>,
1737                Requires<[HasELPMX]>;
1738
1739  let Defs = [R31R30] in {
1740    def ELPMRdZPi : FLPMX<1, 1, (outs GPR8:$rd), (ins ZREG:$z),
1741                          "elpm\t$rd, $z+", []>,
1742                    Requires<[HasELPMX]>;
1743  }
1744
1745  // These pseudos are combination of the OUT and ELPM instructions.
1746  let Defs = [R31R30], hasSideEffects = 1 in {
1747    def ELPMBRdZ : Pseudo<(outs GPR8:$dst), (ins ZREG:$z, LD8:$p),
1748                          "elpmb\t$dst, $z, $p", []>,
1749                   Requires<[HasELPMX]>;
1750
1751    let Constraints = "@earlyclobber $dst" in
1752    def ELPMWRdZ : Pseudo<(outs DREGS:$dst), (ins ZREG:$z, LD8:$p),
1753                          "elpmw\t$dst, $z, $p", []>,
1754                   Requires<[HasELPMX]>;
1755
1756    def ELPMBRdZPi : Pseudo<(outs GPR8:$dst), (ins ZREG:$z, LD8:$p),
1757                            "elpmb\t$dst, $z+, $p", []>,
1758                     Requires<[HasELPMX]>;
1759
1760    def ELPMWRdZPi : Pseudo<(outs DREGS:$dst), (ins ZREG:$z, LD8:$p),
1761                            "elpmw\t$dst, $z+, $p", []>,
1762                     Requires<[HasELPMX]>;
1763  }
1764}
1765
1766// Store program memory operations.
1767let Uses = [R1, R0] in {
1768  let Uses = [R31R30, R1, R0] in def SPM
1769      : F16<0b1001010111101000, (outs), (ins), "spm", []>,
1770      Requires<[HasSPM]>;
1771
1772  let Defs = [R31R30] in def SPMZPi : F16<0b1001010111111000, (outs),
1773                                          (ins ZREG
1774                                           : $z),
1775                                          "spm $z+", []>,
1776      Requires<[HasSPMX]>;
1777}
1778
1779// Read data from IO location operations.
1780let canFoldAsLoad = 1, isReMaterializable = 1 in {
1781  def INRdA : FIORdA<(outs GPR8
1782                      : $rd),
1783                     (ins imm_port6
1784                      : $A),
1785                     "in\t$rd, $A", [(set i8
1786                                         : $rd, (load ioaddr8
1787                                                  : $A))]>;
1788
1789  def INWRdA : Pseudo<(outs DREGS
1790                       : $dst),
1791                      (ins imm_port6
1792                       : $src),
1793                      "inw\t$dst, $src", [(set i16
1794                                           : $dst, (load ioaddr16
1795                                                    : $src))]>;
1796}
1797
1798// Write data to IO location operations.
1799def OUTARr : FIOARr<(outs),
1800                    (ins imm_port6
1801                     : $A, GPR8
1802                     : $rr),
1803                    "out\t$A, $rr", [(store i8
1804                                         : $rr, ioaddr8
1805                                         : $A)]>;
1806
1807def OUTWARr : Pseudo<(outs),
1808                     (ins imm_port6
1809                      : $dst, DREGS
1810                      : $src),
1811                     "outw\t$dst, $src", [(store i16
1812                                           : $src, ioaddr16
1813                                           : $dst)]>;
1814
1815// Stack push/pop operations.
1816let Defs = [SP], Uses = [SP], hasSideEffects = 0 in {
1817  // Stack push operations.
1818  let mayStore = 1 in {
1819    def PUSHRr : FRd<0b1001, 0b0011111, (outs),
1820                     (ins GPR8
1821                      : $rd),
1822                     "push\t$rd", []>,
1823                 Requires<[HasSRAM]>;
1824
1825    def PUSHWRr : Pseudo<(outs),
1826                         (ins DREGS
1827                          : $reg),
1828                         "pushw\t$reg", []>,
1829                  Requires<[HasSRAM]>;
1830  }
1831
1832  // Stack pop operations.
1833  let mayLoad = 1 in {
1834    def POPRd : FRd<0b1001, 0b0001111,
1835                    (outs GPR8
1836                     : $rd),
1837                    (ins), "pop\t$rd", []>,
1838                Requires<[HasSRAM]>;
1839
1840    def POPWRd : Pseudo<(outs DREGS
1841                         : $reg),
1842                        (ins), "popw\t$reg", []>,
1843                 Requires<[HasSRAM]>;
1844  }
1845}
1846
1847// Read-Write-Modify (RMW) instructions.
1848def XCHZRd : FZRd<0b100,
1849                  (outs GPR8
1850                   : $rd),
1851                  (ins ZREG
1852                   : $z),
1853                  "xch\t$z, $rd", []>,
1854             Requires<[SupportsRMW]>;
1855
1856def LASZRd : FZRd<0b101,
1857                  (outs GPR8
1858                   : $rd),
1859                  (ins ZREG
1860                   : $z),
1861                  "las\t$z, $rd", []>,
1862             Requires<[SupportsRMW]>;
1863
1864def LACZRd : FZRd<0b110,
1865                  (outs GPR8
1866                   : $rd),
1867                  (ins ZREG
1868                   : $z),
1869                  "lac\t$z, $rd", []>,
1870             Requires<[SupportsRMW]>;
1871
1872def LATZRd : FZRd<0b111,
1873                  (outs GPR8
1874                   : $rd),
1875                  (ins ZREG
1876                   : $z),
1877                  "lat\t$z, $rd", []>,
1878             Requires<[SupportsRMW]>;
1879
1880//===----------------------------------------------------------------------===//
1881// Bit and bit-test instructions
1882//===----------------------------------------------------------------------===//
1883
1884// Bit shift/rotate operations.
1885let Constraints = "$src = $rd", Defs = [SREG] in {
1886  // 8-bit LSL is an alias of ADD Rd, Rd
1887
1888  def LSLWRd : Pseudo<(outs DREGS
1889                       : $rd),
1890                      (ins DREGS
1891                       : $src),
1892                      "lslw\t$rd",
1893                      [(set i16
1894                        : $rd, (AVRlsl i16
1895                                : $src)),
1896                       (implicit SREG)]>;
1897
1898  def LSLWHiRd : Pseudo<(outs DREGS:$rd), (ins DREGS:$src), "lslwhi\t$rd",
1899                        [(set i16:$rd, (AVRlslhi i16:$src)), (implicit SREG)]>;
1900
1901  def LSLWNRd : Pseudo<(outs DLDREGS
1902                        : $rd),
1903                       (ins DREGS
1904                        : $src, imm16
1905                        : $bits),
1906                       "lslwn\t$rd, $bits", [
1907                         (set i16
1908                          : $rd, (AVRlslwn i16
1909                                  : $src, imm
1910                                  : $bits)),
1911                         (implicit SREG)
1912                       ]>;
1913
1914  def LSLBNRd : Pseudo<(outs LD8
1915                        : $rd),
1916                       (ins GPR8
1917                        : $src, imm_ldi8
1918                        : $bits),
1919                       "lslbn\t$rd, $bits", [
1920                         (set i8
1921                          : $rd, (AVRlslbn i8
1922                                  : $src, imm
1923                                  : $bits)),
1924                         (implicit SREG)
1925                       ]>;
1926
1927  def LSRRd
1928      : FRd<0b1001, 0b0100110,
1929            (outs GPR8
1930             : $rd),
1931            (ins GPR8
1932             : $src),
1933            "lsr\t$rd", [(set i8
1934                          : $rd, (AVRlsr i8
1935                                  : $src)),
1936                         (implicit SREG)]>;
1937
1938  def LSRWRd : Pseudo<(outs DREGS
1939                       : $rd),
1940                      (ins DREGS
1941                       : $src),
1942                      "lsrw\t$rd",
1943                      [(set i16
1944                        : $rd, (AVRlsr i16
1945                                : $src)),
1946                       (implicit SREG)]>;
1947
1948  def LSRWLoRd : Pseudo<(outs DREGS:$rd), (ins DREGS:$src), "lsrwlo\t$rd",
1949                        [(set i16:$rd, (AVRlsrlo i16:$src)), (implicit SREG)]>;
1950
1951  def LSRWNRd : Pseudo<(outs DLDREGS
1952                        : $rd),
1953                       (ins DREGS
1954                        : $src, imm16
1955                        : $bits),
1956                       "lsrwn\t$rd, $bits", [
1957                         (set i16
1958                          : $rd, (AVRlsrwn i16
1959                                  : $src, imm
1960                                  : $bits)),
1961                         (implicit SREG)
1962                       ]>;
1963
1964  def LSRBNRd : Pseudo<(outs LD8
1965                        : $rd),
1966                       (ins GPR8
1967                        : $src, imm_ldi8
1968                        : $bits),
1969                       "lsrbn\t$rd, $bits", [
1970                         (set i8
1971                          : $rd, (AVRlsrbn i8
1972                                  : $src, imm
1973                                  : $bits)),
1974                         (implicit SREG)
1975                       ]>;
1976
1977  def ASRRd
1978      : FRd<0b1001, 0b0100101,
1979            (outs GPR8
1980             : $rd),
1981            (ins GPR8
1982             : $src),
1983            "asr\t$rd", [(set i8
1984                          : $rd, (AVRasr i8
1985                                  : $src)),
1986                         (implicit SREG)]>;
1987
1988  def ASRWNRd : Pseudo<(outs DREGS
1989                        : $rd),
1990                       (ins DREGS
1991                        : $src, imm16
1992                        : $bits),
1993                       "asrwn\t$rd, $bits", [
1994                         (set i16
1995                          : $rd, (AVRasrwn i16
1996                                  : $src, imm
1997                                  : $bits)),
1998                         (implicit SREG)
1999                       ]>;
2000
2001  def ASRBNRd : Pseudo<(outs LD8
2002                        : $rd),
2003                       (ins GPR8
2004                        : $src, imm_ldi8
2005                        : $bits),
2006                       "asrbn\t$rd, $bits", [
2007                         (set i8
2008                          : $rd, (AVRasrbn i8
2009                                  : $src, imm
2010                                  : $bits)),
2011                         (implicit SREG)
2012                       ]>;
2013
2014  def ASRWRd : Pseudo<(outs DREGS
2015                       : $rd),
2016                      (ins DREGS
2017                       : $src),
2018                      "asrw\t$rd",
2019                      [(set i16
2020                        : $rd, (AVRasr i16
2021                                : $src)),
2022                       (implicit SREG)]>;
2023
2024  def ASRWLoRd : Pseudo<(outs DREGS:$rd), (ins DREGS:$src), "asrwlo\t$rd",
2025                        [(set i16:$rd, (AVRasrlo i16:$src)), (implicit SREG)]>;
2026
2027  let hasSideEffects=0 in
2028  def ROLBRd : Pseudo<(outs GPR8
2029                       : $rd),
2030                      (ins GPR8:$src, GPR8:$zero),
2031                      "rolb\t$rd",
2032                      []>;
2033
2034  def RORBRd : Pseudo<(outs GPR8
2035                       : $rd),
2036                      (ins GPR8
2037                       : $src),
2038                      "rorb\t$rd",
2039                      [(set i8
2040                        : $rd, (AVRror i8
2041                                : $src)),
2042                       (implicit SREG)]>;
2043
2044  // Bit rotate operations.
2045  let Uses = [SREG] in {
2046
2047    def ROLWRd
2048        : Pseudo<(outs DREGS
2049                  : $rd),
2050                 (ins DREGS
2051                  : $src),
2052                 "rolw\t$rd",
2053                 [(set i16
2054                   : $rd, (AVRrol i16
2055                           : $src)),
2056                  (implicit SREG)]>;
2057
2058    def RORRd : FRd<0b1001, 0b0100111,
2059                    (outs GPR8
2060                     : $rd),
2061                    (ins GPR8
2062                     : $src),
2063                    "ror\t$rd", []>;
2064
2065    def RORWRd
2066        : Pseudo<(outs DREGS
2067                  : $rd),
2068                 (ins DREGS
2069                  : $src),
2070                 "rorw\t$rd",
2071                 [(set i16
2072                   : $rd, (AVRror i16
2073                           : $src)),
2074                  (implicit SREG)]>;
2075  }
2076}
2077
2078// SWAP Rd
2079// Swaps the high and low nibbles in a register.
2080let Constraints =
2081    "$src = $rd" in def SWAPRd : FRd<0b1001, 0b0100010,
2082                                     (outs GPR8
2083                                      : $rd),
2084                                     (ins GPR8
2085                                      : $src),
2086                                     "swap\t$rd", [(set i8
2087                                                    : $rd, (AVRSwap i8
2088                                                            : $src))]>;
2089
2090// IO register bit set/clear operations.
2091//: TODO: add patterns when popcount(imm)==2 to be expanded with 2 sbi/cbi
2092// instead of in+ori+out which requires one more instr.
2093def SBIAb : FIOBIT<0b10, (outs),
2094                   (ins imm_port5
2095                    : $addr, i8imm
2096                    : $b),
2097                   "sbi\t$addr, $b", [(store(or(i8(load lowioaddr8
2098                                                     : $addr)),
2099                                               iobitpos8
2100                                               : $b),
2101                                         lowioaddr8
2102                                         : $addr)]>;
2103
2104def CBIAb : FIOBIT<0b00, (outs),
2105                   (ins imm_port5
2106                    : $addr, i8imm
2107                    : $b),
2108                   "cbi\t$addr, $b", [(store(and(i8(load lowioaddr8
2109                                                      : $addr)),
2110                                               iobitposn8
2111                                               : $b),
2112                                         lowioaddr8
2113                                         : $addr)]>;
2114
2115// Status register bit load/store operations.
2116let Defs = [SREG] in def BST : FRdB<0b01, (outs),
2117                                    (ins GPR8
2118                                     : $rd, i8imm
2119                                     : $b),
2120                                    "bst\t$rd, $b", []>;
2121
2122let Constraints = "$src = $rd",
2123    Uses = [SREG] in def BLD : FRdB<0b00,
2124                                    (outs GPR8
2125                                     : $rd),
2126                                    (ins GPR8
2127                                     : $src, i8imm
2128                                     : $b),
2129                                    "bld\t$rd, $b", []>;
2130
2131def CBR : InstAlias<"cbr\t$rd, $k", (ANDIRdK LD8 : $rd, imm_com8 : $k), 0>;
2132
2133// CLR Rd
2134// Alias for EOR Rd, Rd
2135// -------------
2136// Clears all bits in a register.
2137def CLR : InstAlias<"clr\t$rd", (EORRdRr GPR8 : $rd, GPR8 : $rd)>;
2138
2139// LSL Rd
2140// Alias for ADD Rd, Rd
2141// --------------
2142// Logical shift left one bit.
2143def LSL : InstAlias<"lsl\t$rd", (ADDRdRr GPR8 : $rd, GPR8 : $rd)>;
2144
2145def ROL : InstAlias<"rol\t$rd", (ADCRdRr GPR8 : $rd, GPR8 : $rd)>;
2146
2147// SER Rd
2148// Alias for LDI Rd, 0xff
2149// ---------
2150// Sets all bits in a register.
2151def : InstAlias<"ser\t$rd", (LDIRdK LD8 : $rd, 0xff), 0>;
2152
2153let hasSideEffects=1 in {
2154  let Defs = [SREG] in def BSETs : FS<0,
2155                                      (outs),
2156                                      (ins i8imm:$s),
2157                                      "bset\t$s", []>;
2158
2159  let Defs = [SREG] in def BCLRs : FS<1,
2160                                      (outs),
2161                                      (ins i8imm:$s),
2162                                      "bclr\t$s", []>;
2163}
2164
2165// Set/clear aliases for the carry (C) status flag (bit 0).
2166def : InstAlias<"sec", (BSETs 0)>;
2167def : InstAlias<"clc", (BCLRs 0)>;
2168
2169// Set/clear aliases for the zero (Z) status flag (bit 1).
2170def : InstAlias<"sez", (BSETs 1)>;
2171def : InstAlias<"clz", (BCLRs 1)>;
2172
2173// Set/clear aliases for the negative (N) status flag (bit 2).
2174def : InstAlias<"sen", (BSETs 2)>;
2175def : InstAlias<"cln", (BCLRs 2)>;
2176
2177// Set/clear aliases for the overflow (V) status flag (bit 3).
2178def : InstAlias<"sev", (BSETs 3)>;
2179def : InstAlias<"clv", (BCLRs 3)>;
2180
2181// Set/clear aliases for the signed (S) status flag (bit 4).
2182def : InstAlias<"ses", (BSETs 4)>;
2183def : InstAlias<"cls", (BCLRs 4)>;
2184
2185// Set/clear aliases for the half-carry (H) status flag (bit 5).
2186def : InstAlias<"seh", (BSETs 5)>;
2187def : InstAlias<"clh", (BCLRs 5)>;
2188
2189// Set/clear aliases for the T status flag (bit 6).
2190def : InstAlias<"set", (BSETs 6)>;
2191def : InstAlias<"clt", (BCLRs 6)>;
2192
2193// Set/clear aliases for the interrupt (I) status flag (bit 7).
2194def : InstAlias<"sei", (BSETs 7)>;
2195def : InstAlias<"cli", (BCLRs 7)>;
2196
2197//===----------------------------------------------------------------------===//
2198// Special/Control instructions
2199//===----------------------------------------------------------------------===//
2200
2201// BREAK
2202// Breakpoint instruction
2203// ---------
2204// <|1001|0101|1001|1000>
2205def BREAK : F16<0b1001010110011000, (outs), (ins), "break", []>,
2206            Requires<[HasBREAK]>;
2207
2208// NOP
2209// No-operation instruction
2210// ---------
2211// <|0000|0000|0000|0000>
2212def NOP : F16<0b0000000000000000, (outs), (ins), "nop", []>;
2213
2214// SLEEP
2215// Sleep instruction
2216// ---------
2217// <|1001|0101|1000|1000>
2218def SLEEP : F16<0b1001010110001000, (outs), (ins), "sleep", []>;
2219
2220// WDR
2221// Watchdog reset
2222// ---------
2223// <|1001|0101|1010|1000>
2224def WDR : F16<0b1001010110101000, (outs), (ins), "wdr", []>;
2225
2226//===----------------------------------------------------------------------===//
2227// Pseudo instructions for later expansion
2228//===----------------------------------------------------------------------===//
2229
2230//: TODO: Optimize this for wider types AND optimize the following code
2231//       compile int foo(char a, char b, char c, char d) {return d+b;}
2232//       looks like a missed sext_inreg opportunity.
2233def SEXT
2234    : ExtensionPseudo<(outs DREGS
2235                       : $dst),
2236                      (ins GPR8
2237                       : $src),
2238                      "sext\t$dst, $src",
2239                      [(set i16
2240                        : $dst, (sext i8
2241                                 : $src)),
2242                       (implicit SREG)]>;
2243
2244def ZEXT
2245    : ExtensionPseudo<(outs DREGS
2246                       : $dst),
2247                      (ins GPR8
2248                       : $src),
2249                      "zext\t$dst, $src",
2250                      [(set i16
2251                        : $dst, (zext i8
2252                                 : $src)),
2253                       (implicit SREG)]>;
2254
2255// This pseudo gets expanded into a movw+adiw thus it clobbers SREG.
2256let Defs = [SREG],
2257    hasSideEffects = 0 in def FRMIDX : Pseudo<(outs DLDREGS
2258                                               : $dst),
2259                                              (ins DLDREGS
2260                                               : $src, i16imm
2261                                               : $src2),
2262                                              "frmidx\t$dst, $src, $src2", []>;
2263
2264// This pseudo is either converted to a regular store or a push which clobbers
2265// SP.
2266def STDSPQRr : StorePseudo<(outs),
2267                           (ins memspi
2268                            : $dst, GPR8
2269                            : $src),
2270                           "stdstk\t$dst, $src", [(store i8
2271                                                   : $src, addr
2272                                                   : $dst)]>;
2273
2274// This pseudo is either converted to a regular store or a push which clobbers
2275// SP.
2276def STDWSPQRr : StorePseudo<(outs),
2277                            (ins memspi
2278                             : $dst, DREGS
2279                             : $src),
2280                            "stdwstk\t$dst, $src", [(store i16
2281                                                     : $src, addr
2282                                                     : $dst)]>;
2283
2284// SP read/write pseudos.
2285let hasSideEffects = 0 in {
2286  let Uses = [SP] in def SPREAD : Pseudo<(outs DREGS
2287                                          : $dst),
2288                                         (ins GPRSP
2289                                          : $src),
2290                                         "spread\t$dst, $src", []>;
2291
2292  let Defs = [SP] in def SPWRITE : Pseudo<(outs GPRSP
2293                                           : $dst),
2294                                          (ins DREGS
2295                                           : $src),
2296                                          "spwrite\t$dst, $src", []>;
2297}
2298
2299def Select8 : SelectPseudo<(outs GPR8
2300                            : $dst),
2301                           (ins GPR8
2302                            : $src, GPR8
2303                            : $src2, i8imm
2304                            : $cc),
2305                           "# Select8 PSEUDO", [(set i8
2306                                                 : $dst, (AVRselectcc i8
2307                                                          : $src, i8
2308                                                          : $src2, imm
2309                                                          : $cc))]>;
2310
2311def Select16 : SelectPseudo<(outs DREGS
2312                             : $dst),
2313                            (ins DREGS
2314                             : $src, DREGS
2315                             : $src2, i8imm
2316                             : $cc),
2317                            "# Select16 PSEUDO", [(set i16
2318                                                   : $dst, (AVRselectcc i16
2319                                                            : $src, i16
2320                                                            : $src2, imm
2321                                                            : $cc))]>;
2322
2323def Lsl8 : ShiftPseudo<(outs GPR8
2324                        : $dst),
2325                       (ins GPR8
2326                        : $src, GPR8
2327                        : $cnt),
2328                       "# Lsl8 PSEUDO", [(set i8
2329                                          : $dst, (AVRlslLoop i8
2330                                                   : $src, i8
2331                                                   : $cnt))]>;
2332
2333def Lsl16 : ShiftPseudo<(outs DREGS
2334                         : $dst),
2335                        (ins DREGS
2336                         : $src, GPR8
2337                         : $cnt),
2338                        "# Lsl16 PSEUDO", [(set i16
2339                                            : $dst, (AVRlslLoop i16
2340                                                     : $src, i8
2341                                                     : $cnt))]>;
2342
2343def Lsl32 : ShiftPseudo<(outs DREGS:$dstlo, DREGS:$dsthi),
2344                        (ins DREGS:$srclo, DREGS:$srchi, i8imm:$cnt),
2345                        "# Lsl32 PSEUDO",
2346                        [(set i16:$dstlo, i16:$dsthi, (AVRlslw i16:$srclo, i16:$srchi, i8:$cnt))]>;
2347
2348def Lsr8 : ShiftPseudo<(outs GPR8
2349                        : $dst),
2350                       (ins GPR8
2351                        : $src, GPR8
2352                        : $cnt),
2353                       "# Lsr8 PSEUDO", [(set i8
2354                                          : $dst, (AVRlsrLoop i8
2355                                                   : $src, i8
2356                                                   : $cnt))]>;
2357
2358def Lsr16 : ShiftPseudo<(outs DREGS
2359                         : $dst),
2360                        (ins DREGS
2361                         : $src, GPR8
2362                         : $cnt),
2363                        "# Lsr16 PSEUDO", [(set i16
2364                                            : $dst, (AVRlsrLoop i16
2365                                                     : $src, i8
2366                                                     : $cnt))]>;
2367
2368def Lsr32 : ShiftPseudo<(outs DREGS:$dstlo, DREGS:$dsthi),
2369                        (ins DREGS:$srclo, DREGS:$srchi, i8imm:$cnt),
2370                        "# Lsr32 PSEUDO",
2371                        [(set i16:$dstlo, i16:$dsthi, (AVRlsrw i16:$srclo, i16:$srchi, i8:$cnt))]>;
2372
2373def Rol8 : ShiftPseudo<(outs GPR8
2374                        : $dst),
2375                       (ins GPR8
2376                        : $src, GPR8
2377                        : $cnt),
2378                       "# Rol8 PSEUDO", [(set i8
2379                                          : $dst, (AVRrolLoop i8
2380                                                   : $src, i8
2381                                                   : $cnt))]>;
2382
2383def Rol16 : ShiftPseudo<(outs DREGS
2384                         : $dst),
2385                        (ins DREGS
2386                         : $src, GPR8
2387                         : $cnt),
2388                        "# Rol16 PSEUDO", [(set i16
2389                                            : $dst, (AVRrolLoop i16
2390                                                     : $src, i8
2391                                                     : $cnt))]>;
2392
2393def Ror8 : ShiftPseudo<(outs GPR8
2394                        : $dst),
2395                       (ins GPR8
2396                        : $src, GPR8
2397                        : $cnt),
2398                       "# Ror8 PSEUDO", [(set i8
2399                                          : $dst, (AVRrorLoop i8
2400                                                   : $src, i8
2401                                                   : $cnt))]>;
2402
2403def Ror16 : ShiftPseudo<(outs DREGS
2404                         : $dst),
2405                        (ins DREGS
2406                         : $src, GPR8
2407                         : $cnt),
2408                        "# Ror16 PSEUDO", [(set i16
2409                                            : $dst, (AVRrorLoop i16
2410                                                     : $src, i8
2411                                                     : $cnt))]>;
2412
2413def Asr8 : ShiftPseudo<(outs GPR8
2414                        : $dst),
2415                       (ins GPR8
2416                        : $src, GPR8
2417                        : $cnt),
2418                       "# Asr8 PSEUDO", [(set i8
2419                                          : $dst, (AVRasrLoop i8
2420                                                   : $src, i8
2421                                                   : $cnt))]>;
2422
2423def Asr16 : ShiftPseudo<(outs DREGS
2424                         : $dst),
2425                        (ins DREGS
2426                         : $src, GPR8
2427                         : $cnt),
2428                        "# Asr16 PSEUDO", [(set i16
2429                                            : $dst, (AVRasrLoop i16
2430                                                     : $src, i8
2431                                                     : $cnt))]>;
2432
2433def Asr32 : ShiftPseudo<(outs DREGS:$dstlo, DREGS:$dsthi),
2434                        (ins DREGS:$srclo, DREGS:$srchi, i8imm:$cnt),
2435                        "# Asr32 PSEUDO",
2436                        [(set i16:$dstlo, i16:$dsthi, (AVRasrw i16:$srclo, i16:$srchi, i8:$cnt))]>;
2437
2438// lowered to a copy from the zero register.
2439let usesCustomInserter=1 in
2440def CopyZero : Pseudo<(outs GPR8:$rd), (ins), "clrz\t$rd", [(set i8:$rd, 0)]>;
2441
2442//===----------------------------------------------------------------------===//
2443// Non-Instruction Patterns
2444//===----------------------------------------------------------------------===//
2445
2446//: TODO: look in x86InstrCompiler.td for odd encoding trick related to
2447// add x, 128 -> sub x, -128. Clang is emitting an eor for this (ldi+eor)
2448
2449// the add instruction always writes the carry flag
2450def : Pat<(addc i8 : $src, i8 : $src2), (ADDRdRr i8 : $src, i8 : $src2)>;
2451def : Pat<(addc DREGS
2452           : $src, DREGS
2453           : $src2),
2454          (ADDWRdRr DREGS
2455           : $src, DREGS
2456           : $src2)>;
2457
2458// all sub instruction variants always writes the carry flag
2459def : Pat<(subc i8 : $src, i8 : $src2), (SUBRdRr i8 : $src, i8 : $src2)>;
2460def : Pat<(subc i16 : $src, i16 : $src2), (SUBWRdRr i16 : $src, i16 : $src2)>;
2461def : Pat<(subc i8 : $src, imm : $src2), (SUBIRdK i8 : $src, imm : $src2)>;
2462def : Pat<(subc i16 : $src, imm : $src2), (SUBIWRdK i16 : $src, imm : $src2)>;
2463
2464// These patterns convert add (x, -imm) to sub (x, imm) since we dont have
2465// any add with imm instructions. Also take care of the adiw/sbiw instructions.
2466def : Pat<(add i16
2467           : $src1, imm0_63_neg
2468           : $src2),
2469          (SBIWRdK i16
2470           : $src1, (imm0_63_neg
2471                     : $src2))>,
2472          Requires<[HasADDSUBIW]>;
2473def : Pat<(add i16
2474           : $src1, imm
2475           : $src2),
2476          (SUBIWRdK i16
2477           : $src1, (imm16_neg_XFORM imm
2478                     : $src2))>;
2479def : Pat<(addc i16
2480           : $src1, imm
2481           : $src2),
2482          (SUBIWRdK i16
2483           : $src1, (imm16_neg_XFORM imm
2484                     : $src2))>;
2485
2486def : Pat<(add i8
2487           : $src1, imm
2488           : $src2),
2489          (SUBIRdK i8
2490           : $src1, (imm8_neg_XFORM imm
2491                     : $src2))>;
2492def : Pat<(addc i8
2493           : $src1, imm
2494           : $src2),
2495          (SUBIRdK i8
2496           : $src1, (imm8_neg_XFORM imm
2497                     : $src2))>;
2498def : Pat<(adde i8
2499           : $src1, imm
2500           : $src2),
2501          (SBCIRdK i8
2502           : $src1, (imm8_neg_XFORM imm
2503                     : $src2))>;
2504
2505// Emit NEGWRd with an extra zero register operand.
2506def : Pat<(ineg i16:$src),
2507          (NEGWRd i16:$src, (CopyZero))>;
2508
2509// Calls.
2510let Predicates = [HasJMPCALL] in {
2511  def : Pat<(AVRcall(i16 tglobaladdr:$dst)), (CALLk tglobaladdr:$dst)>;
2512  def : Pat<(AVRcall(i16 texternalsym:$dst)), (CALLk texternalsym:$dst)>;
2513}
2514def : Pat<(AVRcall(i16 tglobaladdr:$dst)), (RCALLk tglobaladdr:$dst)>;
2515def : Pat<(AVRcall(i16 texternalsym:$dst)), (RCALLk texternalsym:$dst)>;
2516
2517// `anyext`
2518def : Pat<(i16(anyext i8
2519               : $src)),
2520          (INSERT_SUBREG(i16(IMPLICIT_DEF)), i8
2521           : $src, sub_lo)>;
2522
2523// `trunc`
2524def : Pat<(i8(trunc i16 : $src)), (EXTRACT_SUBREG i16 : $src, sub_lo)>;
2525
2526// sext_inreg
2527def : Pat<(sext_inreg i16
2528           : $src, i8),
2529          (SEXT(i8(EXTRACT_SUBREG i16
2530                   : $src, sub_lo)))>;
2531
2532// GlobalAddress
2533def : Pat<(i16(AVRWrapper tglobaladdr : $dst)), (LDIWRdK tglobaladdr : $dst)>;
2534def : Pat<(add i16
2535           : $src, (AVRWrapper tglobaladdr
2536                    : $src2)),
2537          (SUBIWRdK i16
2538           : $src, tglobaladdr
2539           : $src2)>;
2540def : Pat<(i8(load(AVRWrapper tglobaladdr:$dst))),
2541          (LDSRdK tglobaladdr:$dst)>,
2542          Requires<[HasSRAM, HasNonTinyEncoding]>;
2543def : Pat<(i8(load(AVRWrapper tglobaladdr:$dst))),
2544          (LDSRdKTiny tglobaladdr:$dst)>,
2545          Requires<[HasSRAM, HasTinyEncoding]>;
2546def : Pat<(i16(load(AVRWrapper tglobaladdr:$dst))),
2547          (LDSWRdK tglobaladdr:$dst)>,
2548          Requires<[HasSRAM, HasNonTinyEncoding]>;
2549def : Pat<(store i8:$src, (i16(AVRWrapper tglobaladdr:$dst))),
2550          (STSKRr tglobaladdr:$dst, i8:$src)>,
2551          Requires<[HasSRAM, HasNonTinyEncoding]>;
2552def : Pat<(store i8:$src, (i16(AVRWrapper tglobaladdr:$dst))),
2553          (STSKRrTiny tglobaladdr:$dst, i8:$src)>,
2554          Requires<[HasSRAM, HasTinyEncoding]>;
2555def : Pat<(store i16:$src, (i16(AVRWrapper tglobaladdr:$dst))),
2556          (STSWKRr tglobaladdr:$dst, i16:$src)>,
2557          Requires<[HasSRAM, HasNonTinyEncoding]>;
2558
2559// BlockAddress
2560def : Pat<(i16(AVRWrapper tblockaddress
2561               : $dst)),
2562          (LDIWRdK tblockaddress
2563           : $dst)>;
2564
2565def : Pat<(i8(trunc(AVRlsrwn DLDREGS
2566                    : $src, (i16 8)))),
2567          (EXTRACT_SUBREG DREGS
2568           : $src, sub_hi)>;
2569
2570// :FIXME: DAGCombiner produces an shl node after legalization from these seq:
2571// BR_JT -> (mul x, 2) -> (shl x, 1)
2572def : Pat<(shl i16 : $src1, (i8 1)), (LSLWRd i16 : $src1)>;
2573
2574// Lowering of 'tst' node to 'TST' instruction.
2575// TST is an alias of AND Rd, Rd.
2576def : Pat<(AVRtst i8 : $rd), (ANDRdRr GPR8 : $rd, GPR8 : $rd)>;
2577
2578// Lowering of 'lsl' node to 'LSL' instruction.
2579// LSL is an alias of 'ADD Rd, Rd'
2580def : Pat<(AVRlsl i8 : $rd), (ADDRdRr GPR8 : $rd, GPR8 : $rd)>;
2581