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