Mips16InstrInfo.td revision ffbe432595c78ba28c8a9d200bf92996eed5e5d9
1//===- Mips16InstrInfo.td - Target Description for Mips16  -*- tablegen -*-=//
2//
3//                     The LLVM Compiler Infrastructure
4//
5// This file is distributed under the University of Illinois Open Source
6// License. See LICENSE.TXT for details.
7//
8//===----------------------------------------------------------------------===//
9//
10// This file describes Mips16 instructions.
11//
12//===----------------------------------------------------------------------===//
13//
14//
15// Mips Address
16//
17def addr16 :
18  ComplexPattern<iPTR, 3, "SelectAddr16", [frameindex], [SDNPWantParent]>;
19
20//
21// Address operand
22def mem16 : Operand<i32> {
23  let PrintMethod = "printMemOperand";
24  let MIOperandInfo = (ops CPU16Regs, simm16, CPU16Regs);
25  let EncoderMethod = "getMemEncoding";
26}
27
28def mem16_ea : Operand<i32> {
29  let PrintMethod = "printMemOperandEA";
30  let MIOperandInfo = (ops CPU16Regs, simm16);
31  let EncoderMethod = "getMemEncoding";
32}
33
34//
35//
36// I8 instruction format
37//
38
39class FI816_ins_base<bits<3> _func, string asmstr,
40                     string asmstr2, InstrItinClass itin>:
41  FI816<_func, (outs), (ins simm16:$imm), !strconcat(asmstr, asmstr2),
42        [], itin>;
43
44
45class FI816_SP_ins<bits<3> _func, string asmstr,
46                   InstrItinClass itin>:
47  FI816_ins_base<_func, asmstr, "\t$$sp, $imm # 16 bit inst", itin>;
48
49//
50// RI instruction format
51//
52
53
54class FRI16_ins_base<bits<5> op, string asmstr, string asmstr2,
55                     InstrItinClass itin>:
56  FRI16<op, (outs CPU16Regs:$rx), (ins simm16:$imm),
57        !strconcat(asmstr, asmstr2), [], itin>;
58
59class FRI16_ins<bits<5> op, string asmstr,
60                InstrItinClass itin>:
61  FRI16_ins_base<op, asmstr, "\t$rx, $imm \t# 16 bit inst", itin>;
62
63class FRI16R_ins_base<bits<5> op, string asmstr, string asmstr2,
64                     InstrItinClass itin>:
65  FRI16<op, (outs), (ins CPU16Regs:$rx, simm16:$imm),
66        !strconcat(asmstr, asmstr2), [], itin>;
67
68class FRI16R_ins<bits<5> op, string asmstr,
69                InstrItinClass itin>:
70  FRI16R_ins_base<op, asmstr, "\t$rx, $imm \t# 16 bit inst", itin>;
71
72class F2RI16_ins<bits<5> _op, string asmstr,
73                     InstrItinClass itin>:
74  FRI16<_op, (outs CPU16Regs:$rx), (ins CPU16Regs:$rx_, simm16:$imm),
75        !strconcat(asmstr, "\t$rx, $imm\t# 16 bit inst"), [], itin> {
76  let Constraints = "$rx_ = $rx";
77}
78
79class FRI16_B_ins<bits<5> _op, string asmstr,
80                  InstrItinClass itin>:
81  FRI16<_op, (outs), (ins  CPU16Regs:$rx, brtarget:$imm),
82        !strconcat(asmstr, "\t$rx, $imm  # 16 bit inst"), [], itin>;
83//
84// Compare a register and immediate and place result in CC
85// Implicit use of T8
86//
87// EXT-CCRR Instruction format
88//
89class FEXT_CCRXI16_ins<string asmstr>:
90  MipsPseudo16<(outs CPU16Regs:$cc), (ins CPU16Regs:$rx, simm16:$imm),
91               !strconcat(asmstr, "\t$rx, $imm\n\tmove\t$cc, $$t8"), []> {
92  let isCodeGenOnly=1;
93}
94
95// JAL and JALX instruction format
96//
97class FJAL16_ins<bits<1> _X, string asmstr,
98                 InstrItinClass itin>:
99  FJAL16<_X, (outs), (ins simm20:$imm),
100         !strconcat(asmstr, "\t$imm\n\tnop"),[],
101         itin>  {
102  let isCodeGenOnly=1;
103}
104//
105// EXT-I instruction format
106//
107class FEXT_I16_ins<bits<5> eop, string asmstr, InstrItinClass itin> :
108  FEXT_I16<eop, (outs), (ins brtarget:$imm16),
109           !strconcat(asmstr, "\t$imm16"),[], itin>;
110
111//
112// EXT-I8 instruction format
113//
114
115class FEXT_I816_ins_base<bits<3> _func, string asmstr,
116                         string asmstr2, InstrItinClass itin>:
117  FEXT_I816<_func, (outs), (ins simm16:$imm), !strconcat(asmstr, asmstr2),
118            [], itin>;
119
120class FEXT_I816_ins<bits<3> _func, string asmstr,
121                    InstrItinClass itin>:
122  FEXT_I816_ins_base<_func, asmstr, "\t$imm", itin>;
123
124class FEXT_I816_SP_ins<bits<3> _func, string asmstr,
125                       InstrItinClass itin>:
126      FEXT_I816_ins_base<_func, asmstr, "\t$$sp, $imm", itin>;
127
128//
129// Assembler formats in alphabetical order.
130// Natural and pseudos are mixed together.
131//
132// Compare two registers and place result in CC
133// Implicit use of T8
134//
135// CC-RR Instruction format
136//
137class FCCRR16_ins<string asmstr> :
138  MipsPseudo16<(outs CPU16Regs:$cc), (ins CPU16Regs:$rx, CPU16Regs:$ry),
139               !strconcat(asmstr, "\t$rx, $ry\n\tmove\t$cc, $$t8"), []> {
140  let isCodeGenOnly=1;
141}
142
143//
144// EXT-RI instruction format
145//
146
147class FEXT_RI16_ins_base<bits<5> _op, string asmstr, string asmstr2,
148                         InstrItinClass itin>:
149  FEXT_RI16<_op, (outs CPU16Regs:$rx), (ins simm16:$imm),
150                  !strconcat(asmstr, asmstr2), [], itin>;
151
152class FEXT_RI16_ins<bits<5> _op, string asmstr,
153                    InstrItinClass itin>:
154  FEXT_RI16_ins_base<_op, asmstr, "\t$rx, $imm", itin>;
155
156class FEXT_RI16R_ins_base<bits<5> _op, string asmstr, string asmstr2,
157                         InstrItinClass itin>:
158  FEXT_RI16<_op, (outs ), (ins CPU16Regs:$rx, simm16:$imm),
159                  !strconcat(asmstr, asmstr2), [], itin>;
160
161class FEXT_RI16R_ins<bits<5> _op, string asmstr,
162                    InstrItinClass itin>:
163  FEXT_RI16R_ins_base<_op, asmstr, "\t$rx, $imm", itin>;
164
165class FEXT_RI16_PC_ins<bits<5> _op, string asmstr, InstrItinClass itin>:
166  FEXT_RI16_ins_base<_op, asmstr, "\t$rx, $$pc, $imm", itin>;
167
168class FEXT_RI16_B_ins<bits<5> _op, string asmstr,
169                      InstrItinClass itin>:
170  FEXT_RI16<_op, (outs), (ins  CPU16Regs:$rx, brtarget:$imm),
171            !strconcat(asmstr, "\t$rx, $imm"), [], itin>;
172
173class FEXT_2RI16_ins<bits<5> _op, string asmstr,
174                     InstrItinClass itin>:
175  FEXT_RI16<_op, (outs CPU16Regs:$rx), (ins CPU16Regs:$rx_, simm16:$imm),
176            !strconcat(asmstr, "\t$rx, $imm"), [], itin> {
177  let Constraints = "$rx_ = $rx";
178}
179
180
181// this has an explicit sp argument that we ignore to work around a problem
182// in the compiler
183class FEXT_RI16_SP_explicit_ins<bits<5> _op, string asmstr,
184                                InstrItinClass itin>:
185  FEXT_RI16<_op, (outs CPU16Regs:$rx), (ins CPUSPReg:$ry, simm16:$imm),
186            !strconcat(asmstr, "\t$rx, $imm ( $ry ); "), [], itin>;
187
188//
189// EXT-RRI instruction format
190//
191
192class FEXT_RRI16_mem_ins<bits<5> op, string asmstr, Operand MemOpnd,
193                         InstrItinClass itin>:
194  FEXT_RRI16<op, (outs CPU16Regs:$ry), (ins  MemOpnd:$addr),
195             !strconcat(asmstr, "\t$ry, $addr"), [], itin>;
196
197class FEXT_RRI16_mem2_ins<bits<5> op, string asmstr, Operand MemOpnd,
198                          InstrItinClass itin>:
199  FEXT_RRI16<op, (outs ), (ins  CPU16Regs:$ry, MemOpnd:$addr),
200             !strconcat(asmstr, "\t$ry, $addr"), [], itin>;
201
202//
203//
204// EXT-RRI-A instruction format
205//
206
207class FEXT_RRI_A16_mem_ins<bits<1> op, string asmstr, Operand MemOpnd,
208                           InstrItinClass itin>:
209  FEXT_RRI_A16<op, (outs CPU16Regs:$ry), (ins  MemOpnd:$addr),
210               !strconcat(asmstr, "\t$ry, $addr"), [], itin>;
211
212//
213// EXT-SHIFT instruction format
214//
215class FEXT_SHIFT16_ins<bits<2> _f, string asmstr, InstrItinClass itin>:
216  FEXT_SHIFT16<_f, (outs CPU16Regs:$rx), (ins CPU16Regs:$ry, shamt:$sa),
217               !strconcat(asmstr, "\t$rx, $ry, $sa"), [], itin>;
218
219//
220// EXT-T8I8
221//
222class FEXT_T8I816_ins<string asmstr, string asmstr2>:
223  MipsPseudo16<(outs),
224               (ins CPU16Regs:$rx, CPU16Regs:$ry, brtarget:$imm),
225               !strconcat(asmstr2, !strconcat("\t$rx, $ry\n\t",
226               !strconcat(asmstr, "\t$imm"))),[]> {
227  let isCodeGenOnly=1;
228}
229
230//
231// EXT-T8I8I
232//
233class FEXT_T8I8I16_ins<string asmstr, string asmstr2>:
234  MipsPseudo16<(outs),
235               (ins CPU16Regs:$rx, simm16:$imm, brtarget:$targ),
236               !strconcat(asmstr2, !strconcat("\t$rx, $imm\n\t",
237               !strconcat(asmstr, "\t$targ"))), []> {
238  let isCodeGenOnly=1;
239}
240//
241
242
243//
244// I8_MOVR32 instruction format (used only by the MOVR32 instructio
245//
246class FI8_MOVR3216_ins<string asmstr, InstrItinClass itin>:
247       FI8_MOVR3216<(outs CPU16Regs:$rz), (ins CPURegs:$r32),
248       !strconcat(asmstr,  "\t$rz, $r32"), [], itin>;
249
250//
251// I8_MOV32R instruction format (used only by MOV32R instruction)
252//
253
254class FI8_MOV32R16_ins<string asmstr, InstrItinClass itin>:
255  FI8_MOV32R16<(outs CPURegs:$r32), (ins CPU16Regs:$rz),
256               !strconcat(asmstr,  "\t$r32, $rz"), [], itin>;
257
258//
259// This are pseudo formats for multiply
260// This first one can be changed to non pseudo now.
261//
262// MULT
263//
264class FMULT16_ins<string asmstr, InstrItinClass itin> :
265  MipsPseudo16<(outs), (ins CPU16Regs:$rx, CPU16Regs:$ry),
266               !strconcat(asmstr, "\t$rx, $ry"), []>;
267
268//
269// MULT-LO
270//
271class FMULT16_LO_ins<string asmstr, InstrItinClass itin> :
272  MipsPseudo16<(outs CPU16Regs:$rz), (ins CPU16Regs:$rx, CPU16Regs:$ry),
273               !strconcat(asmstr, "\t$rx, $ry\n\tmflo\t$rz"), []> {
274  let isCodeGenOnly=1;
275}
276
277//
278// RR-type instruction format
279//
280
281class FRR16_ins<bits<5> f, string asmstr, InstrItinClass itin> :
282  FRR16<f, (outs CPU16Regs:$rx), (ins CPU16Regs:$ry),
283        !strconcat(asmstr, "\t$rx, $ry"), [], itin> {
284}
285
286class FRRTR16_ins<string asmstr> :
287  MipsPseudo16<(outs CPU16Regs:$rz), (ins CPU16Regs:$rx, CPU16Regs:$ry),
288               !strconcat(asmstr, "\t$rx, $ry\n\tmove\t$rz, $$t8"), []> ;
289
290//
291// maybe refactor but need a $zero as a dummy first parameter
292//
293class FRR16_div_ins<bits<5> f, string asmstr, InstrItinClass itin> :
294  FRR16<f, (outs ), (ins CPU16Regs:$rx, CPU16Regs:$ry),
295        !strconcat(asmstr, "\t$$zero, $rx, $ry"), [], itin> ;
296
297class FUnaryRR16_ins<bits<5> f, string asmstr, InstrItinClass itin> :
298  FRR16<f, (outs CPU16Regs:$rx), (ins CPU16Regs:$ry),
299        !strconcat(asmstr, "\t$rx, $ry"), [], itin> ;
300
301
302class FRR16_M_ins<bits<5> f, string asmstr,
303                  InstrItinClass itin> :
304  FRR16<f, (outs CPU16Regs:$rx), (ins),
305        !strconcat(asmstr, "\t$rx"), [], itin>;
306
307class FRxRxRy16_ins<bits<5> f, string asmstr,
308                    InstrItinClass itin> :
309  FRR16<f, (outs CPU16Regs:$rz), (ins CPU16Regs:$rx, CPU16Regs:$ry),
310            !strconcat(asmstr, "\t$rz, $ry"),
311            [], itin> {
312  let Constraints = "$rx = $rz";
313}
314
315let rx=0 in
316class FRR16_JALRC_RA_only_ins<bits<1> nd_, bits<1> l_,
317                              string asmstr, InstrItinClass itin>:
318  FRR16_JALRC<nd_, l_, 1, (outs), (ins), !strconcat(asmstr, "\t $$ra"),
319              [], itin> ;
320
321
322class FRR16_JALRC_ins<bits<1> nd, bits<1> l, bits<1> ra,
323                      string asmstr, InstrItinClass itin>:
324  FRR16_JALRC<nd, l, ra, (outs), (ins CPU16Regs:$rx),
325              !strconcat(asmstr, "\t $rx"), [], itin> ;
326
327//
328// RRR-type instruction format
329//
330
331class FRRR16_ins<bits<2> _f, string asmstr,  InstrItinClass itin> :
332  FRRR16<_f, (outs CPU16Regs:$rz), (ins CPU16Regs:$rx, CPU16Regs:$ry),
333         !strconcat(asmstr, "\t$rz, $rx, $ry"), [], itin>;
334
335//
336// These Sel patterns support the generation of conditional move
337// pseudo instructions.
338//
339// The nomenclature uses the components making up the pseudo and may
340// be a bit counter intuitive when compared with the end result we seek.
341// For example using a bqez in the example directly below results in the
342// conditional move being done if the tested register is not zero.
343// I considered in easier to check by keeping the pseudo consistent with
344// it's components but it could have been done differently.
345//
346// The simplest case is when can test and operand directly and do the
347// conditional move based on a simple mips16 conditional
348//  branch instruction.
349// for example:
350// if $op == beqz or bnez:
351//
352// $op1 $rt, .+4
353// move $rd, $rs
354//
355// if $op == beqz, then if $rt != 0, then the conditional assignment
356// $rd = $rs is done.
357
358// if $op == bnez, then if $rt == 0, then the conditional assignment
359// $rd = $rs is done.
360//
361// So this pseudo class only has one operand, i.e. op
362//
363class Sel<string op>:
364  MipsPseudo16<(outs CPU16Regs:$rd_), (ins CPU16Regs:$rd, CPU16Regs:$rs,
365               CPU16Regs:$rt),
366               !strconcat(op, "\t$rt, .+4\n\t\n\tmove $rd, $rs"), []> {
367  //let isCodeGenOnly=1;
368  let Constraints = "$rd = $rd_";
369  let usesCustomInserter = 1;
370}
371
372//
373// The next two instruction classes allow for an operand which tests
374// two operands and returns a value in register T8 and
375//then does a conditional branch based on the value of T8
376//
377
378// op2 can be cmpi or slti/sltiu
379// op1 can bteqz or btnez
380// the operands for op2 are a register and a signed constant
381//
382// $op2 $t, $imm  ;test register t and branch conditionally
383// $op1 .+4       ;op1 is a conditional branch
384// move $rd, $rs
385//
386//
387class SeliT<string op1, string op2>:
388  MipsPseudo16<(outs CPU16Regs:$rd_), (ins CPU16Regs:$rd, CPU16Regs:$rs,
389                                       CPU16Regs:$rl, simm16:$imm),
390               !strconcat(op2,
391               !strconcat("\t$rl, $imm\n\t",
392               !strconcat(op1, "\t.+4\n\tmove $rd, $rs"))), []> {
393  let isCodeGenOnly=1;
394  let Constraints = "$rd = $rd_";
395}
396
397//
398// op2 can be cmp or slt/sltu
399// op1 can be bteqz or btnez
400// the operands for op2 are two registers
401// op1 is a conditional branch
402//
403//
404// $op2 $rl, $rr  ;test registers rl,rr
405// $op1 .+4       ;op2 is a conditional branch
406// move $rd, $rs
407//
408//
409class SelT<string op1, string op2>:
410  MipsPseudo16<(outs CPU16Regs:$rd_),
411               (ins CPU16Regs:$rd, CPU16Regs:$rs,
412                CPU16Regs:$rl, CPU16Regs:$rr),
413               !strconcat(op2,
414               !strconcat("\t$rl, $rr\n\t",
415               !strconcat(op1, "\t.+4\n\tmove $rd, $rs"))), []> {
416  let isCodeGenOnly=1;
417  let Constraints = "$rd = $rd_";
418}
419
420//
421// 32 bit constant
422//
423def imm32: Operand<i32>;
424
425def Constant32:
426  MipsPseudo16<(outs), (ins imm32:$imm), "\t.word $imm", []>;
427
428def LwConstant32:
429  MipsPseudo16<(outs), (ins CPU16Regs:$rx, imm32:$imm),
430    "lw\t$rx, 1f\n\tb\t2f\n\t.align\t2\n1: \t.word\t$imm\n2:", []>;
431
432
433//
434// Some general instruction class info
435//
436//
437
438class ArithLogic16Defs<bit isCom=0> {
439  bits<5> shamt = 0;
440  bit isCommutable = isCom;
441  bit isReMaterializable = 1;
442  bit neverHasSideEffects = 1;
443}
444
445class branch16 {
446  bit isBranch = 1;
447  bit isTerminator = 1;
448  bit isBarrier = 1;
449}
450
451class cbranch16 {
452  bit isBranch = 1;
453  bit isTerminator = 1;
454}
455
456class MayLoad {
457  bit mayLoad = 1;
458}
459
460class MayStore {
461  bit mayStore = 1;
462}
463//
464
465
466// Format: ADDIU rx, immediate MIPS16e
467// Purpose: Add Immediate Unsigned Word (2-Operand, Extended)
468// To add a constant to a 32-bit integer.
469//
470def AddiuRxImmX16: FEXT_RI16_ins<0b01001, "addiu", IIAlu>;
471
472def AddiuRxRxImm16: F2RI16_ins<0b01001, "addiu", IIAlu>,
473  ArithLogic16Defs<0> {
474  let AddedComplexity = 5;
475}
476def AddiuRxRxImmX16: FEXT_2RI16_ins<0b01001, "addiu", IIAlu>,
477  ArithLogic16Defs<0> {
478  let isCodeGenOnly = 1;
479}
480
481def AddiuRxRyOffMemX16:
482  FEXT_RRI_A16_mem_ins<0, "addiu", mem16_ea, IIAlu>;
483
484//
485
486// Format: ADDIU rx, pc, immediate MIPS16e
487// Purpose: Add Immediate Unsigned Word (3-Operand, PC-Relative, Extended)
488// To add a constant to the program counter.
489//
490def AddiuRxPcImmX16: FEXT_RI16_PC_ins<0b00001, "addiu", IIAlu>;
491
492//
493// Format: ADDIU sp, immediate MIPS16e
494// Purpose: Add Immediate Unsigned Word (2-Operand, SP-Relative, Extended)
495// To add a constant to the stack pointer.
496//
497def AddiuSpImm16
498  : FI816_SP_ins<0b011, "addiu", IIAlu> {
499  let Defs = [SP];
500  let Uses = [SP];
501  let AddedComplexity = 5;
502}
503
504def AddiuSpImmX16
505  : FEXT_I816_SP_ins<0b011, "addiu", IIAlu> {
506  let Defs = [SP];
507  let Uses = [SP];
508}
509
510//
511// Format: ADDU rz, rx, ry MIPS16e
512// Purpose: Add Unsigned Word (3-Operand)
513// To add 32-bit integers.
514//
515
516def AdduRxRyRz16: FRRR16_ins<01, "addu", IIAlu>, ArithLogic16Defs<1>;
517
518//
519// Format: AND rx, ry MIPS16e
520// Purpose: AND
521// To do a bitwise logical AND.
522
523def AndRxRxRy16: FRxRxRy16_ins<0b01100, "and", IIAlu>, ArithLogic16Defs<1>;
524
525
526//
527// Format: BEQZ rx, offset MIPS16e
528// Purpose: Branch on Equal to Zero
529// To test a GPR then do a PC-relative conditional branch.
530//
531def BeqzRxImm16: FRI16_B_ins<0b00100, "beqz", IIAlu>, cbranch16;
532
533
534//
535// Format: BEQZ rx, offset MIPS16e
536// Purpose: Branch on Equal to Zero (Extended)
537// To test a GPR then do a PC-relative conditional branch.
538//
539def BeqzRxImmX16: FEXT_RI16_B_ins<0b00100, "beqz", IIAlu>, cbranch16;
540
541// Format: B offset MIPS16e
542// Purpose: Unconditional Branch
543// To do an unconditional PC-relative branch.
544//
545def BimmX16: FEXT_I16_ins<0b00010, "b", IIAlu>, branch16;
546
547//
548// Format: BNEZ rx, offset MIPS16e
549// Purpose: Branch on Not Equal to Zero
550// To test a GPR then do a PC-relative conditional branch.
551//
552def BnezRxImm16: FRI16_B_ins<0b00101, "bnez", IIAlu>, cbranch16;
553
554//
555// Format: BNEZ rx, offset MIPS16e
556// Purpose: Branch on Not Equal to Zero (Extended)
557// To test a GPR then do a PC-relative conditional branch.
558//
559def BnezRxImmX16: FEXT_RI16_B_ins<0b00101, "bnez", IIAlu>, cbranch16;
560
561//
562// Format: BTEQZ offset MIPS16e
563// Purpose: Branch on T Equal to Zero (Extended)
564// To test special register T then do a PC-relative conditional branch.
565//
566def BteqzX16: FEXT_I816_ins<0b000, "bteqz", IIAlu>, cbranch16 {
567  let Uses = [T8];
568}
569
570def BteqzT8CmpX16: FEXT_T8I816_ins<"bteqz", "cmp">, cbranch16;
571
572def BteqzT8CmpiX16: FEXT_T8I8I16_ins<"bteqz", "cmpi">,
573  cbranch16;
574
575def BteqzT8SltX16: FEXT_T8I816_ins<"bteqz", "slt">, cbranch16;
576
577def BteqzT8SltuX16: FEXT_T8I816_ins<"bteqz", "sltu">, cbranch16;
578
579def BteqzT8SltiX16: FEXT_T8I8I16_ins<"bteqz", "slti">, cbranch16;
580
581def BteqzT8SltiuX16: FEXT_T8I8I16_ins<"bteqz", "sltiu">,
582  cbranch16;
583
584//
585// Format: BTNEZ offset MIPS16e
586// Purpose: Branch on T Not Equal to Zero (Extended)
587// To test special register T then do a PC-relative conditional branch.
588//
589def BtnezX16: FEXT_I816_ins<0b001, "btnez", IIAlu> ,cbranch16 {
590  let Uses = [T8];
591}
592
593def BtnezT8CmpX16: FEXT_T8I816_ins<"btnez", "cmp">, cbranch16;
594
595def BtnezT8CmpiX16: FEXT_T8I8I16_ins<"btnez", "cmpi">, cbranch16;
596
597def BtnezT8SltX16: FEXT_T8I816_ins<"btnez", "slt">, cbranch16;
598
599def BtnezT8SltuX16: FEXT_T8I816_ins<"btnez", "sltu">, cbranch16;
600
601def BtnezT8SltiX16: FEXT_T8I8I16_ins<"btnez", "slti">, cbranch16;
602
603def BtnezT8SltiuX16: FEXT_T8I8I16_ins<"btnez", "sltiu">,
604  cbranch16;
605
606//
607// Format: CMP rx, ry MIPS16e
608// Purpose: Compare
609// To compare the contents of two GPRs.
610//
611def CmpRxRy16: FRR16_ins<0b01010, "cmp", IIAlu> {
612  let Defs = [T8];
613}
614
615//
616// Format: CMPI rx, immediate MIPS16e
617// Purpose: Compare Immediate
618// To compare a constant with the contents of a GPR.
619//
620def CmpiRxImm16: FRI16_ins<0b01110, "cmpi", IIAlu> {
621  let Defs = [T8];
622}
623
624//
625// Format: CMPI rx, immediate MIPS16e
626// Purpose: Compare Immediate (Extended)
627// To compare a constant with the contents of a GPR.
628//
629def CmpiRxImmX16: FEXT_RI16_ins<0b01110, "cmpi", IIAlu> {
630  let Defs = [T8];
631}
632
633
634//
635// Format: DIV rx, ry MIPS16e
636// Purpose: Divide Word
637// To divide 32-bit signed integers.
638//
639def DivRxRy16: FRR16_div_ins<0b11010, "div", IIAlu> {
640  let Defs = [HI, LO];
641}
642
643//
644// Format: DIVU rx, ry MIPS16e
645// Purpose: Divide Unsigned Word
646// To divide 32-bit unsigned integers.
647//
648def DivuRxRy16: FRR16_div_ins<0b11011, "divu", IIAlu> {
649  let Defs = [HI, LO];
650}
651//
652// Format: JAL target MIPS16e
653// Purpose: Jump and Link
654// To execute a procedure call within the current 256 MB-aligned
655// region and preserve the current ISA.
656//
657
658def Jal16 : FJAL16_ins<0b0, "jal", IIAlu> {
659  let isBranch = 1;
660  let hasDelaySlot = 0;  // not true, but we add the nop for now
661  let isTerminator=1;
662  let isBarrier=1;
663}
664
665//
666// Format: JR ra MIPS16e
667// Purpose: Jump Register Through Register ra
668// To execute a branch to the instruction address in the return
669// address register.
670//
671
672def JrRa16: FRR16_JALRC_RA_only_ins<0, 0, "jr", IIAlu> {
673  let isBranch = 1;
674  let isIndirectBranch = 1;
675  let hasDelaySlot = 1;
676  let isTerminator=1;
677  let isBarrier=1;
678}
679
680def JrcRa16: FRR16_JALRC_RA_only_ins<1, 1, "jrc", IIAlu> {
681  let isBranch = 1;
682  let isIndirectBranch = 1;
683  let isTerminator=1;
684  let isBarrier=1;
685}
686
687def JrcRx16: FRR16_JALRC_ins<1, 1, 0, "jrc", IIAlu> {
688  let isBranch = 1;
689  let isIndirectBranch = 1;
690  let isTerminator=1;
691  let isBarrier=1;
692}
693//
694// Format: LB ry, offset(rx) MIPS16e
695// Purpose: Load Byte (Extended)
696// To load a byte from memory as a signed value.
697//
698def LbRxRyOffMemX16: FEXT_RRI16_mem_ins<0b10011, "lb", mem16, IILoad>, MayLoad{
699  let isCodeGenOnly = 1;
700}
701
702//
703// Format: LBU ry, offset(rx) MIPS16e
704// Purpose: Load Byte Unsigned (Extended)
705// To load a byte from memory as a unsigned value.
706//
707def LbuRxRyOffMemX16:
708  FEXT_RRI16_mem_ins<0b10100, "lbu", mem16, IILoad>, MayLoad {
709  let isCodeGenOnly = 1;
710}
711
712//
713// Format: LH ry, offset(rx) MIPS16e
714// Purpose: Load Halfword signed (Extended)
715// To load a halfword from memory as a signed value.
716//
717def LhRxRyOffMemX16: FEXT_RRI16_mem_ins<0b10100, "lh", mem16, IILoad>, MayLoad{
718  let isCodeGenOnly = 1;
719}
720
721//
722// Format: LHU ry, offset(rx) MIPS16e
723// Purpose: Load Halfword unsigned (Extended)
724// To load a halfword from memory as an unsigned value.
725//
726def LhuRxRyOffMemX16:
727  FEXT_RRI16_mem_ins<0b10100, "lhu", mem16, IILoad>, MayLoad {
728  let isCodeGenOnly = 1;
729}
730
731//
732// Format: LI rx, immediate MIPS16e
733// Purpose: Load Immediate
734// To load a constant into a GPR.
735//
736def LiRxImm16: FRI16_ins<0b01101, "li", IIAlu>;
737
738//
739// Format: LI rx, immediate MIPS16e
740// Purpose: Load Immediate (Extended)
741// To load a constant into a GPR.
742//
743def LiRxImmX16: FEXT_RI16_ins<0b01101, "li", IIAlu>;
744
745//
746// Format: LW ry, offset(rx) MIPS16e
747// Purpose: Load Word (Extended)
748// To load a word from memory as a signed value.
749//
750def LwRxRyOffMemX16: FEXT_RRI16_mem_ins<0b10011, "lw", mem16, IILoad>, MayLoad{
751  let isCodeGenOnly = 1;
752}
753
754// Format: LW rx, offset(sp) MIPS16e
755// Purpose: Load Word (SP-Relative, Extended)
756// To load an SP-relative word from memory as a signed value.
757//
758def LwRxSpImmX16: FEXT_RI16_SP_explicit_ins<0b10110, "lw", IILoad>, MayLoad{
759  let Uses = [SP];
760}
761
762//
763// Format: MOVE r32, rz MIPS16e
764// Purpose: Move
765// To move the contents of a GPR to a GPR.
766//
767def Move32R16: FI8_MOV32R16_ins<"move", IIAlu>;
768
769//
770// Format: MOVE ry, r32 MIPS16e
771//Purpose: Move
772// To move the contents of a GPR to a GPR.
773//
774def MoveR3216: FI8_MOVR3216_ins<"move", IIAlu>;
775
776//
777// Format: MFHI rx MIPS16e
778// Purpose: Move From HI Register
779// To copy the special purpose HI register to a GPR.
780//
781def Mfhi16: FRR16_M_ins<0b10000, "mfhi", IIAlu> {
782  let Uses = [HI];
783  let neverHasSideEffects = 1;
784}
785
786//
787// Format: MFLO rx MIPS16e
788// Purpose: Move From LO Register
789// To copy the special purpose LO register to a GPR.
790//
791def Mflo16: FRR16_M_ins<0b10010, "mflo", IIAlu> {
792  let Uses = [LO];
793  let neverHasSideEffects = 1;
794}
795
796//
797// Pseudo Instruction for mult
798//
799def MultRxRy16:  FMULT16_ins<"mult",  IIAlu> {
800  let isCommutable = 1;
801  let neverHasSideEffects = 1;
802  let Defs = [HI, LO];
803}
804
805def MultuRxRy16: FMULT16_ins<"multu", IIAlu> {
806  let isCommutable = 1;
807  let neverHasSideEffects = 1;
808  let Defs = [HI, LO];
809}
810
811//
812// Format: MULT rx, ry MIPS16e
813// Purpose: Multiply Word
814// To multiply 32-bit signed integers.
815//
816def MultRxRyRz16: FMULT16_LO_ins<"mult", IIAlu> {
817  let isCommutable = 1;
818  let neverHasSideEffects = 1;
819  let Defs = [HI, LO];
820}
821
822//
823// Format: MULTU rx, ry MIPS16e
824// Purpose: Multiply Unsigned Word
825// To multiply 32-bit unsigned integers.
826//
827def MultuRxRyRz16: FMULT16_LO_ins<"multu", IIAlu> {
828  let isCommutable = 1;
829  let neverHasSideEffects = 1;
830  let Defs = [HI, LO];
831}
832
833//
834// Format: NEG rx, ry MIPS16e
835// Purpose: Negate
836// To negate an integer value.
837//
838def NegRxRy16: FUnaryRR16_ins<0b11101, "neg", IIAlu>;
839
840//
841// Format: NOT rx, ry MIPS16e
842// Purpose: Not
843// To complement an integer value
844//
845def NotRxRy16: FUnaryRR16_ins<0b01111, "not", IIAlu>;
846
847//
848// Format: OR rx, ry MIPS16e
849// Purpose: Or
850// To do a bitwise logical OR.
851//
852def OrRxRxRy16: FRxRxRy16_ins<0b01101, "or", IIAlu>, ArithLogic16Defs<1>;
853
854//
855// Format: RESTORE {ra,}{s0/s1/s0-1,}{framesize}
856// (All args are optional) MIPS16e
857// Purpose: Restore Registers and Deallocate Stack Frame
858// To deallocate a stack frame before exit from a subroutine,
859// restoring return address and static registers, and adjusting
860// stack
861//
862
863// fixed form for restoring RA and the frame
864// for direct object emitter, encoding needs to be adjusted for the
865// frame size
866//
867let ra=1, s=0,s0=1,s1=1 in
868def RestoreRaF16:
869  FI8_SVRS16<0b1, (outs), (ins uimm16:$frame_size),
870             "restore\t$$ra,  $$s0, $$s1, $frame_size", [], IILoad >, MayLoad {
871  let isCodeGenOnly = 1;
872  let Defs = [S0, S1, RA, SP];
873  let Uses = [SP];
874}
875
876// Use Restore to increment SP since SP is not a Mip 16 register, this
877// is an easy way to do that which does not require a register.
878//
879let ra=0, s=0,s0=0,s1=0 in
880def RestoreIncSpF16:
881  FI8_SVRS16<0b1, (outs), (ins uimm16:$frame_size),
882             "restore\t$frame_size", [], IILoad >, MayLoad {
883  let isCodeGenOnly = 1;
884  let Defs = [SP];
885  let Uses = [SP];
886}
887
888//
889// Format: SAVE {ra,}{s0/s1/s0-1,}{framesize} (All arguments are optional)
890// MIPS16e
891// Purpose: Save Registers and Set Up Stack Frame
892// To set up a stack frame on entry to a subroutine,
893// saving return address and static registers, and adjusting stack
894//
895let ra=1, s=1,s0=1,s1=1 in
896def SaveRaF16:
897  FI8_SVRS16<0b1, (outs), (ins uimm16:$frame_size),
898             "save\t$$ra, $$s0, $$s1, $frame_size", [], IIStore >, MayStore {
899  let isCodeGenOnly = 1;
900  let Uses = [RA, SP, S0, S1];
901  let Defs = [SP];
902}
903
904//
905// Use Save to decrement the SP by a constant since SP is not
906// a Mips16 register.
907//
908let ra=0, s=0,s0=0,s1=0 in
909def SaveDecSpF16:
910  FI8_SVRS16<0b1, (outs), (ins uimm16:$frame_size),
911             "save\t$frame_size", [], IIStore >, MayStore {
912  let isCodeGenOnly = 1;
913  let Uses = [SP];
914  let Defs = [SP];
915}
916//
917// Format: SB ry, offset(rx) MIPS16e
918// Purpose: Store Byte (Extended)
919// To store a byte to memory.
920//
921def SbRxRyOffMemX16:
922  FEXT_RRI16_mem2_ins<0b11000, "sb", mem16, IIStore>, MayStore;
923
924//
925// The Sel(T) instructions are pseudos
926// T means that they use T8 implicitly.
927//
928//
929// Format: SelBeqZ rd, rs, rt
930// Purpose: if rt==0, do nothing
931//          else rs = rt
932//
933def SelBeqZ: Sel<"beqz">;
934
935//
936// Format:  SelTBteqZCmp rd, rs, rl, rr
937// Purpose: b = Cmp rl, rr.
938//          If b==0 then do nothing.
939//          if b!=0 then rd = rs
940//
941def SelTBteqZCmp: SelT<"bteqz", "cmp">;
942
943//
944// Format:  SelTBteqZCmpi rd, rs, rl, rr
945// Purpose: b = Cmpi rl, imm.
946//          If b==0 then do nothing.
947//          if b!=0 then rd = rs
948//
949def SelTBteqZCmpi: SeliT<"bteqz", "cmpi">;
950
951//
952// Format:  SelTBteqZSlt rd, rs, rl, rr
953// Purpose: b = Slt rl, rr.
954//          If b==0 then do nothing.
955//          if b!=0 then rd = rs
956//
957def SelTBteqZSlt: SelT<"bteqz", "slt">;
958
959//
960// Format:  SelTBteqZSlti rd, rs, rl, rr
961// Purpose: b = Slti rl, imm.
962//          If b==0 then do nothing.
963//          if b!=0 then rd = rs
964//
965def SelTBteqZSlti: SeliT<"bteqz", "slti">;
966
967//
968// Format:  SelTBteqZSltu rd, rs, rl, rr
969// Purpose: b = Sltu rl, rr.
970//          If b==0 then do nothing.
971//          if b!=0 then rd = rs
972//
973def SelTBteqZSltu: SelT<"bteqz", "sltu">;
974
975//
976// Format:  SelTBteqZSltiu rd, rs, rl, rr
977// Purpose: b = Sltiu rl, imm.
978//          If b==0 then do nothing.
979//          if b!=0 then rd = rs
980//
981def SelTBteqZSltiu: SeliT<"bteqz", "sltiu">;
982
983//
984// Format: SelBnez rd, rs, rt
985// Purpose: if rt!=0, do nothing
986//          else rs = rt
987//
988def SelBneZ: Sel<"bnez">;
989
990//
991// Format:  SelTBtneZCmp rd, rs, rl, rr
992// Purpose: b = Cmp rl, rr.
993//          If b!=0 then do nothing.
994//          if b0=0 then rd = rs
995//
996def SelTBtneZCmp: SelT<"btnez", "cmp">;
997
998//
999// Format:  SelTBtnezCmpi rd, rs, rl, rr
1000// Purpose: b = Cmpi rl, imm.
1001//          If b!=0 then do nothing.
1002//          if b==0 then rd = rs
1003//
1004def SelTBtneZCmpi: SeliT<"btnez", "cmpi">;
1005
1006//
1007// Format:  SelTBtneZSlt rd, rs, rl, rr
1008// Purpose: b = Slt rl, rr.
1009//          If b!=0 then do nothing.
1010//          if b==0 then rd = rs
1011//
1012def SelTBtneZSlt: SelT<"btnez", "slt">;
1013
1014//
1015// Format:  SelTBtneZSlti rd, rs, rl, rr
1016// Purpose: b = Slti rl, imm.
1017//          If b!=0 then do nothing.
1018//          if b==0 then rd = rs
1019//
1020def SelTBtneZSlti: SeliT<"btnez", "slti">;
1021
1022//
1023// Format:  SelTBtneZSltu rd, rs, rl, rr
1024// Purpose: b = Sltu rl, rr.
1025//          If b!=0 then do nothing.
1026//          if b==0 then rd = rs
1027//
1028def SelTBtneZSltu: SelT<"btnez", "sltu">;
1029
1030//
1031// Format:  SelTBtneZSltiu rd, rs, rl, rr
1032// Purpose: b = Slti rl, imm.
1033//          If b!=0 then do nothing.
1034//          if b==0 then rd = rs
1035//
1036def SelTBtneZSltiu: SeliT<"btnez", "sltiu">;
1037//
1038//
1039// Format: SH ry, offset(rx) MIPS16e
1040// Purpose: Store Halfword (Extended)
1041// To store a halfword to memory.
1042//
1043def ShRxRyOffMemX16:
1044  FEXT_RRI16_mem2_ins<0b11001, "sh", mem16, IIStore>, MayStore;
1045
1046//
1047// Format: SLL rx, ry, sa MIPS16e
1048// Purpose: Shift Word Left Logical (Extended)
1049// To execute a left-shift of a word by a fixed number of bits—0 to 31 bits.
1050//
1051def SllX16: FEXT_SHIFT16_ins<0b00, "sll", IIAlu>;
1052
1053//
1054// Format: SLLV ry, rx MIPS16e
1055// Purpose: Shift Word Left Logical Variable
1056// To execute a left-shift of a word by a variable number of bits.
1057//
1058def SllvRxRy16 : FRxRxRy16_ins<0b00100, "sllv", IIAlu>;
1059
1060// Format: SLTI rx, immediate MIPS16e
1061// Purpose: Set on Less Than Immediate
1062// To record the result of a less-than comparison with a constant.
1063//
1064//
1065def SltiRxImm16: FRI16R_ins<0b01010, "slti", IIAlu> {
1066  let Defs = [T8];
1067}
1068
1069//
1070// Format: SLTI rx, immediate MIPS16e
1071// Purpose: Set on Less Than Immediate (Extended)
1072// To record the result of a less-than comparison with a constant.
1073//
1074//
1075def SltiRxImmX16: FEXT_RI16R_ins<0b01010, "slti", IIAlu> {
1076  let Defs = [T8];
1077}
1078
1079def SltiCCRxImmX16: FEXT_CCRXI16_ins<"slti">;
1080
1081// Format: SLTIU rx, immediate MIPS16e
1082// Purpose: Set on Less Than Immediate Unsigned
1083// To record the result of a less-than comparison with a constant.
1084//
1085//
1086def SltiuRxImm16: FRI16R_ins<0b01011, "sltiu", IIAlu> {
1087  let Defs = [T8];
1088}
1089
1090//
1091// Format: SLTI rx, immediate MIPS16e
1092// Purpose: Set on Less Than Immediate Unsigned (Extended)
1093// To record the result of a less-than comparison with a constant.
1094//
1095//
1096def SltiuRxImmX16: FEXT_RI16R_ins<0b01011, "sltiu", IIAlu> {
1097  let Defs = [T8];
1098}
1099//
1100// Format: SLTIU rx, immediate MIPS16e
1101// Purpose: Set on Less Than Immediate Unsigned (Extended)
1102// To record the result of a less-than comparison with a constant.
1103//
1104def SltiuCCRxImmX16: FEXT_CCRXI16_ins<"sltiu">;
1105
1106//
1107// Format: SLT rx, ry MIPS16e
1108// Purpose: Set on Less Than
1109// To record the result of a less-than comparison.
1110//
1111def SltRxRy16: FRR16_ins<0b00010, "slt", IIAlu>{
1112  let Defs = [T8];
1113}
1114
1115def SltCCRxRy16: FCCRR16_ins<"slt">;
1116
1117// Format: SLTU rx, ry MIPS16e
1118// Purpose: Set on Less Than Unsigned
1119// To record the result of an unsigned less-than comparison.
1120//
1121def SltuRxRy16: FRR16_ins<0b00011, "sltu", IIAlu>{
1122  let Defs = [T8];
1123}
1124
1125def SltuRxRyRz16: FRRTR16_ins<"sltu"> {
1126  let isCodeGenOnly=1;
1127  let Defs = [T8];
1128}
1129
1130
1131def SltuCCRxRy16: FCCRR16_ins<"sltu">;
1132//
1133// Format: SRAV ry, rx MIPS16e
1134// Purpose: Shift Word Right Arithmetic Variable
1135// To execute an arithmetic right-shift of a word by a variable
1136// number of bits.
1137//
1138def SravRxRy16: FRxRxRy16_ins<0b00111, "srav", IIAlu>;
1139
1140
1141//
1142// Format: SRA rx, ry, sa MIPS16e
1143// Purpose: Shift Word Right Arithmetic (Extended)
1144// To execute an arithmetic right-shift of a word by a fixed
1145// number of bits—1 to 8 bits.
1146//
1147def SraX16: FEXT_SHIFT16_ins<0b11, "sra", IIAlu>;
1148
1149
1150//
1151// Format: SRLV ry, rx MIPS16e
1152// Purpose: Shift Word Right Logical Variable
1153// To execute a logical right-shift of a word by a variable
1154// number of bits.
1155//
1156def SrlvRxRy16: FRxRxRy16_ins<0b00110, "srlv", IIAlu>;
1157
1158
1159//
1160// Format: SRL rx, ry, sa MIPS16e
1161// Purpose: Shift Word Right Logical (Extended)
1162// To execute a logical right-shift of a word by a fixed
1163// number of bits—1 to 31 bits.
1164//
1165def SrlX16: FEXT_SHIFT16_ins<0b10, "srl", IIAlu>;
1166
1167//
1168// Format: SUBU rz, rx, ry MIPS16e
1169// Purpose: Subtract Unsigned Word
1170// To subtract 32-bit integers
1171//
1172def SubuRxRyRz16: FRRR16_ins<0b11, "subu", IIAlu>, ArithLogic16Defs<0>;
1173
1174//
1175// Format: SW ry, offset(rx) MIPS16e
1176// Purpose: Store Word (Extended)
1177// To store a word to memory.
1178//
1179def SwRxRyOffMemX16:
1180  FEXT_RRI16_mem2_ins<0b11011, "sw", mem16, IIStore>, MayStore;
1181
1182//
1183// Format: SW rx, offset(sp) MIPS16e
1184// Purpose: Store Word rx (SP-Relative)
1185// To store an SP-relative word to memory.
1186//
1187def SwRxSpImmX16: FEXT_RI16_SP_explicit_ins<0b11010, "sw", IIStore>, MayStore;
1188
1189//
1190//
1191// Format: XOR rx, ry MIPS16e
1192// Purpose: Xor
1193// To do a bitwise logical XOR.
1194//
1195def XorRxRxRy16: FRxRxRy16_ins<0b01110, "xor", IIAlu>, ArithLogic16Defs<1>;
1196
1197class Mips16Pat<dag pattern, dag result> : Pat<pattern, result> {
1198  let Predicates = [InMips16Mode];
1199}
1200
1201// Unary Arith/Logic
1202//
1203class ArithLogicU_pat<PatFrag OpNode, Instruction I> :
1204  Mips16Pat<(OpNode CPU16Regs:$r),
1205            (I CPU16Regs:$r)>;
1206
1207def: ArithLogicU_pat<not, NotRxRy16>;
1208def: ArithLogicU_pat<ineg, NegRxRy16>;
1209
1210class ArithLogic16_pat<SDNode OpNode, Instruction I> :
1211  Mips16Pat<(OpNode CPU16Regs:$l, CPU16Regs:$r),
1212            (I CPU16Regs:$l, CPU16Regs:$r)>;
1213
1214def: ArithLogic16_pat<add, AdduRxRyRz16>;
1215def: ArithLogic16_pat<and, AndRxRxRy16>;
1216def: ArithLogic16_pat<mul, MultRxRyRz16>;
1217def: ArithLogic16_pat<or, OrRxRxRy16>;
1218def: ArithLogic16_pat<sub, SubuRxRyRz16>;
1219def: ArithLogic16_pat<xor, XorRxRxRy16>;
1220
1221// Arithmetic and logical instructions with 2 register operands.
1222
1223class ArithLogicI16_pat<SDNode OpNode, PatFrag imm_type, Instruction I> :
1224  Mips16Pat<(OpNode CPU16Regs:$in, imm_type:$imm),
1225            (I CPU16Regs:$in, imm_type:$imm)>;
1226
1227def: ArithLogicI16_pat<add, immSExt8, AddiuRxRxImm16>;
1228def: ArithLogicI16_pat<add, immSExt16, AddiuRxRxImmX16>;
1229def: ArithLogicI16_pat<shl, immZExt5, SllX16>;
1230def: ArithLogicI16_pat<srl, immZExt5, SrlX16>;
1231def: ArithLogicI16_pat<sra, immZExt5, SraX16>;
1232
1233class shift_rotate_reg16_pat<SDNode OpNode, Instruction I> :
1234  Mips16Pat<(OpNode CPU16Regs:$r, CPU16Regs:$ra),
1235            (I CPU16Regs:$r, CPU16Regs:$ra)>;
1236
1237def: shift_rotate_reg16_pat<shl, SllvRxRy16>;
1238def: shift_rotate_reg16_pat<sra, SravRxRy16>;
1239def: shift_rotate_reg16_pat<srl, SrlvRxRy16>;
1240
1241class LoadM16_pat<PatFrag OpNode, Instruction I> :
1242  Mips16Pat<(OpNode addr16:$addr), (I addr16:$addr)>;
1243
1244def: LoadM16_pat<sextloadi8, LbRxRyOffMemX16>;
1245def: LoadM16_pat<zextloadi8, LbuRxRyOffMemX16>;
1246def: LoadM16_pat<sextloadi16, LhRxRyOffMemX16>;
1247def: LoadM16_pat<zextloadi16, LhuRxRyOffMemX16>;
1248def: LoadM16_pat<load, LwRxRyOffMemX16>;
1249
1250class StoreM16_pat<PatFrag OpNode, Instruction I> :
1251  Mips16Pat<(OpNode CPU16Regs:$r, addr16:$addr),
1252            (I CPU16Regs:$r, addr16:$addr)>;
1253
1254def: StoreM16_pat<truncstorei8, SbRxRyOffMemX16>;
1255def: StoreM16_pat<truncstorei16, ShRxRyOffMemX16>;
1256def: StoreM16_pat<store, SwRxRyOffMemX16>;
1257
1258// Unconditional branch
1259class UncondBranch16_pat<SDNode OpNode, Instruction I>:
1260  Mips16Pat<(OpNode bb:$imm16), (I bb:$imm16)> {
1261    let Predicates = [InMips16Mode];
1262  }
1263
1264def : Mips16Pat<(MipsJmpLink (i32 tglobaladdr:$dst)),
1265                (Jal16 tglobaladdr:$dst)>;
1266
1267def : Mips16Pat<(MipsJmpLink (i32 texternalsym:$dst)),
1268                (Jal16 texternalsym:$dst)>;
1269
1270// Indirect branch
1271def: Mips16Pat<
1272  (brind CPU16Regs:$rs),
1273  (JrcRx16 CPU16Regs:$rs)>;
1274
1275// Jump and Link (Call)
1276let isCall=1, hasDelaySlot=0 in
1277def JumpLinkReg16:
1278  FRR16_JALRC<0, 0, 0, (outs), (ins CPU16Regs:$rs),
1279              "jalrc \t$rs", [(MipsJmpLink CPU16Regs:$rs)], IIBranch>;
1280
1281// Mips16 pseudos
1282let isReturn=1, isTerminator=1, hasDelaySlot=1, isBarrier=1, hasCtrlDep=1,
1283  hasExtraSrcRegAllocReq = 1 in
1284def RetRA16 : MipsPseudo16<(outs), (ins), "", [(MipsRet)]>;
1285
1286
1287// setcc patterns
1288
1289class SetCC_R16<PatFrag cond_op, Instruction I>:
1290  Mips16Pat<(cond_op CPU16Regs:$rx, CPU16Regs:$ry),
1291            (I CPU16Regs:$rx, CPU16Regs:$ry)>;
1292
1293class SetCC_I16<PatFrag cond_op, PatLeaf imm_type, Instruction I>:
1294  Mips16Pat<(cond_op CPU16Regs:$rx, imm_type:$imm16),
1295            (I CPU16Regs:$rx, imm_type:$imm16)>;
1296
1297
1298def: Mips16Pat<(i32  addr16:$addr),
1299               (AddiuRxRyOffMemX16  addr16:$addr)>;
1300
1301
1302// Large (>16 bit) immediate loads
1303def : Mips16Pat<(i32 imm:$imm),
1304                (OrRxRxRy16 (SllX16 (LiRxImmX16 (HI16 imm:$imm)), 16),
1305                (LiRxImmX16 (LO16 imm:$imm)))>;
1306
1307// Carry MipsPatterns
1308def : Mips16Pat<(subc CPU16Regs:$lhs, CPU16Regs:$rhs),
1309                (SubuRxRyRz16 CPU16Regs:$lhs, CPU16Regs:$rhs)>;
1310def : Mips16Pat<(addc CPU16Regs:$lhs, CPU16Regs:$rhs),
1311                (AdduRxRyRz16 CPU16Regs:$lhs, CPU16Regs:$rhs)>;
1312def : Mips16Pat<(addc  CPU16Regs:$src, immSExt16:$imm),
1313                (AddiuRxRxImmX16 CPU16Regs:$src, imm:$imm)>;
1314
1315//
1316// Some branch conditional patterns are not generated by llvm at this time.
1317// Some are for seemingly arbitrary reasons not used: i.e. with signed number
1318// comparison they are used and for unsigned a different pattern is used.
1319// I am pushing upstream from the full mips16 port and it seemed that I needed
1320// these earlier and the mips32 port has these but now I cannot create test
1321// cases that use these patterns. While I sort this all out I will leave these
1322// extra patterns commented out and if I can be sure they are really not used,
1323// I will delete the code. I don't want to check the code in uncommented without
1324// a valid test case. In some cases, the compiler is generating patterns with
1325// setcc instead and earlier I had implemented setcc first so may have masked
1326// the problem. The setcc variants are suboptimal for mips16 so I may wantto
1327// figure out how to enable the brcond patterns or else possibly new
1328// combinations of of brcond and setcc.
1329//
1330//
1331// bcond-seteq
1332//
1333def: Mips16Pat
1334  <(brcond (i32 (seteq CPU16Regs:$rx, CPU16Regs:$ry)), bb:$imm16),
1335   (BteqzT8CmpX16 CPU16Regs:$rx, CPU16Regs:$ry,  bb:$imm16)
1336  >;
1337
1338
1339def: Mips16Pat
1340  <(brcond (i32 (seteq CPU16Regs:$rx, immZExt16:$imm)), bb:$targ16),
1341   (BteqzT8CmpiX16 CPU16Regs:$rx, immSExt16:$imm,  bb:$targ16)
1342  >;
1343
1344def: Mips16Pat
1345  <(brcond (i32 (seteq CPU16Regs:$rx, 0)), bb:$targ16),
1346   (BeqzRxImmX16 CPU16Regs:$rx, bb:$targ16)
1347  >;
1348
1349//
1350// bcond-setgt (do we need to have this pair of setlt, setgt??)
1351//
1352def: Mips16Pat
1353  <(brcond (i32 (setgt CPU16Regs:$rx, CPU16Regs:$ry)), bb:$imm16),
1354   (BtnezT8SltX16 CPU16Regs:$ry, CPU16Regs:$rx,  bb:$imm16)
1355  >;
1356
1357//
1358// bcond-setge
1359//
1360def: Mips16Pat
1361  <(brcond (i32 (setge CPU16Regs:$rx, CPU16Regs:$ry)), bb:$imm16),
1362   (BteqzT8SltX16 CPU16Regs:$rx, CPU16Regs:$ry,  bb:$imm16)
1363  >;
1364
1365//
1366// never called because compiler transforms a >= k to a > (k-1)
1367def: Mips16Pat
1368  <(brcond (i32 (setge CPU16Regs:$rx, immSExt16:$imm)), bb:$imm16),
1369   (BteqzT8SltiX16 CPU16Regs:$rx, immSExt16:$imm,  bb:$imm16)
1370  >;
1371
1372//
1373// bcond-setlt
1374//
1375def: Mips16Pat
1376  <(brcond (i32 (setlt CPU16Regs:$rx, CPU16Regs:$ry)), bb:$imm16),
1377   (BtnezT8SltX16 CPU16Regs:$rx, CPU16Regs:$ry,  bb:$imm16)
1378  >;
1379
1380def: Mips16Pat
1381  <(brcond (i32 (setlt CPU16Regs:$rx, immSExt16:$imm)), bb:$imm16),
1382   (BtnezT8SltiX16 CPU16Regs:$rx, immSExt16:$imm,  bb:$imm16)
1383  >;
1384
1385//
1386// bcond-setle
1387//
1388def: Mips16Pat
1389  <(brcond (i32 (setle CPU16Regs:$rx, CPU16Regs:$ry)), bb:$imm16),
1390   (BteqzT8SltX16 CPU16Regs:$ry, CPU16Regs:$rx,  bb:$imm16)
1391  >;
1392
1393//
1394// bcond-setne
1395//
1396def: Mips16Pat
1397  <(brcond (i32 (setne CPU16Regs:$rx, CPU16Regs:$ry)), bb:$imm16),
1398   (BtnezT8CmpX16 CPU16Regs:$rx, CPU16Regs:$ry,  bb:$imm16)
1399  >;
1400
1401def: Mips16Pat
1402  <(brcond (i32 (setne CPU16Regs:$rx, immZExt16:$imm)), bb:$targ16),
1403   (BtnezT8CmpiX16 CPU16Regs:$rx, immSExt16:$imm,  bb:$targ16)
1404  >;
1405
1406def: Mips16Pat
1407  <(brcond (i32 (setne CPU16Regs:$rx, 0)), bb:$targ16),
1408   (BnezRxImmX16 CPU16Regs:$rx, bb:$targ16)
1409  >;
1410
1411//
1412// This needs to be there but I forget which code will generate it
1413//
1414def: Mips16Pat
1415  <(brcond CPU16Regs:$rx, bb:$targ16),
1416   (BnezRxImmX16 CPU16Regs:$rx, bb:$targ16)
1417  >;
1418
1419//
1420
1421//
1422// bcond-setugt
1423//
1424//def: Mips16Pat
1425//  <(brcond (i32 (setugt CPU16Regs:$rx, CPU16Regs:$ry)), bb:$imm16),
1426//   (BtnezT8SltuX16 CPU16Regs:$ry, CPU16Regs:$rx,  bb:$imm16)
1427//  >;
1428
1429//
1430// bcond-setuge
1431//
1432//def: Mips16Pat
1433//  <(brcond (i32 (setuge CPU16Regs:$rx, CPU16Regs:$ry)), bb:$imm16),
1434//   (BteqzT8SltuX16 CPU16Regs:$rx, CPU16Regs:$ry,  bb:$imm16)
1435//  >;
1436
1437
1438//
1439// bcond-setult
1440//
1441//def: Mips16Pat
1442//  <(brcond (i32 (setult CPU16Regs:$rx, CPU16Regs:$ry)), bb:$imm16),
1443//   (BtnezT8SltuX16 CPU16Regs:$rx, CPU16Regs:$ry,  bb:$imm16)
1444//  >;
1445
1446def: UncondBranch16_pat<br, BimmX16>;
1447
1448// Small immediates
1449def: Mips16Pat<(i32 immSExt16:$in),
1450               (AddiuRxRxImmX16 (Move32R16 ZERO), immSExt16:$in)>;
1451
1452def: Mips16Pat<(i32 immZExt16:$in), (LiRxImmX16 immZExt16:$in)>;
1453
1454//
1455// MipsDivRem
1456//
1457def: Mips16Pat
1458  <(MipsDivRem CPU16Regs:$rx, CPU16Regs:$ry),
1459   (DivRxRy16 CPU16Regs:$rx, CPU16Regs:$ry)>;
1460
1461//
1462// MipsDivRemU
1463//
1464def: Mips16Pat
1465  <(MipsDivRemU CPU16Regs:$rx, CPU16Regs:$ry),
1466   (DivuRxRy16 CPU16Regs:$rx, CPU16Regs:$ry)>;
1467
1468//  signed a,b
1469//  x = (a>=b)?x:y
1470//
1471//  if !(a < b) x = y
1472//
1473def : Mips16Pat<(select (i32 (setge CPU16Regs:$a, CPU16Regs:$b)),
1474                 CPU16Regs:$x, CPU16Regs:$y),
1475                (SelTBteqZSlt CPU16Regs:$x, CPU16Regs:$y,
1476                 CPU16Regs:$a, CPU16Regs:$b)>;
1477
1478//  signed a,b
1479//  x = (a>b)?x:y
1480//
1481//  if  (b < a) x = y
1482//
1483def : Mips16Pat<(select (i32 (setgt CPU16Regs:$a, CPU16Regs:$b)),
1484                 CPU16Regs:$x, CPU16Regs:$y),
1485                (SelTBtneZSlt CPU16Regs:$x, CPU16Regs:$y,
1486                 CPU16Regs:$b, CPU16Regs:$a)>;
1487
1488// unsigned a,b
1489// x = (a>=b)?x:y
1490//
1491// if !(a < b) x = y;
1492//
1493def : Mips16Pat<
1494  (select (i32 (setuge CPU16Regs:$a, CPU16Regs:$b)),
1495   CPU16Regs:$x, CPU16Regs:$y),
1496  (SelTBteqZSltu CPU16Regs:$x, CPU16Regs:$y,
1497   CPU16Regs:$a, CPU16Regs:$b)>;
1498
1499//  unsigned a,b
1500//  x = (a>b)?x:y
1501//
1502//  if (b < a) x = y
1503//
1504def : Mips16Pat<(select (i32 (setugt CPU16Regs:$a, CPU16Regs:$b)),
1505                 CPU16Regs:$x, CPU16Regs:$y),
1506                (SelTBtneZSltu CPU16Regs:$x, CPU16Regs:$y,
1507                 CPU16Regs:$b, CPU16Regs:$a)>;
1508
1509// signed
1510// x = (a >= k)?x:y
1511// due to an llvm optimization, i don't think that this will ever
1512// be used. This is transformed into x = (a > k-1)?x:y
1513//
1514//
1515
1516//def : Mips16Pat<
1517//  (select (i32 (setge CPU16Regs:$lhs, immSExt16:$rhs)),
1518//   CPU16Regs:$T, CPU16Regs:$F),
1519//  (SelTBteqZSlti CPU16Regs:$T, CPU16Regs:$F,
1520//   CPU16Regs:$lhs, immSExt16:$rhs)>;
1521
1522//def : Mips16Pat<
1523//  (select (i32 (setuge CPU16Regs:$lhs, immSExt16:$rhs)),
1524//   CPU16Regs:$T, CPU16Regs:$F),
1525//  (SelTBteqZSltiu CPU16Regs:$T, CPU16Regs:$F,
1526//   CPU16Regs:$lhs, immSExt16:$rhs)>;
1527
1528// signed
1529// x = (a < k)?x:y
1530//
1531// if !(a < k) x = y;
1532//
1533def : Mips16Pat<
1534  (select (i32 (setlt CPU16Regs:$a, immSExt16:$b)),
1535   CPU16Regs:$x, CPU16Regs:$y),
1536  (SelTBtneZSlti CPU16Regs:$x, CPU16Regs:$y,
1537   CPU16Regs:$a, immSExt16:$b)>;
1538
1539
1540//
1541//
1542// signed
1543// x = (a <= b)? x : y
1544//
1545// if  (b < a) x = y
1546//
1547def : Mips16Pat<(select (i32 (setle CPU16Regs:$a, CPU16Regs:$b)),
1548                 CPU16Regs:$x, CPU16Regs:$y),
1549                (SelTBteqZSlt CPU16Regs:$x, CPU16Regs:$y,
1550                 CPU16Regs:$b, CPU16Regs:$a)>;
1551
1552//
1553// unnsigned
1554// x = (a <= b)? x : y
1555//
1556// if  (b < a) x = y
1557//
1558def : Mips16Pat<(select (i32 (setule CPU16Regs:$a, CPU16Regs:$b)),
1559                 CPU16Regs:$x, CPU16Regs:$y),
1560                (SelTBteqZSltu CPU16Regs:$x, CPU16Regs:$y,
1561                 CPU16Regs:$b, CPU16Regs:$a)>;
1562
1563//
1564// signed/unsigned
1565// x = (a == b)? x : y
1566//
1567// if (a != b) x = y
1568//
1569def : Mips16Pat<(select (i32 (seteq CPU16Regs:$a, CPU16Regs:$b)),
1570                 CPU16Regs:$x, CPU16Regs:$y),
1571                (SelTBteqZCmp CPU16Regs:$x, CPU16Regs:$y,
1572                 CPU16Regs:$b, CPU16Regs:$a)>;
1573
1574//
1575// signed/unsigned
1576// x = (a == 0)? x : y
1577//
1578// if (a != 0) x = y
1579//
1580def : Mips16Pat<(select (i32 (seteq CPU16Regs:$a, 0)),
1581                 CPU16Regs:$x, CPU16Regs:$y),
1582                (SelBeqZ CPU16Regs:$x, CPU16Regs:$y,
1583                 CPU16Regs:$a)>;
1584
1585
1586//
1587// signed/unsigned
1588// x = (a == k)? x : y
1589//
1590// if (a != k) x = y
1591//
1592def : Mips16Pat<(select (i32 (seteq CPU16Regs:$a, immZExt16:$k)),
1593                 CPU16Regs:$x, CPU16Regs:$y),
1594                (SelTBteqZCmpi CPU16Regs:$x, CPU16Regs:$y,
1595                 CPU16Regs:$a, immZExt16:$k)>;
1596
1597
1598//
1599// signed/unsigned
1600// x = (a != b)? x : y
1601//
1602// if (a == b) x = y
1603//
1604//
1605def : Mips16Pat<(select (i32 (setne CPU16Regs:$a, CPU16Regs:$b)),
1606                 CPU16Regs:$x, CPU16Regs:$y),
1607                (SelTBtneZCmp CPU16Regs:$x, CPU16Regs:$y,
1608                 CPU16Regs:$b, CPU16Regs:$a)>;
1609
1610//
1611// signed/unsigned
1612// x = (a != 0)? x : y
1613//
1614// if (a == 0) x = y
1615//
1616def : Mips16Pat<(select (i32 (setne CPU16Regs:$a, 0)),
1617                 CPU16Regs:$x, CPU16Regs:$y),
1618                (SelBneZ CPU16Regs:$x, CPU16Regs:$y,
1619                 CPU16Regs:$a)>;
1620
1621// signed/unsigned
1622// x = (a)? x : y
1623//
1624// if (!a) x = y
1625//
1626def : Mips16Pat<(select  CPU16Regs:$a,
1627                 CPU16Regs:$x, CPU16Regs:$y),
1628      (SelBneZ CPU16Regs:$x, CPU16Regs:$y,
1629       CPU16Regs:$a)>;
1630
1631
1632//
1633// signed/unsigned
1634// x = (a != k)? x : y
1635//
1636// if (a == k) x = y
1637//
1638def : Mips16Pat<(select (i32 (setne CPU16Regs:$a, immZExt16:$k)),
1639                 CPU16Regs:$x, CPU16Regs:$y),
1640                (SelTBtneZCmpi CPU16Regs:$x, CPU16Regs:$y,
1641                 CPU16Regs:$a, immZExt16:$k)>;
1642
1643//
1644// When writing C code to test setxx these patterns,
1645// some will be transformed into
1646// other things. So we test using C code but using -O3 and -O0
1647//
1648// seteq
1649//
1650def : Mips16Pat
1651  <(seteq CPU16Regs:$lhs,CPU16Regs:$rhs),
1652   (SltiuCCRxImmX16 (XorRxRxRy16 CPU16Regs:$lhs, CPU16Regs:$rhs), 1)>;
1653
1654def : Mips16Pat
1655  <(seteq CPU16Regs:$lhs, 0),
1656   (SltiuCCRxImmX16 CPU16Regs:$lhs, 1)>;
1657
1658
1659//
1660// setge
1661//
1662
1663def: Mips16Pat
1664  <(setge CPU16Regs:$lhs, CPU16Regs:$rhs),
1665   (XorRxRxRy16 (SltCCRxRy16 CPU16Regs:$lhs, CPU16Regs:$rhs),
1666   (LiRxImmX16 1))>;
1667
1668//
1669// For constants, llvm transforms this to:
1670// x > (k -1) and then reverses the operands to use setlt. So this pattern
1671// is not used now by the compiler. (Presumably checking that k-1 does not
1672// overflow). The compiler never uses this at a the current time, due to
1673// other optimizations.
1674//
1675//def: Mips16Pat
1676//  <(setge CPU16Regs:$lhs, immSExt16:$rhs),
1677//   (XorRxRxRy16 (SltiCCRxImmX16 CPU16Regs:$lhs, immSExt16:$rhs),
1678//   (LiRxImmX16 1))>;
1679
1680// This catches the x >= -32768 case by transforming it to  x > -32769
1681//
1682def: Mips16Pat
1683  <(setgt CPU16Regs:$lhs, -32769),
1684   (XorRxRxRy16 (SltiCCRxImmX16 CPU16Regs:$lhs, -32768),
1685   (LiRxImmX16 1))>;
1686
1687//
1688// setgt
1689//
1690//
1691
1692def: Mips16Pat
1693  <(setgt CPU16Regs:$lhs, CPU16Regs:$rhs),
1694   (SltCCRxRy16 CPU16Regs:$rhs, CPU16Regs:$lhs)>;
1695
1696//
1697// setle
1698//
1699def: Mips16Pat
1700  <(setle CPU16Regs:$lhs, CPU16Regs:$rhs),
1701   (XorRxRxRy16 (SltCCRxRy16 CPU16Regs:$rhs, CPU16Regs:$lhs), (LiRxImm16 1))>;
1702
1703//
1704// setlt
1705//
1706def: SetCC_R16<setlt, SltCCRxRy16>;
1707
1708def: SetCC_I16<setlt, immSExt16, SltiCCRxImmX16>;
1709
1710//
1711// setne
1712//
1713def : Mips16Pat
1714  <(setne CPU16Regs:$lhs,CPU16Regs:$rhs),
1715   (SltuCCRxRy16 (LiRxImmX16 0),
1716   (XorRxRxRy16 CPU16Regs:$lhs, CPU16Regs:$rhs))>;
1717
1718
1719//
1720// setuge
1721//
1722def: Mips16Pat
1723  <(setuge CPU16Regs:$lhs, CPU16Regs:$rhs),
1724   (XorRxRxRy16 (SltuCCRxRy16 CPU16Regs:$lhs, CPU16Regs:$rhs),
1725   (LiRxImmX16 1))>;
1726
1727// this pattern will never be used because the compiler will transform
1728// x >= k to x > (k - 1) and then use SLT
1729//
1730//def: Mips16Pat
1731//  <(setuge CPU16Regs:$lhs, immZExt16:$rhs),
1732//   (XorRxRxRy16 (SltiuCCRxImmX16 CPU16Regs:$lhs, immZExt16:$rhs),
1733//   (LiRxImmX16 1))>;
1734
1735//
1736// setugt
1737//
1738def: Mips16Pat
1739  <(setugt CPU16Regs:$lhs, CPU16Regs:$rhs),
1740   (SltuCCRxRy16 CPU16Regs:$rhs, CPU16Regs:$lhs)>;
1741
1742//
1743// setule
1744//
1745def: Mips16Pat
1746  <(setule CPU16Regs:$lhs, CPU16Regs:$rhs),
1747   (XorRxRxRy16 (SltuCCRxRy16 CPU16Regs:$rhs, CPU16Regs:$lhs), (LiRxImmX16 1))>;
1748
1749//
1750// setult
1751//
1752def: SetCC_R16<setult, SltuCCRxRy16>;
1753
1754def: SetCC_I16<setult, immSExt16, SltiuCCRxImmX16>;
1755
1756def: Mips16Pat<(add CPU16Regs:$hi, (MipsLo tglobaladdr:$lo)),
1757               (AddiuRxRxImmX16 CPU16Regs:$hi, tglobaladdr:$lo)>;
1758
1759// hi/lo relocs
1760
1761def : Mips16Pat<(MipsHi tglobaladdr:$in),
1762                (SllX16 (LiRxImmX16 tglobaladdr:$in), 16)>;
1763def : Mips16Pat<(MipsHi tjumptable:$in),
1764                (SllX16 (LiRxImmX16 tjumptable:$in), 16)>;
1765def : Mips16Pat<(MipsHi tglobaltlsaddr:$in),
1766                (SllX16 (LiRxImmX16 tglobaltlsaddr:$in), 16)>;
1767
1768// wrapper_pic
1769class Wrapper16Pat<SDNode node, Instruction ADDiuOp, RegisterClass RC>:
1770  Mips16Pat<(MipsWrapper RC:$gp, node:$in),
1771            (ADDiuOp RC:$gp, node:$in)>;
1772
1773
1774def : Wrapper16Pat<tglobaladdr, AddiuRxRxImmX16, CPU16Regs>;
1775def : Wrapper16Pat<tglobaltlsaddr, AddiuRxRxImmX16, CPU16Regs>;
1776
1777def : Mips16Pat<(i32 (extloadi8   addr16:$src)),
1778                (LbuRxRyOffMemX16  addr16:$src)>;
1779def : Mips16Pat<(i32 (extloadi16  addr16:$src)),
1780                (LhuRxRyOffMemX16  addr16:$src)>;
1781