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