blob: feffddc02ee7904a39c1a49da161f00579c4897c [file] [log] [blame]
Akira Hatanakadf98a7a2012-05-24 18:32:33 +00001//===- 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//===----------------------------------------------------------------------===//
Reed Kotler24032212012-10-05 18:27:54 +000013//
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +000014
15//
Reed Kotler0f2e44a2012-10-10 01:58:16 +000016// Address operand
17def mem16 : Operand<i32> {
18 let PrintMethod = "printMemOperand";
19 let MIOperandInfo = (ops CPU16Regs, simm16);
20 let EncoderMethod = "getMemEncoding";
Akira Hatanaka22bec282012-08-03 22:57:02 +000021}
22
Reed Kotler0f2e44a2012-10-10 01:58:16 +000023//
Reed Kotler164bb372012-10-23 01:35:48 +000024// Compare a register and immediate and place result in CC
25// Implicit use of T8
26//
27// EXT-CCRR Instruction format
28//
29class FEXT_CCRXI16_ins<bits<5> _op, string asmstr,
30 InstrItinClass itin>:
31 FEXT_RI16<_op, (outs CPU16Regs:$cc), (ins CPU16Regs:$rx, simm16:$imm),
32 !strconcat(asmstr, "\t$rx, $imm\n\tmove\t$cc, $$t8"), [], itin> {
33 let isCodeGenOnly=1;
34}
35
36//
Reed Kotler67439242012-10-17 22:29:54 +000037// EXT-I instruction format
38//
39class FEXT_I16_ins<bits<5> eop, string asmstr, InstrItinClass itin> :
40 FEXT_I16<eop, (outs), (ins brtarget:$imm16),
41 !strconcat(asmstr, "\t$imm16"),[], itin>;
42
43//
44// EXT-I8 instruction format
45//
46
47class FEXT_I816_ins_base<bits<3> _func, string asmstr,
48 string asmstr2, InstrItinClass itin>:
49 FEXT_I816<_func, (outs), (ins uimm16:$imm), !strconcat(asmstr, asmstr2),
50 [], itin>;
51
52class FEXT_I816_ins<bits<3> _func, string asmstr,
53 InstrItinClass itin>:
54 FEXT_I816_ins_base<_func, asmstr, "\t$imm", itin>;
55
56//
Reed Kotler0f2e44a2012-10-10 01:58:16 +000057// Assembler formats in alphabetical order.
58// Natural and pseudos are mixed together.
59//
Reed Kotler164bb372012-10-23 01:35:48 +000060// Compare two registers and place result in CC
61// Implicit use of T8
62//
63// CC-RR Instruction format
64//
65class FCCRR16_ins<bits<5> f, string asmstr, InstrItinClass itin> :
66 FRR16<f, (outs CPU16Regs:$cc), (ins CPU16Regs:$rx, CPU16Regs:$ry),
67 !strconcat(asmstr, "\t$rx, $ry\n\tmove\t$cc, $$t8"), [], itin> {
68 let isCodeGenOnly=1;
69}
70
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +000071//
Reed Kotler210ebe92012-09-28 02:26:24 +000072// EXT-RI instruction format
73//
74
75class FEXT_RI16_ins_base<bits<5> _op, string asmstr, string asmstr2,
76 InstrItinClass itin>:
77 FEXT_RI16<_op, (outs CPU16Regs:$rx), (ins simm16:$imm),
78 !strconcat(asmstr, asmstr2), [], itin>;
79
80class FEXT_RI16_ins<bits<5> _op, string asmstr,
81 InstrItinClass itin>:
82 FEXT_RI16_ins_base<_op, asmstr, "\t$rx, $imm", itin>;
83
84class FEXT_RI16_PC_ins<bits<5> _op, string asmstr, InstrItinClass itin>:
85 FEXT_RI16_ins_base<_op, asmstr, "\t$rx, $$pc, $imm", itin>;
86
Reed Kotler67439242012-10-17 22:29:54 +000087class FEXT_RI16_B_ins<bits<5> _op, string asmstr,
88 InstrItinClass itin>:
89 FEXT_RI16<_op, (outs), (ins CPU16Regs:$rx, brtarget:$imm),
90 !strconcat(asmstr, "\t$rx, $imm"), [], itin>;
91
Reed Kotler210ebe92012-09-28 02:26:24 +000092class FEXT_2RI16_ins<bits<5> _op, string asmstr,
93 InstrItinClass itin>:
94 FEXT_RI16<_op, (outs CPU16Regs:$rx), (ins CPU16Regs:$rx_, simm16:$imm),
95 !strconcat(asmstr, "\t$rx, $imm"), [], itin> {
96 let Constraints = "$rx_ = $rx";
97}
Reed Kotler24032212012-10-05 18:27:54 +000098
Reed Kotler67439242012-10-17 22:29:54 +000099
Reed Kotler210ebe92012-09-28 02:26:24 +0000100// this has an explicit sp argument that we ignore to work around a problem
101// in the compiler
102class FEXT_RI16_SP_explicit_ins<bits<5> _op, string asmstr,
103 InstrItinClass itin>:
104 FEXT_RI16<_op, (outs CPU16Regs:$rx), (ins CPUSPReg:$ry, simm16:$imm),
Reed Kotler24032212012-10-05 18:27:54 +0000105 !strconcat(asmstr, "\t$rx, $imm ( $ry ); "), [], itin>;
Reed Kotler210ebe92012-09-28 02:26:24 +0000106
107//
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000108// EXT-RRI instruction format
109//
110
111class FEXT_RRI16_mem_ins<bits<5> op, string asmstr, Operand MemOpnd,
112 InstrItinClass itin>:
113 FEXT_RRI16<op, (outs CPU16Regs:$ry), (ins MemOpnd:$addr),
114 !strconcat(asmstr, "\t$ry, $addr"), [], itin>;
115
Akira Hatanaka22bec282012-08-03 22:57:02 +0000116class FEXT_RRI16_mem2_ins<bits<5> op, string asmstr, Operand MemOpnd,
117 InstrItinClass itin>:
118 FEXT_RRI16<op, (outs ), (ins CPU16Regs:$ry, MemOpnd:$addr),
119 !strconcat(asmstr, "\t$ry, $addr"), [], itin>;
120
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000121//
122// EXT-SHIFT instruction format
123//
124class FEXT_SHIFT16_ins<bits<2> _f, string asmstr, InstrItinClass itin>:
Akira Hatanaka22bec282012-08-03 22:57:02 +0000125 FEXT_SHIFT16<_f, (outs CPU16Regs:$rx), (ins CPU16Regs:$ry, shamt:$sa),
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000126 !strconcat(asmstr, "\t$rx, $ry, $sa"), [], itin>;
127
Reed Kotler67439242012-10-17 22:29:54 +0000128//
129// EXT-T8I8
130//
131class FEXT_T8I816_ins<bits<3> _func, string asmstr, string asmstr2,
132 InstrItinClass itin>:
133 FEXT_I816<_func, (outs),
134 (ins CPU16Regs:$rx, CPU16Regs:$ry, brtarget:$imm),
135 !strconcat(asmstr2, !strconcat("\t$rx, $ry\n\t",
136 !strconcat(asmstr, "\t$imm"))),[], itin> {
137 let isCodeGenOnly=1;
138}
139
140//
141// EXT-T8I8I
142//
143class FEXT_T8I8I16_ins<bits<3> _func, string asmstr, string asmstr2,
144 InstrItinClass itin>:
145 FEXT_I816<_func, (outs),
146 (ins CPU16Regs:$rx, simm16:$imm, brtarget:$targ),
147 !strconcat(asmstr2, !strconcat("\t$rx, $imm\n\t",
148 !strconcat(asmstr, "\t$targ"))), [], itin> {
149 let isCodeGenOnly=1;
150}
151//
152
Reed Kotler0f2e44a2012-10-10 01:58:16 +0000153
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000154//
Reed Kotler0f2e44a2012-10-10 01:58:16 +0000155// I8_MOVR32 instruction format (used only by the MOVR32 instructio
156//
157class FI8_MOVR3216_ins<string asmstr, InstrItinClass itin>:
158 FI8_MOVR3216<(outs CPU16Regs:$rz), (ins CPURegs:$r32),
159 !strconcat(asmstr, "\t$rz, $r32"), [], itin>;
160
161//
162// I8_MOV32R instruction format (used only by MOV32R instruction)
163//
164
165class FI8_MOV32R16_ins<string asmstr, InstrItinClass itin>:
166 FI8_MOV32R16<(outs CPURegs:$r32), (ins CPU16Regs:$rz),
167 !strconcat(asmstr, "\t$r32, $rz"), [], itin>;
168
169//
170// This are pseudo formats for multiply
171// This first one can be changed to non pseudo now.
172//
173// MULT
174//
175class FMULT16_ins<string asmstr, InstrItinClass itin> :
176 MipsPseudo16<(outs), (ins CPU16Regs:$rx, CPU16Regs:$ry),
177 !strconcat(asmstr, "\t$rx, $ry"), []>;
178
179//
180// MULT-LO
181//
182class FMULT16_LO_ins<string asmstr, InstrItinClass itin> :
183 MipsPseudo16<(outs CPU16Regs:$rz), (ins CPU16Regs:$rx, CPU16Regs:$ry),
184 !strconcat(asmstr, "\t$rx, $ry\n\tmflo\t$rz"), []> {
185 let isCodeGenOnly=1;
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000186}
187
188//
Reed Kotler0f2e44a2012-10-10 01:58:16 +0000189// RR-type instruction format
190//
191
192class FRR16_ins<bits<5> f, string asmstr, InstrItinClass itin> :
193 FRR16<f, (outs CPU16Regs:$rx), (ins CPU16Regs:$ry),
194 !strconcat(asmstr, "\t$rx, $ry"), [], itin> {
195}
Reed Kotlercf11c592012-10-12 02:01:09 +0000196
Reed Kotler287f0442012-10-26 04:46:26 +0000197class FRRTR16_ins<bits<5> f, string asmstr, InstrItinClass itin> :
198 FRR16<f, (outs CPU16Regs:$rz), (ins CPU16Regs:$rx, CPU16Regs:$ry),
199 !strconcat(asmstr, "\t$rx, $ry\n\tmove\t$rz, $$t8"), [], itin> ;
200
Reed Kotlercf11c592012-10-12 02:01:09 +0000201//
202// maybe refactor but need a $zero as a dummy first parameter
203//
204class FRR16_div_ins<bits<5> f, string asmstr, InstrItinClass itin> :
205 FRR16<f, (outs ), (ins CPU16Regs:$rx, CPU16Regs:$ry),
206 !strconcat(asmstr, "\t$$zero, $rx, $ry"), [], itin> ;
207
Reed Kotler4e1c6292012-10-26 16:18:19 +0000208class FUnaryRR16_ins<bits<5> f, string asmstr, InstrItinClass itin> :
209 FRR16<f, (outs CPU16Regs:$rx), (ins CPU16Regs:$ry),
210 !strconcat(asmstr, "\t$rx, $ry"), [], itin> ;
211
212
Reed Kotler0f2e44a2012-10-10 01:58:16 +0000213class FRR16_M_ins<bits<5> f, string asmstr,
214 InstrItinClass itin> :
215 FRR16<f, (outs CPU16Regs:$rx), (ins),
216 !strconcat(asmstr, "\t$rx"), [], itin>;
217
218class FRxRxRy16_ins<bits<5> f, string asmstr,
219 InstrItinClass itin> :
220 FRR16<f, (outs CPU16Regs:$rz), (ins CPU16Regs:$rx, CPU16Regs:$ry),
221 !strconcat(asmstr, "\t$rz, $ry"),
222 [], itin> {
223 let Constraints = "$rx = $rz";
224}
225
226let rx=0 in
227class FRR16_JALRC_RA_only_ins<bits<1> nd_, bits<1> l_,
228 string asmstr, InstrItinClass itin>:
229 FRR16_JALRC<nd_, l_, 1, (outs), (ins), !strconcat(asmstr, "\t $$ra"),
230 [], itin> ;
231
232//
233// RRR-type instruction format
234//
235
236class FRRR16_ins<bits<2> _f, string asmstr, InstrItinClass itin> :
237 FRRR16<_f, (outs CPU16Regs:$rz), (ins CPU16Regs:$rx, CPU16Regs:$ry),
238 !strconcat(asmstr, "\t$rz, $rx, $ry"), [], itin>;
239
240//
Reed Kotler097556d2012-10-25 21:33:30 +0000241// These Sel patterns support the generation of conditional move
242// pseudo instructions.
243//
244// The nomenclature uses the components making up the pseudo and may
245// be a bit counter intuitive when compared with the end result we seek.
246// For example using a bqez in the example directly below results in the
247// conditional move being done if the tested register is not zero.
248// I considered in easier to check by keeping the pseudo consistent with
249// it's components but it could have been done differently.
250//
251// The simplest case is when can test and operand directly and do the
252// conditional move based on a simple mips16 conditional
253// branch instruction.
254// for example:
255// if $op == beqz or bnez:
256//
257// $op1 $rt, .+4
258// move $rd, $rs
259//
260// if $op == beqz, then if $rt != 0, then the conditional assignment
261// $rd = $rs is done.
262
263// if $op == bnez, then if $rt == 0, then the conditional assignment
264// $rd = $rs is done.
265//
266// So this pseudo class only has one operand, i.e. op
267//
268class Sel<bits<5> f1, string op, InstrItinClass itin>:
269 MipsInst16_32<(outs CPU16Regs:$rd_), (ins CPU16Regs:$rd, CPU16Regs:$rs,
270 CPU16Regs:$rt),
271 !strconcat(op, "\t$rt, .+4\n\t\n\tmove $rd, $rs"), [], itin,
272 Pseudo16> {
273 let isCodeGenOnly=1;
274 let Constraints = "$rd = $rd_";
275}
276
277//
278// The next two instruction classes allow for an operand which tests
279// two operands and returns a value in register T8 and
280//then does a conditional branch based on the value of T8
281//
282
283// op2 can be cmpi or slti/sltiu
284// op1 can bteqz or btnez
285// the operands for op2 are a register and a signed constant
286//
287// $op2 $t, $imm ;test register t and branch conditionally
288// $op1 .+4 ;op1 is a conditional branch
289// move $rd, $rs
290//
291//
292class SeliT<bits<5> f1, string op1, bits<5> f2, string op2,
293 InstrItinClass itin>:
294 MipsInst16_32<(outs CPU16Regs:$rd_), (ins CPU16Regs:$rd, CPU16Regs:$rs,
295 CPU16Regs:$rl, simm16:$imm),
296 !strconcat(op2,
297 !strconcat("\t$rl, $imm\n\t",
298 !strconcat(op1, "\t.+4\n\tmove $rd, $rs"))), [], itin,
299 Pseudo16> {
300 let isCodeGenOnly=1;
301 let Constraints = "$rd = $rd_";
302}
303
304//
305// op2 can be cmp or slt/sltu
306// op1 can be bteqz or btnez
307// the operands for op2 are two registers
308// op1 is a conditional branch
309//
310//
311// $op2 $rl, $rr ;test registers rl,rr
312// $op1 .+4 ;op2 is a conditional branch
313// move $rd, $rs
314//
315//
316class SelT<bits<5> f1, string op1, bits<5> f2, string op2,
317 InstrItinClass itin>:
318 MipsInst16_32<(outs CPU16Regs:$rd_), (ins CPU16Regs:$rd, CPU16Regs:$rs,
319 CPU16Regs:$rl, CPU16Regs:$rr),
320 !strconcat(op2,
321 !strconcat("\t$rl, $rr\n\t",
322 !strconcat(op1, "\t.+4\n\tmove $rd, $rs"))), [], itin,
323 Pseudo16> {
324 let isCodeGenOnly=1;
325 let Constraints = "$rd = $rd_";
326}
327
328
329//
Akira Hatanaka22bec282012-08-03 22:57:02 +0000330// Some general instruction class info
331//
332//
333
334class ArithLogic16Defs<bit isCom=0> {
335 bits<5> shamt = 0;
336 bit isCommutable = isCom;
337 bit isReMaterializable = 1;
338 bit neverHasSideEffects = 1;
339}
340
Reed Kotler67439242012-10-17 22:29:54 +0000341class branch16 {
342 bit isBranch = 1;
343 bit isTerminator = 1;
344 bit isBarrier = 1;
345}
346
347class cbranch16 {
348 bit isBranch = 1;
349 bit isTerminator = 1;
350}
351
Reed Kotler210ebe92012-09-28 02:26:24 +0000352class MayLoad {
353 bit mayLoad = 1;
354}
355
356class MayStore {
357 bit mayStore = 1;
358}
Akira Hatanaka22bec282012-08-03 22:57:02 +0000359//
Akira Hatanaka64626fc2012-07-26 02:24:43 +0000360
361// Format: ADDIU rx, immediate MIPS16e
362// Purpose: Add Immediate Unsigned Word (2-Operand, Extended)
363// To add a constant to a 32-bit integer.
364//
Akira Hatanaka22bec282012-08-03 22:57:02 +0000365def AddiuRxImmX16: FEXT_RI16_ins<0b01001, "addiu", IIAlu>;
Akira Hatanaka64626fc2012-07-26 02:24:43 +0000366
Akira Hatanaka22bec282012-08-03 22:57:02 +0000367def AddiuRxRxImmX16: FEXT_2RI16_ins<0b01001, "addiu", IIAlu>,
368 ArithLogic16Defs<0>;
Akira Hatanaka64626fc2012-07-26 02:24:43 +0000369
370//
371
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000372// Format: ADDIU rx, pc, immediate MIPS16e
373// Purpose: Add Immediate Unsigned Word (3-Operand, PC-Relative, Extended)
374// To add a constant to the program counter.
375//
Akira Hatanaka22bec282012-08-03 22:57:02 +0000376def AddiuRxPcImmX16: FEXT_RI16_PC_ins<0b00001, "addiu", IIAlu>;
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000377//
378// Format: ADDU rz, rx, ry MIPS16e
379// Purpose: Add Unsigned Word (3-Operand)
380// To add 32-bit integers.
381//
382
Akira Hatanaka22bec282012-08-03 22:57:02 +0000383def AdduRxRyRz16: FRRR16_ins<01, "addu", IIAlu>, ArithLogic16Defs<1>;
384
385//
386// Format: AND rx, ry MIPS16e
387// Purpose: AND
388// To do a bitwise logical AND.
389
390def AndRxRxRy16: FRxRxRy16_ins<0b01100, "and", IIAlu>, ArithLogic16Defs<1>;
Reed Kotler67439242012-10-17 22:29:54 +0000391
392
393//
394// Format: BEQZ rx, offset MIPS16e
395// Purpose: Branch on Equal to Zero (Extended)
396// To test a GPR then do a PC-relative conditional branch.
397//
398def BeqzRxImmX16: FEXT_RI16_B_ins<0b00100, "beqz", IIAlu>, cbranch16;
399
400// Format: B offset MIPS16e
401// Purpose: Unconditional Branch
402// To do an unconditional PC-relative branch.
403//
404def BimmX16: FEXT_I16_ins<0b00010, "b", IIAlu>, branch16;
405
406//
407// Format: BNEZ rx, offset MIPS16e
408// Purpose: Branch on Not Equal to Zero (Extended)
409// To test a GPR then do a PC-relative conditional branch.
410//
411def BnezRxImmX16: FEXT_RI16_B_ins<0b00101, "bnez", IIAlu>, cbranch16;
412
413//
414// Format: BTEQZ offset MIPS16e
415// Purpose: Branch on T Equal to Zero (Extended)
416// To test special register T then do a PC-relative conditional branch.
417//
418def BteqzX16: FEXT_I816_ins<0b000, "bteqz", IIAlu>, cbranch16;
419
420def BteqzT8CmpX16: FEXT_T8I816_ins<0b000, "bteqz", "cmp", IIAlu>, cbranch16;
421
422def BteqzT8CmpiX16: FEXT_T8I8I16_ins<0b000, "bteqz", "cmpi", IIAlu>,
423 cbranch16;
424
425def BteqzT8SltX16: FEXT_T8I816_ins<0b000, "bteqz", "slt", IIAlu>, cbranch16;
426
427def BteqzT8SltuX16: FEXT_T8I816_ins<0b000, "bteqz", "sltu", IIAlu>, cbranch16;
428
429def BteqzT8SltiX16: FEXT_T8I8I16_ins<0b000, "bteqz", "slti", IIAlu>, cbranch16;
430
431def BteqzT8SltiuX16: FEXT_T8I8I16_ins<0b000, "bteqz", "sltiu", IIAlu>,
432 cbranch16;
433
434//
435// Format: BTNEZ offset MIPS16e
436// Purpose: Branch on T Not Equal to Zero (Extended)
437// To test special register T then do a PC-relative conditional branch.
438//
439def BtnezX16: FEXT_I816_ins<0b001, "btnez", IIAlu> ,cbranch16;
440
441def BtnezT8CmpX16: FEXT_T8I816_ins<0b000, "btnez", "cmp", IIAlu>, cbranch16;
442
443def BtnezT8CmpiX16: FEXT_T8I8I16_ins<0b000, "btnez", "cmpi", IIAlu>, cbranch16;
444
445def BtnezT8SltX16: FEXT_T8I816_ins<0b000, "btnez", "slt", IIAlu>, cbranch16;
446
447def BtnezT8SltuX16: FEXT_T8I816_ins<0b000, "btnez", "sltu", IIAlu>, cbranch16;
448
449def BtnezT8SltiX16: FEXT_T8I8I16_ins<0b000, "btnez", "slti", IIAlu>, cbranch16;
450
451def BtnezT8SltiuX16: FEXT_T8I8I16_ins<0b000, "btnez", "sltiu", IIAlu>,
452 cbranch16;
453
Reed Kotlercf11c592012-10-12 02:01:09 +0000454//
455// Format: DIV rx, ry MIPS16e
456// Purpose: Divide Word
457// To divide 32-bit signed integers.
458//
459def DivRxRy16: FRR16_div_ins<0b11010, "div", IIAlu> {
460 let Defs = [HI, LO];
461}
462
463//
464// Format: DIVU rx, ry MIPS16e
465// Purpose: Divide Unsigned Word
466// To divide 32-bit unsigned integers.
467//
468def DivuRxRy16: FRR16_div_ins<0b11011, "divu", IIAlu> {
469 let Defs = [HI, LO];
470}
471
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000472
473//
474// Format: JR ra MIPS16e
475// Purpose: Jump Register Through Register ra
476// To execute a branch to the instruction address in the return
477// address register.
478//
479
480def JrRa16: FRR16_JALRC_RA_only_ins<0, 0, "jr", IIAlu>;
481
482//
Akira Hatanaka22bec282012-08-03 22:57:02 +0000483// Format: LB ry, offset(rx) MIPS16e
484// Purpose: Load Byte (Extended)
485// To load a byte from memory as a signed value.
486//
Reed Kotler210ebe92012-09-28 02:26:24 +0000487def LbRxRyOffMemX16: FEXT_RRI16_mem_ins<0b10011, "lb", mem16, IILoad>, MayLoad;
Akira Hatanaka22bec282012-08-03 22:57:02 +0000488
489//
490// Format: LBU ry, offset(rx) MIPS16e
491// Purpose: Load Byte Unsigned (Extended)
492// To load a byte from memory as a unsigned value.
493//
Reed Kotler210ebe92012-09-28 02:26:24 +0000494def LbuRxRyOffMemX16:
495 FEXT_RRI16_mem_ins<0b10100, "lbu", mem16, IILoad>, MayLoad;
Akira Hatanaka22bec282012-08-03 22:57:02 +0000496
497//
498// Format: LH ry, offset(rx) MIPS16e
499// Purpose: Load Halfword signed (Extended)
500// To load a halfword from memory as a signed value.
501//
Reed Kotler210ebe92012-09-28 02:26:24 +0000502def LhRxRyOffMemX16: FEXT_RRI16_mem_ins<0b10100, "lh", mem16, IILoad>, MayLoad;
Akira Hatanaka22bec282012-08-03 22:57:02 +0000503
504//
505// Format: LHU ry, offset(rx) MIPS16e
506// Purpose: Load Halfword unsigned (Extended)
507// To load a halfword from memory as an unsigned value.
508//
Reed Kotler210ebe92012-09-28 02:26:24 +0000509def LhuRxRyOffMemX16:
510 FEXT_RRI16_mem_ins<0b10100, "lhu", mem16, IILoad>, MayLoad;
Akira Hatanaka22bec282012-08-03 22:57:02 +0000511
512//
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000513// Format: LI rx, immediate MIPS16e
514// Purpose: Load Immediate (Extended)
515// To load a constant into a GPR.
516//
517def LiRxImmX16: FEXT_RI16_ins<0b01101, "li", IIAlu>;
518
519//
520// Format: LW ry, offset(rx) MIPS16e
521// Purpose: Load Word (Extended)
522// To load a word from memory as a signed value.
523//
Reed Kotler210ebe92012-09-28 02:26:24 +0000524def LwRxRyOffMemX16: FEXT_RRI16_mem_ins<0b10011, "lw", mem16, IILoad>, MayLoad;
525
526// Format: LW rx, offset(sp) MIPS16e
527// Purpose: Load Word (SP-Relative, Extended)
528// To load an SP-relative word from memory as a signed value.
529//
530def LwRxSpImmX16: FEXT_RI16_SP_explicit_ins<0b10110, "lw", IILoad>, MayLoad;
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000531
532//
533// Format: MOVE r32, rz MIPS16e
534// Purpose: Move
535// To move the contents of a GPR to a GPR.
536//
Akira Hatanaka0fbaec22012-09-14 03:21:56 +0000537def Move32R16: FI8_MOV32R16_ins<"move", IIAlu>;
538
539//
540// Format: MOVE ry, r32 MIPS16e
541//Purpose: Move
542// To move the contents of a GPR to a GPR.
543//
544def MoveR3216: FI8_MOVR3216_ins<"move", IIAlu>;
Akira Hatanaka22bec282012-08-03 22:57:02 +0000545
546//
Reed Kotler24032212012-10-05 18:27:54 +0000547// Format: MFHI rx MIPS16e
548// Purpose: Move From HI Register
549// To copy the special purpose HI register to a GPR.
550//
551def Mfhi16: FRR16_M_ins<0b10000, "mfhi", IIAlu> {
552 let Uses = [HI];
553 let neverHasSideEffects = 1;
554}
555
556//
557// Format: MFLO rx MIPS16e
558// Purpose: Move From LO Register
559// To copy the special purpose LO register to a GPR.
560//
561def Mflo16: FRR16_M_ins<0b10010, "mflo", IIAlu> {
562 let Uses = [LO];
563 let neverHasSideEffects = 1;
564}
565
566//
567// Pseudo Instruction for mult
568//
569def MultRxRy16: FMULT16_ins<"mult", IIAlu> {
570 let isCommutable = 1;
571 let neverHasSideEffects = 1;
572 let Defs = [HI, LO];
573}
574
575def MultuRxRy16: FMULT16_ins<"multu", IIAlu> {
576 let isCommutable = 1;
577 let neverHasSideEffects = 1;
578 let Defs = [HI, LO];
579}
580
581//
582// Format: MULT rx, ry MIPS16e
583// Purpose: Multiply Word
584// To multiply 32-bit signed integers.
585//
586def MultRxRyRz16: FMULT16_LO_ins<"mult", IIAlu> {
587 let isCommutable = 1;
588 let neverHasSideEffects = 1;
589 let Defs = [HI, LO];
590}
591
592//
593// Format: MULTU rx, ry MIPS16e
594// Purpose: Multiply Unsigned Word
595// To multiply 32-bit unsigned integers.
596//
597def MultuRxRyRz16: FMULT16_LO_ins<"multu", IIAlu> {
598 let isCommutable = 1;
599 let neverHasSideEffects = 1;
600 let Defs = [HI, LO];
601}
602
603//
Akira Hatanaka22bec282012-08-03 22:57:02 +0000604// Format: NEG rx, ry MIPS16e
605// Purpose: Negate
606// To negate an integer value.
607//
Reed Kotler4e1c6292012-10-26 16:18:19 +0000608def NegRxRy16: FUnaryRR16_ins<0b11101, "neg", IIAlu>;
Akira Hatanaka22bec282012-08-03 22:57:02 +0000609
610//
611// Format: NOT rx, ry MIPS16e
612// Purpose: Not
613// To complement an integer value
614//
Reed Kotler4e1c6292012-10-26 16:18:19 +0000615def NotRxRy16: FUnaryRR16_ins<0b01111, "not", IIAlu>;
Akira Hatanaka22bec282012-08-03 22:57:02 +0000616
617//
618// Format: OR rx, ry MIPS16e
619// Purpose: Or
620// To do a bitwise logical OR.
621//
622def OrRxRxRy16: FRxRxRy16_ins<0b01101, "or", IIAlu>, ArithLogic16Defs<1>;
623
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000624//
625// Format: RESTORE {ra,}{s0/s1/s0-1,}{framesize}
626// (All args are optional) MIPS16e
627// Purpose: Restore Registers and Deallocate Stack Frame
628// To deallocate a stack frame before exit from a subroutine,
629// restoring return address and static registers, and adjusting
630// stack
631//
632
633// fixed form for restoring RA and the frame
634// for direct object emitter, encoding needs to be adjusted for the
635// frame size
636//
Akira Hatanakacd04e2b2012-09-21 01:08:16 +0000637let ra=1, s=0,s0=1,s1=1 in
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000638def RestoreRaF16:
639 FI8_SVRS16<0b1, (outs), (ins uimm16:$frame_size),
Reed Kotler210ebe92012-09-28 02:26:24 +0000640 "restore \t$$ra, $$s0, $$s1, $frame_size", [], IILoad >, MayLoad {
Akira Hatanakacd04e2b2012-09-21 01:08:16 +0000641 let isCodeGenOnly = 1;
642}
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000643
644//
645// Format: SAVE {ra,}{s0/s1/s0-1,}{framesize} (All arguments are optional)
646// MIPS16e
647// Purpose: Save Registers and Set Up Stack Frame
648// To set up a stack frame on entry to a subroutine,
649// saving return address and static registers, and adjusting stack
650//
Akira Hatanakacd04e2b2012-09-21 01:08:16 +0000651let ra=1, s=1,s0=1,s1=1 in
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000652def SaveRaF16:
653 FI8_SVRS16<0b1, (outs), (ins uimm16:$frame_size),
Reed Kotler210ebe92012-09-28 02:26:24 +0000654 "save \t$$ra, $$s0, $$s1, $frame_size", [], IIStore >, MayStore {
Akira Hatanakacd04e2b2012-09-21 01:08:16 +0000655 let isCodeGenOnly = 1;
656}
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000657//
Akira Hatanaka22bec282012-08-03 22:57:02 +0000658// Format: SB ry, offset(rx) MIPS16e
659// Purpose: Store Byte (Extended)
660// To store a byte to memory.
661//
Reed Kotler210ebe92012-09-28 02:26:24 +0000662def SbRxRyOffMemX16:
663 FEXT_RRI16_mem2_ins<0b11000, "sb", mem16, IIStore>, MayStore;
Akira Hatanaka22bec282012-08-03 22:57:02 +0000664
665//
Reed Kotler097556d2012-10-25 21:33:30 +0000666// The Sel(T) instructions are pseudos
667// T means that they use T8 implicitly.
668//
669//
670// Format: SelBeqZ rd, rs, rt
671// Purpose: if rt==0, do nothing
672// else rs = rt
673//
674def SelBeqZ: Sel<0b00100, "beqz", IIAlu>;
675
676//
677// Format: SelTBteqZCmp rd, rs, rl, rr
678// Purpose: b = Cmp rl, rr.
679// If b==0 then do nothing.
680// if b!=0 then rd = rs
681//
682def SelTBteqZCmp: SelT<0b000, "bteqz", 0b01010, "cmp", IIAlu>;
683
684//
685// Format: SelTBteqZCmpi rd, rs, rl, rr
686// Purpose: b = Cmpi rl, imm.
687// If b==0 then do nothing.
688// if b!=0 then rd = rs
689//
690def SelTBteqZCmpi: SeliT<0b000, "bteqz", 0b01110, "cmpi", IIAlu>;
691
692//
693// Format: SelTBteqZSlt rd, rs, rl, rr
694// Purpose: b = Slt rl, rr.
695// If b==0 then do nothing.
696// if b!=0 then rd = rs
697//
698def SelTBteqZSlt: SelT<0b000, "bteqz", 0b00010, "slt", IIAlu>;
699
700//
701// Format: SelTBteqZSlti rd, rs, rl, rr
702// Purpose: b = Slti rl, imm.
703// If b==0 then do nothing.
704// if b!=0 then rd = rs
705//
706def SelTBteqZSlti: SeliT<0b000, "bteqz", 0b01010, "slti", IIAlu>;
707
708//
709// Format: SelTBteqZSltu rd, rs, rl, rr
710// Purpose: b = Sltu rl, rr.
711// If b==0 then do nothing.
712// if b!=0 then rd = rs
713//
714def SelTBteqZSltu: SelT<0b000, "bteqz", 0b00011, "sltu", IIAlu>;
715
716//
717// Format: SelTBteqZSltiu rd, rs, rl, rr
718// Purpose: b = Sltiu rl, imm.
719// If b==0 then do nothing.
720// if b!=0 then rd = rs
721//
722def SelTBteqZSltiu: SeliT<0b000, "bteqz", 0b01011, "sltiu", IIAlu>;
723
724//
725// Format: SelBnez rd, rs, rt
726// Purpose: if rt!=0, do nothing
727// else rs = rt
728//
729def SelBneZ: Sel<0b00101, "bnez", IIAlu>;
730
731//
732// Format: SelTBtneZCmp rd, rs, rl, rr
733// Purpose: b = Cmp rl, rr.
734// If b!=0 then do nothing.
735// if b0=0 then rd = rs
736//
737def SelTBtneZCmp: SelT<0b001, "btnez", 0b01010, "cmp", IIAlu>;
738
739//
740// Format: SelTBtnezCmpi rd, rs, rl, rr
741// Purpose: b = Cmpi rl, imm.
742// If b!=0 then do nothing.
743// if b==0 then rd = rs
744//
745def SelTBtneZCmpi: SeliT<0b000, "btnez", 0b01110, "cmpi", IIAlu>;
746
747//
748// Format: SelTBtneZSlt rd, rs, rl, rr
749// Purpose: b = Slt rl, rr.
750// If b!=0 then do nothing.
751// if b==0 then rd = rs
752//
753def SelTBtneZSlt: SelT<0b001, "btnez", 0b00010, "slt", IIAlu>;
754
755//
756// Format: SelTBtneZSlti rd, rs, rl, rr
757// Purpose: b = Slti rl, imm.
758// If b!=0 then do nothing.
759// if b==0 then rd = rs
760//
761def SelTBtneZSlti: SeliT<0b001, "btnez", 0b01010, "slti", IIAlu>;
762
763//
764// Format: SelTBtneZSltu rd, rs, rl, rr
765// Purpose: b = Sltu rl, rr.
766// If b!=0 then do nothing.
767// if b==0 then rd = rs
768//
769def SelTBtneZSltu: SelT<0b001, "btnez", 0b00011, "sltu", IIAlu>;
770
771//
772// Format: SelTBtneZSltiu rd, rs, rl, rr
773// Purpose: b = Slti rl, imm.
774// If b!=0 then do nothing.
775// if b==0 then rd = rs
776//
777def SelTBtneZSltiu: SeliT<0b001, "btnez", 0b01011, "sltiu", IIAlu>;
778//
779//
Akira Hatanaka22bec282012-08-03 22:57:02 +0000780// Format: SH ry, offset(rx) MIPS16e
781// Purpose: Store Halfword (Extended)
782// To store a halfword to memory.
783//
Reed Kotler210ebe92012-09-28 02:26:24 +0000784def ShRxRyOffMemX16:
785 FEXT_RRI16_mem2_ins<0b11001, "sh", mem16, IIStore>, MayStore;
Akira Hatanaka22bec282012-08-03 22:57:02 +0000786
787//
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000788// Format: SLL rx, ry, sa MIPS16e
789// Purpose: Shift Word Left Logical (Extended)
790// To execute a left-shift of a word by a fixed number of bits—0 to 31 bits.
791//
792def SllX16: FEXT_SHIFT16_ins<0b00, "sll", IIAlu>;
793
794//
Akira Hatanaka22bec282012-08-03 22:57:02 +0000795// Format: SLLV ry, rx MIPS16e
796// Purpose: Shift Word Left Logical Variable
797// To execute a left-shift of a word by a variable number of bits.
798//
799def SllvRxRy16 : FRxRxRy16_ins<0b00100, "sllv", IIAlu>;
800
Reed Kotler164bb372012-10-23 01:35:48 +0000801//
802// Format: SLTI rx, immediate MIPS16e
803// Purpose: Set on Less Than Immediate (Extended)
804// To record the result of a less-than comparison with a constant.
805//
806def SltiCCRxImmX16: FEXT_CCRXI16_ins<0b01010, "slti", IIAlu>;
Akira Hatanaka22bec282012-08-03 22:57:02 +0000807
808//
Reed Kotler164bb372012-10-23 01:35:48 +0000809// Format: SLTIU rx, immediate MIPS16e
810// Purpose: Set on Less Than Immediate Unsigned (Extended)
811// To record the result of a less-than comparison with a constant.
812//
813def SltiuCCRxImmX16: FEXT_CCRXI16_ins<0b01011, "sltiu", IIAlu>;
814
815//
816// Format: SLT rx, ry MIPS16e
817// Purpose: Set on Less Than
818// To record the result of a less-than comparison.
819//
820def SltRxRy16: FRR16_ins<0b00010, "slt", IIAlu>;
821
822def SltCCRxRy16: FCCRR16_ins<0b00010, "slt", IIAlu>;
823
824// Format: SLTU rx, ry MIPS16e
825// Purpose: Set on Less Than Unsigned
826// To record the result of an unsigned less-than comparison.
827//
Reed Kotler287f0442012-10-26 04:46:26 +0000828def SltuRxRyRz16: FRRTR16_ins<0b00011, "sltu", IIAlu> {
829 let isCodeGenOnly=1;
830}
Reed Kotler164bb372012-10-23 01:35:48 +0000831
832
833def SltuCCRxRy16: FCCRR16_ins<0b00011, "sltu", IIAlu>;
834//
Akira Hatanaka22bec282012-08-03 22:57:02 +0000835// Format: SRAV ry, rx MIPS16e
836// Purpose: Shift Word Right Arithmetic Variable
837// To execute an arithmetic right-shift of a word by a variable
838// number of bits.
839//
840def SravRxRy16: FRxRxRy16_ins<0b00111, "srav", IIAlu>;
841
842
843//
844// Format: SRA rx, ry, sa MIPS16e
845// Purpose: Shift Word Right Arithmetic (Extended)
846// To execute an arithmetic right-shift of a word by a fixed
847// number of bits—1 to 8 bits.
848//
849def SraX16: FEXT_SHIFT16_ins<0b11, "sra", IIAlu>;
850
851
852//
853// Format: SRLV ry, rx MIPS16e
854// Purpose: Shift Word Right Logical Variable
855// To execute a logical right-shift of a word by a variable
856// number of bits.
857//
858def SrlvRxRy16: FRxRxRy16_ins<0b00110, "srlv", IIAlu>;
859
860
861//
862// Format: SRL rx, ry, sa MIPS16e
863// Purpose: Shift Word Right Logical (Extended)
864// To execute a logical right-shift of a word by a fixed
865// number of bits—1 to 31 bits.
866//
867def SrlX16: FEXT_SHIFT16_ins<0b10, "srl", IIAlu>;
868
869//
870// Format: SUBU rz, rx, ry MIPS16e
871// Purpose: Subtract Unsigned Word
872// To subtract 32-bit integers
873//
874def SubuRxRyRz16: FRRR16_ins<0b11, "subu", IIAlu>, ArithLogic16Defs<0>;
875
876//
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000877// Format: SW ry, offset(rx) MIPS16e
878// Purpose: Store Word (Extended)
879// To store a word to memory.
880//
Reed Kotler210ebe92012-09-28 02:26:24 +0000881def SwRxRyOffMemX16:
882 FEXT_RRI16_mem2_ins<0b11011, "sw", mem16, IIStore>, MayStore;
Akira Hatanaka22bec282012-08-03 22:57:02 +0000883
884//
Reed Kotler210ebe92012-09-28 02:26:24 +0000885// Format: SW rx, offset(sp) MIPS16e
886// Purpose: Store Word rx (SP-Relative)
887// To store an SP-relative word to memory.
888//
889def SwRxSpImmX16: FEXT_RI16_SP_explicit_ins<0b11010, "sw", IIStore>, MayStore;
890
891//
892//
Akira Hatanaka22bec282012-08-03 22:57:02 +0000893// Format: XOR rx, ry MIPS16e
894// Purpose: Xor
895// To do a bitwise logical XOR.
896//
897def XorRxRxRy16: FRxRxRy16_ins<0b01110, "xor", IIAlu>, ArithLogic16Defs<1>;
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000898
Akira Hatanaka765c3122012-06-21 20:39:10 +0000899class Mips16Pat<dag pattern, dag result> : Pat<pattern, result> {
900 let Predicates = [InMips16Mode];
901}
902
Akira Hatanaka22bec282012-08-03 22:57:02 +0000903// Unary Arith/Logic
904//
905class ArithLogicU_pat<PatFrag OpNode, Instruction I> :
906 Mips16Pat<(OpNode CPU16Regs:$r),
907 (I CPU16Regs:$r)>;
Akira Hatanakabff8e312012-05-31 02:59:44 +0000908
Akira Hatanaka22bec282012-08-03 22:57:02 +0000909def: ArithLogicU_pat<not, NotRxRy16>;
910def: ArithLogicU_pat<ineg, NegRxRy16>;
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000911
Akira Hatanaka22bec282012-08-03 22:57:02 +0000912class ArithLogic16_pat<SDNode OpNode, Instruction I> :
913 Mips16Pat<(OpNode CPU16Regs:$l, CPU16Regs:$r),
914 (I CPU16Regs:$l, CPU16Regs:$r)>;
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000915
Akira Hatanaka22bec282012-08-03 22:57:02 +0000916def: ArithLogic16_pat<add, AdduRxRyRz16>;
917def: ArithLogic16_pat<and, AndRxRxRy16>;
Reed Kotler24032212012-10-05 18:27:54 +0000918def: ArithLogic16_pat<mul, MultRxRyRz16>;
Akira Hatanaka22bec282012-08-03 22:57:02 +0000919def: ArithLogic16_pat<or, OrRxRxRy16>;
920def: ArithLogic16_pat<sub, SubuRxRyRz16>;
921def: ArithLogic16_pat<xor, XorRxRxRy16>;
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000922
Akira Hatanaka22bec282012-08-03 22:57:02 +0000923// Arithmetic and logical instructions with 2 register operands.
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000924
Akira Hatanaka22bec282012-08-03 22:57:02 +0000925class ArithLogicI16_pat<SDNode OpNode, PatFrag imm_type, Instruction I> :
926 Mips16Pat<(OpNode CPU16Regs:$in, imm_type:$imm),
927 (I CPU16Regs:$in, imm_type:$imm)>;
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000928
Akira Hatanaka22bec282012-08-03 22:57:02 +0000929def: ArithLogicI16_pat<add, immSExt16, AddiuRxRxImmX16>;
930def: ArithLogicI16_pat<shl, immZExt5, SllX16>;
931def: ArithLogicI16_pat<srl, immZExt5, SrlX16>;
932def: ArithLogicI16_pat<sra, immZExt5, SraX16>;
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000933
Akira Hatanaka22bec282012-08-03 22:57:02 +0000934class shift_rotate_reg16_pat<SDNode OpNode, Instruction I> :
935 Mips16Pat<(OpNode CPU16Regs:$r, CPU16Regs:$ra),
936 (I CPU16Regs:$r, CPU16Regs:$ra)>;
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000937
Akira Hatanaka22bec282012-08-03 22:57:02 +0000938def: shift_rotate_reg16_pat<shl, SllvRxRy16>;
939def: shift_rotate_reg16_pat<sra, SravRxRy16>;
940def: shift_rotate_reg16_pat<srl, SrlvRxRy16>;
941
942class LoadM16_pat<PatFrag OpNode, Instruction I> :
943 Mips16Pat<(OpNode addr:$addr), (I addr:$addr)>;
944
945def: LoadM16_pat<sextloadi8, LbRxRyOffMemX16>;
946def: LoadM16_pat<zextloadi8, LbuRxRyOffMemX16>;
Akira Hatanaka3e7ba762012-09-15 01:52:08 +0000947def: LoadM16_pat<sextloadi16, LhRxRyOffMemX16>;
948def: LoadM16_pat<zextloadi16, LhuRxRyOffMemX16>;
949def: LoadM16_pat<load, LwRxRyOffMemX16>;
Akira Hatanaka22bec282012-08-03 22:57:02 +0000950
951class StoreM16_pat<PatFrag OpNode, Instruction I> :
952 Mips16Pat<(OpNode CPU16Regs:$r, addr:$addr), (I CPU16Regs:$r, addr:$addr)>;
953
954def: StoreM16_pat<truncstorei8, SbRxRyOffMemX16>;
Akira Hatanaka3e7ba762012-09-15 01:52:08 +0000955def: StoreM16_pat<truncstorei16, ShRxRyOffMemX16>;
956def: StoreM16_pat<store, SwRxRyOffMemX16>;
Akira Hatanaka22bec282012-08-03 22:57:02 +0000957
Reed Kotler67439242012-10-17 22:29:54 +0000958// Unconditional branch
959class UncondBranch16_pat<SDNode OpNode, Instruction I>:
960 Mips16Pat<(OpNode bb:$imm16), (I bb:$imm16)> {
961 let Predicates = [RelocPIC, InMips16Mode];
962 }
Akira Hatanakabff8e312012-05-31 02:59:44 +0000963
964// Jump and Link (Call)
Akira Hatanakaf640f042012-07-17 22:55:34 +0000965let isCall=1, hasDelaySlot=1 in
Akira Hatanakabff8e312012-05-31 02:59:44 +0000966def JumpLinkReg16:
Akira Hatanakaf640f042012-07-17 22:55:34 +0000967 FRR16_JALRC<0, 0, 0, (outs), (ins CPU16Regs:$rs),
968 "jalr \t$rs", [(MipsJmpLink CPU16Regs:$rs)], IIBranch>;
969
Akira Hatanaka26e9ecb2012-07-23 23:45:54 +0000970// Mips16 pseudos
971let isReturn=1, isTerminator=1, hasDelaySlot=1, isBarrier=1, hasCtrlDep=1,
972 hasExtraSrcRegAllocReq = 1 in
973def RetRA16 : MipsPseudo16<(outs), (ins), "", [(MipsRet)]>;
974
Reed Kotler67439242012-10-17 22:29:54 +0000975
Reed Kotler164bb372012-10-23 01:35:48 +0000976// setcc patterns
977
978class SetCC_R16<PatFrag cond_op, Instruction I>:
979 Mips16Pat<(cond_op CPU16Regs:$rx, CPU16Regs:$ry),
980 (I CPU16Regs:$rx, CPU16Regs:$ry)>;
981
982class SetCC_I16<PatFrag cond_op, PatLeaf imm_type, Instruction I>:
983 Mips16Pat<(cond_op CPU16Regs:$rx, imm_type:$imm16),
Reed Kotler097556d2012-10-25 21:33:30 +0000984 (I CPU16Regs:$rx, imm_type:$imm16)>;
Reed Kotler164bb372012-10-23 01:35:48 +0000985
Reed Kotlere47873a2012-10-26 03:09:34 +0000986// Large (>16 bit) immediate loads
987def : Mips16Pat<(i32 imm:$imm),
988 (OrRxRxRy16 (SllX16 (LiRxImmX16 (HI16 imm:$imm)), 16),
989 (LiRxImmX16 (LO16 imm:$imm)))>;
Reed Kotler164bb372012-10-23 01:35:48 +0000990
Reed Kotler287f0442012-10-26 04:46:26 +0000991// Carry MipsPatterns
992def : Mips16Pat<(subc CPU16Regs:$lhs, CPU16Regs:$rhs),
993 (SubuRxRyRz16 CPU16Regs:$lhs, CPU16Regs:$rhs)>;
994def : Mips16Pat<(addc CPU16Regs:$lhs, CPU16Regs:$rhs),
995 (AdduRxRyRz16 CPU16Regs:$lhs, CPU16Regs:$rhs)>;
996def : Mips16Pat<(addc CPU16Regs:$src, immSExt16:$imm),
997 (AddiuRxRxImmX16 CPU16Regs:$src, imm:$imm)>;
998
Reed Kotler67439242012-10-17 22:29:54 +0000999//
1000// Some branch conditional patterns are not generated by llvm at this time.
1001// Some are for seemingly arbitrary reasons not used: i.e. with signed number
1002// comparison they are used and for unsigned a different pattern is used.
1003// I am pushing upstream from the full mips16 port and it seemed that I needed
1004// these earlier and the mips32 port has these but now I cannot create test
1005// cases that use these patterns. While I sort this all out I will leave these
1006// extra patterns commented out and if I can be sure they are really not used,
1007// I will delete the code. I don't want to check the code in uncommented without
1008// a valid test case. In some cases, the compiler is generating patterns with
1009// setcc instead and earlier I had implemented setcc first so may have masked
1010// the problem. The setcc variants are suboptimal for mips16 so I may wantto
1011// figure out how to enable the brcond patterns or else possibly new
1012// combinations of of brcond and setcc.
1013//
1014//
1015// bcond-seteq
1016//
1017def: Mips16Pat
1018 <(brcond (i32 (seteq CPU16Regs:$rx, CPU16Regs:$ry)), bb:$imm16),
1019 (BteqzT8CmpX16 CPU16Regs:$rx, CPU16Regs:$ry, bb:$imm16)
1020 >;
1021
1022
1023def: Mips16Pat
1024 <(brcond (i32 (seteq CPU16Regs:$rx, immZExt16:$imm)), bb:$targ16),
1025 (BteqzT8CmpiX16 CPU16Regs:$rx, immSExt16:$imm, bb:$targ16)
1026 >;
1027
1028def: Mips16Pat
1029 <(brcond (i32 (seteq CPU16Regs:$rx, 0)), bb:$targ16),
1030 (BeqzRxImmX16 CPU16Regs:$rx, bb:$targ16)
1031 >;
1032
1033//
1034// bcond-setgt (do we need to have this pair of setlt, setgt??)
1035//
1036def: Mips16Pat
1037 <(brcond (i32 (setgt CPU16Regs:$rx, CPU16Regs:$ry)), bb:$imm16),
1038 (BtnezT8SltX16 CPU16Regs:$ry, CPU16Regs:$rx, bb:$imm16)
1039 >;
1040
1041//
1042// bcond-setge
1043//
1044def: Mips16Pat
1045 <(brcond (i32 (setge CPU16Regs:$rx, CPU16Regs:$ry)), bb:$imm16),
1046 (BteqzT8SltX16 CPU16Regs:$rx, CPU16Regs:$ry, bb:$imm16)
1047 >;
1048
1049//
1050// never called because compiler transforms a >= k to a > (k-1)
Reed Kotler164bb372012-10-23 01:35:48 +00001051def: Mips16Pat
1052 <(brcond (i32 (setge CPU16Regs:$rx, immSExt16:$imm)), bb:$imm16),
1053 (BteqzT8SltiX16 CPU16Regs:$rx, immSExt16:$imm, bb:$imm16)
1054 >;
Reed Kotler67439242012-10-17 22:29:54 +00001055
1056//
1057// bcond-setlt
1058//
1059def: Mips16Pat
1060 <(brcond (i32 (setlt CPU16Regs:$rx, CPU16Regs:$ry)), bb:$imm16),
1061 (BtnezT8SltX16 CPU16Regs:$rx, CPU16Regs:$ry, bb:$imm16)
1062 >;
1063
1064def: Mips16Pat
1065 <(brcond (i32 (setlt CPU16Regs:$rx, immSExt16:$imm)), bb:$imm16),
1066 (BtnezT8SltiX16 CPU16Regs:$rx, immSExt16:$imm, bb:$imm16)
1067 >;
1068
1069//
1070// bcond-setle
1071//
1072def: Mips16Pat
1073 <(brcond (i32 (setle CPU16Regs:$rx, CPU16Regs:$ry)), bb:$imm16),
1074 (BteqzT8SltX16 CPU16Regs:$ry, CPU16Regs:$rx, bb:$imm16)
1075 >;
1076
1077//
1078// bcond-setne
1079//
1080def: Mips16Pat
1081 <(brcond (i32 (setne CPU16Regs:$rx, CPU16Regs:$ry)), bb:$imm16),
1082 (BtnezT8CmpX16 CPU16Regs:$rx, CPU16Regs:$ry, bb:$imm16)
1083 >;
1084
1085def: Mips16Pat
1086 <(brcond (i32 (setne CPU16Regs:$rx, immZExt16:$imm)), bb:$targ16),
1087 (BtnezT8CmpiX16 CPU16Regs:$rx, immSExt16:$imm, bb:$targ16)
1088 >;
1089
1090def: Mips16Pat
1091 <(brcond (i32 (setne CPU16Regs:$rx, 0)), bb:$targ16),
1092 (BnezRxImmX16 CPU16Regs:$rx, bb:$targ16)
1093 >;
1094
1095//
1096// This needs to be there but I forget which code will generate it
1097//
1098def: Mips16Pat
1099 <(brcond CPU16Regs:$rx, bb:$targ16),
1100 (BnezRxImmX16 CPU16Regs:$rx, bb:$targ16)
1101 >;
1102
1103//
1104
1105//
1106// bcond-setugt
1107//
1108//def: Mips16Pat
1109// <(brcond (i32 (setugt CPU16Regs:$rx, CPU16Regs:$ry)), bb:$imm16),
1110// (BtnezT8SltuX16 CPU16Regs:$ry, CPU16Regs:$rx, bb:$imm16)
1111// >;
1112
1113//
1114// bcond-setuge
1115//
1116//def: Mips16Pat
1117// <(brcond (i32 (setuge CPU16Regs:$rx, CPU16Regs:$ry)), bb:$imm16),
1118// (BteqzT8SltuX16 CPU16Regs:$rx, CPU16Regs:$ry, bb:$imm16)
1119// >;
1120
1121
1122//
1123// bcond-setult
1124//
1125//def: Mips16Pat
1126// <(brcond (i32 (setult CPU16Regs:$rx, CPU16Regs:$ry)), bb:$imm16),
1127// (BtnezT8SltuX16 CPU16Regs:$rx, CPU16Regs:$ry, bb:$imm16)
1128// >;
1129
1130def: UncondBranch16_pat<br, BimmX16>;
1131
Akira Hatanaka765c3122012-06-21 20:39:10 +00001132// Small immediates
Reed Kotler67439242012-10-17 22:29:54 +00001133def: Mips16Pat<(i32 immSExt16:$in),
1134 (AddiuRxRxImmX16 (Move32R16 ZERO), immSExt16:$in)>;
1135
Akira Hatanaka22bec282012-08-03 22:57:02 +00001136def: Mips16Pat<(i32 immZExt16:$in), (LiRxImmX16 immZExt16:$in)>;
Akira Hatanaka64626fc2012-07-26 02:24:43 +00001137
Reed Kotlercf11c592012-10-12 02:01:09 +00001138//
1139// MipsDivRem
1140//
1141def: Mips16Pat
1142 <(MipsDivRem CPU16Regs:$rx, CPU16Regs:$ry),
1143 (DivRxRy16 CPU16Regs:$rx, CPU16Regs:$ry)>;
1144
1145//
1146// MipsDivRemU
1147//
1148def: Mips16Pat
1149 <(MipsDivRemU CPU16Regs:$rx, CPU16Regs:$ry),
1150 (DivuRxRy16 CPU16Regs:$rx, CPU16Regs:$ry)>;
1151
Reed Kotler097556d2012-10-25 21:33:30 +00001152// signed a,b
1153// x = (a>=b)?x:y
1154//
1155// if !(a < b) x = y
1156//
1157def : Mips16Pat<(select (i32 (setge CPU16Regs:$a, CPU16Regs:$b)),
1158 CPU16Regs:$x, CPU16Regs:$y),
1159 (SelTBteqZSlt CPU16Regs:$x, CPU16Regs:$y,
1160 CPU16Regs:$a, CPU16Regs:$b)>;
1161
1162// signed a,b
1163// x = (a>b)?x:y
1164//
1165// if (b < a) x = y
1166//
1167def : Mips16Pat<(select (i32 (setgt CPU16Regs:$a, CPU16Regs:$b)),
1168 CPU16Regs:$x, CPU16Regs:$y),
1169 (SelTBtneZSlt CPU16Regs:$x, CPU16Regs:$y,
1170 CPU16Regs:$b, CPU16Regs:$a)>;
1171
1172// unsigned a,b
1173// x = (a>=b)?x:y
1174//
1175// if !(a < b) x = y;
1176//
1177def : Mips16Pat<
1178 (select (i32 (setuge CPU16Regs:$a, CPU16Regs:$b)),
1179 CPU16Regs:$x, CPU16Regs:$y),
1180 (SelTBteqZSltu CPU16Regs:$x, CPU16Regs:$y,
1181 CPU16Regs:$a, CPU16Regs:$b)>;
1182
1183// unsigned a,b
1184// x = (a>b)?x:y
1185//
1186// if (b < a) x = y
1187//
1188def : Mips16Pat<(select (i32 (setugt CPU16Regs:$a, CPU16Regs:$b)),
1189 CPU16Regs:$x, CPU16Regs:$y),
1190 (SelTBtneZSltu CPU16Regs:$x, CPU16Regs:$y,
1191 CPU16Regs:$b, CPU16Regs:$a)>;
1192
1193// signed
1194// x = (a >= k)?x:y
1195// due to an llvm optimization, i don't think that this will ever
1196// be used. This is transformed into x = (a > k-1)?x:y
1197//
1198//
1199
1200//def : Mips16Pat<
1201// (select (i32 (setge CPU16Regs:$lhs, immSExt16:$rhs)),
1202// CPU16Regs:$T, CPU16Regs:$F),
1203// (SelTBteqZSlti CPU16Regs:$T, CPU16Regs:$F,
1204// CPU16Regs:$lhs, immSExt16:$rhs)>;
1205
1206//def : Mips16Pat<
1207// (select (i32 (setuge CPU16Regs:$lhs, immSExt16:$rhs)),
1208// CPU16Regs:$T, CPU16Regs:$F),
1209// (SelTBteqZSltiu CPU16Regs:$T, CPU16Regs:$F,
1210// CPU16Regs:$lhs, immSExt16:$rhs)>;
1211
1212// signed
1213// x = (a < k)?x:y
1214//
1215// if !(a < k) x = y;
1216//
1217def : Mips16Pat<
1218 (select (i32 (setlt CPU16Regs:$a, immSExt16:$b)),
1219 CPU16Regs:$x, CPU16Regs:$y),
1220 (SelTBtneZSlti CPU16Regs:$x, CPU16Regs:$y,
1221 CPU16Regs:$a, immSExt16:$b)>;
1222
1223
1224//
1225//
1226// signed
1227// x = (a <= b)? x : y
1228//
1229// if (b < a) x = y
1230//
1231def : Mips16Pat<(select (i32 (setle CPU16Regs:$a, CPU16Regs:$b)),
1232 CPU16Regs:$x, CPU16Regs:$y),
1233 (SelTBteqZSlt CPU16Regs:$x, CPU16Regs:$y,
1234 CPU16Regs:$b, CPU16Regs:$a)>;
1235
1236//
1237// unnsigned
1238// x = (a <= b)? x : y
1239//
1240// if (b < a) x = y
1241//
1242def : Mips16Pat<(select (i32 (setule CPU16Regs:$a, CPU16Regs:$b)),
1243 CPU16Regs:$x, CPU16Regs:$y),
1244 (SelTBteqZSltu CPU16Regs:$x, CPU16Regs:$y,
1245 CPU16Regs:$b, CPU16Regs:$a)>;
1246
1247//
1248// signed/unsigned
1249// x = (a == b)? x : y
1250//
1251// if (a != b) x = y
1252//
1253def : Mips16Pat<(select (i32 (seteq CPU16Regs:$a, CPU16Regs:$b)),
1254 CPU16Regs:$x, CPU16Regs:$y),
1255 (SelTBteqZCmp CPU16Regs:$x, CPU16Regs:$y,
1256 CPU16Regs:$b, CPU16Regs:$a)>;
1257
1258//
1259// signed/unsigned
1260// x = (a == 0)? x : y
1261//
1262// if (a != 0) x = y
1263//
1264def : Mips16Pat<(select (i32 (seteq CPU16Regs:$a, 0)),
1265 CPU16Regs:$x, CPU16Regs:$y),
1266 (SelBeqZ CPU16Regs:$x, CPU16Regs:$y,
1267 CPU16Regs:$a)>;
1268
1269
1270//
1271// signed/unsigned
1272// x = (a == k)? x : y
1273//
1274// if (a != k) x = y
1275//
1276def : Mips16Pat<(select (i32 (seteq CPU16Regs:$a, immZExt16:$k)),
1277 CPU16Regs:$x, CPU16Regs:$y),
1278 (SelTBteqZCmpi CPU16Regs:$x, CPU16Regs:$y,
1279 CPU16Regs:$a, immZExt16:$k)>;
1280
1281
1282//
1283// signed/unsigned
1284// x = (a != b)? x : y
1285//
1286// if (a == b) x = y
1287//
1288//
1289def : Mips16Pat<(select (i32 (setne CPU16Regs:$a, CPU16Regs:$b)),
1290 CPU16Regs:$x, CPU16Regs:$y),
1291 (SelTBtneZCmp CPU16Regs:$x, CPU16Regs:$y,
1292 CPU16Regs:$b, CPU16Regs:$a)>;
1293
1294//
1295// signed/unsigned
1296// x = (a != 0)? x : y
1297//
1298// if (a == 0) x = y
1299//
1300def : Mips16Pat<(select (i32 (setne CPU16Regs:$a, 0)),
1301 CPU16Regs:$x, CPU16Regs:$y),
1302 (SelBneZ CPU16Regs:$x, CPU16Regs:$y,
1303 CPU16Regs:$a)>;
1304
1305// signed/unsigned
1306// x = (a)? x : y
1307//
1308// if (!a) x = y
1309//
1310def : Mips16Pat<(select CPU16Regs:$a,
1311 CPU16Regs:$x, CPU16Regs:$y),
1312 (SelBneZ CPU16Regs:$x, CPU16Regs:$y,
1313 CPU16Regs:$a)>;
1314
1315
1316//
1317// signed/unsigned
1318// x = (a != k)? x : y
1319//
1320// if (a == k) x = y
1321//
1322def : Mips16Pat<(select (i32 (setne CPU16Regs:$a, immZExt16:$k)),
1323 CPU16Regs:$x, CPU16Regs:$y),
1324 (SelTBtneZCmpi CPU16Regs:$x, CPU16Regs:$y,
1325 CPU16Regs:$a, immZExt16:$k)>;
Reed Kotlercf11c592012-10-12 02:01:09 +00001326
Reed Kotler164bb372012-10-23 01:35:48 +00001327//
1328// When writing C code to test setxx these patterns,
1329// some will be transformed into
1330// other things. So we test using C code but using -O3 and -O0
1331//
1332// seteq
1333//
1334def : Mips16Pat
1335 <(seteq CPU16Regs:$lhs,CPU16Regs:$rhs),
1336 (SltiuCCRxImmX16 (XorRxRxRy16 CPU16Regs:$lhs, CPU16Regs:$rhs), 1)>;
1337
1338def : Mips16Pat
1339 <(seteq CPU16Regs:$lhs, 0),
1340 (SltiuCCRxImmX16 CPU16Regs:$lhs, 1)>;
1341
1342
1343//
1344// setge
1345//
1346
1347def: Mips16Pat
1348 <(setge CPU16Regs:$lhs, CPU16Regs:$rhs),
1349 (XorRxRxRy16 (SltCCRxRy16 CPU16Regs:$lhs, CPU16Regs:$rhs),
1350 (LiRxImmX16 1))>;
1351
1352//
1353// For constants, llvm transforms this to:
1354// x > (k -1) and then reverses the operands to use setlt. So this pattern
1355// is not used now by the compiler. (Presumably checking that k-1 does not
1356// overflow). The compiler never uses this at a the current time, due to
1357// other optimizations.
1358//
1359//def: Mips16Pat
1360// <(setge CPU16Regs:$lhs, immSExt16:$rhs),
1361// (XorRxRxRy16 (SltiCCRxImmX16 CPU16Regs:$lhs, immSExt16:$rhs),
1362// (LiRxImmX16 1))>;
1363
1364// This catches the x >= -32768 case by transforming it to x > -32769
1365//
1366def: Mips16Pat
1367 <(setgt CPU16Regs:$lhs, -32769),
1368 (XorRxRxRy16 (SltiCCRxImmX16 CPU16Regs:$lhs, -32768),
1369 (LiRxImmX16 1))>;
1370
1371//
1372// setgt
1373//
1374//
1375
1376def: Mips16Pat
1377 <(setgt CPU16Regs:$lhs, CPU16Regs:$rhs),
1378 (SltCCRxRy16 CPU16Regs:$rhs, CPU16Regs:$lhs)>;
1379
1380//
1381// setle
1382//
1383def: Mips16Pat
1384 <(setle CPU16Regs:$lhs, CPU16Regs:$rhs),
1385 (XorRxRxRy16 (SltCCRxRy16 CPU16Regs:$rhs, CPU16Regs:$lhs), (LiRxImmX16 1))>;
1386
1387//
1388// setlt
1389//
1390def: SetCC_R16<setlt, SltCCRxRy16>;
1391
1392def: SetCC_I16<setlt, immSExt16, SltiCCRxImmX16>;
1393
1394//
1395// setne
1396//
1397def : Mips16Pat
1398 <(setne CPU16Regs:$lhs,CPU16Regs:$rhs),
1399 (SltuCCRxRy16 (LiRxImmX16 0),
1400 (XorRxRxRy16 CPU16Regs:$lhs, CPU16Regs:$rhs))>;
1401
1402
1403//
1404// setuge
1405//
1406def: Mips16Pat
1407 <(setuge CPU16Regs:$lhs, CPU16Regs:$rhs),
1408 (XorRxRxRy16 (SltuCCRxRy16 CPU16Regs:$lhs, CPU16Regs:$rhs),
1409 (LiRxImmX16 1))>;
1410
1411// this pattern will never be used because the compiler will transform
1412// x >= k to x > (k - 1) and then use SLT
1413//
1414//def: Mips16Pat
1415// <(setuge CPU16Regs:$lhs, immZExt16:$rhs),
1416// (XorRxRxRy16 (SltiuCCRxImmX16 CPU16Regs:$lhs, immZExt16:$rhs),
Reed Kotler097556d2012-10-25 21:33:30 +00001417// (LiRxImmX16 1))>;
Reed Kotler164bb372012-10-23 01:35:48 +00001418
1419//
1420// setugt
1421//
1422def: Mips16Pat
1423 <(setugt CPU16Regs:$lhs, CPU16Regs:$rhs),
1424 (SltuCCRxRy16 CPU16Regs:$rhs, CPU16Regs:$lhs)>;
1425
1426//
1427// setule
1428//
1429def: Mips16Pat
1430 <(setule CPU16Regs:$lhs, CPU16Regs:$rhs),
1431 (XorRxRxRy16 (SltuCCRxRy16 CPU16Regs:$rhs, CPU16Regs:$lhs), (LiRxImmX16 1))>;
1432
1433//
1434// setult
1435//
1436def: SetCC_R16<setult, SltuCCRxRy16>;
1437
1438def: SetCC_I16<setult, immSExt16, SltiuCCRxImmX16>;
1439
Akira Hatanaka22bec282012-08-03 22:57:02 +00001440def: Mips16Pat<(add CPU16Regs:$hi, (MipsLo tglobaladdr:$lo)),
1441 (AddiuRxRxImmX16 CPU16Regs:$hi, tglobaladdr:$lo)>;