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