1. Finishing MBlaze MC asm parser test cases
[oota-llvm.git] / lib / Target / MBlaze / MBlazeInstrInfo.td
1 //===- MBlazeInstrInfo.td - MBlaze Instruction defs --------*- 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 //===----------------------------------------------------------------------===//
11 // Instruction format superclass
12 //===----------------------------------------------------------------------===//
13 include "MBlazeInstrFormats.td"
14
15 //===----------------------------------------------------------------------===//
16 // MBlaze type profiles
17 //===----------------------------------------------------------------------===//
18
19 // def SDTMBlazeSelectCC : SDTypeProfile<1, 3, [SDTCisSameAs<0, 1>]>;
20 def SDT_MBlazeRet     : SDTypeProfile<0, 1, [SDTCisInt<0>]>;
21 def SDT_MBlazeJmpLink : SDTypeProfile<0, 1, [SDTCisVT<0, i32>]>;
22 def SDT_MBCallSeqStart : SDCallSeqStart<[SDTCisVT<0, i32>]>;
23 def SDT_MBCallSeqEnd   : SDCallSeqEnd<[SDTCisVT<0, i32>, SDTCisVT<1, i32>]>;
24
25 //===----------------------------------------------------------------------===//
26 // MBlaze specific nodes
27 //===----------------------------------------------------------------------===//
28
29 def MBlazeRet     : SDNode<"MBlazeISD::Ret", SDT_MBlazeRet,
30                            [SDNPHasChain, SDNPOptInFlag]>;
31
32 def MBlazeJmpLink : SDNode<"MBlazeISD::JmpLink",SDT_MBlazeJmpLink,
33                            [SDNPHasChain,SDNPOptInFlag,SDNPOutFlag]>;
34
35 def MBWrapper   : SDNode<"MBlazeISD::Wrap", SDTIntUnaryOp>;
36
37 def callseq_start : SDNode<"ISD::CALLSEQ_START", SDT_MBCallSeqStart,
38                            [SDNPHasChain, SDNPOutFlag]>;
39
40 def callseq_end   : SDNode<"ISD::CALLSEQ_END", SDT_MBCallSeqEnd,
41                            [SDNPHasChain, SDNPOptInFlag, SDNPOutFlag]>;
42
43 //===----------------------------------------------------------------------===//
44 // MBlaze Instruction Predicate Definitions.
45 //===----------------------------------------------------------------------===//
46 def HasPipe3     : Predicate<"Subtarget.hasPipe3()">;
47 def HasBarrel    : Predicate<"Subtarget.hasBarrel()">;
48 def NoBarrel     : Predicate<"!Subtarget.hasBarrel()">;
49 def HasDiv       : Predicate<"Subtarget.hasDiv()">;
50 def HasMul       : Predicate<"Subtarget.hasMul()">;
51 def HasFSL       : Predicate<"Subtarget.hasFSL()">;
52 def HasEFSL      : Predicate<"Subtarget.hasEFSL()">;
53 def HasMSRSet    : Predicate<"Subtarget.hasMSRSet()">;
54 def HasException : Predicate<"Subtarget.hasException()">;
55 def HasPatCmp    : Predicate<"Subtarget.hasPatCmp()">;
56 def HasFPU       : Predicate<"Subtarget.hasFPU()">;
57 def HasESR       : Predicate<"Subtarget.hasESR()">;
58 def HasPVR       : Predicate<"Subtarget.hasPVR()">;
59 def HasMul64     : Predicate<"Subtarget.hasMul64()">;
60 def HasSqrt      : Predicate<"Subtarget.hasSqrt()">;
61 def HasMMU       : Predicate<"Subtarget.hasMMU()">;
62
63 //===----------------------------------------------------------------------===//
64 // MBlaze Operand, Complex Patterns and Transformations Definitions.
65 //===----------------------------------------------------------------------===//
66
67 def MBlazeMemAsmOperand : AsmOperandClass {
68   let Name = "Mem";
69   let SuperClasses = [];
70 }
71
72 def MBlazeFslAsmOperand : AsmOperandClass {
73   let Name = "Fsl";
74   let SuperClasses = [];
75 }
76
77 // Instruction operand types
78 def brtarget    : Operand<OtherVT>;
79 def calltarget  : Operand<i32>;
80 def simm16      : Operand<i32>;
81 def uimm5       : Operand<i32>;
82 def uimm14      : Operand<i32>;
83 def uimm15      : Operand<i32>;
84 def fimm        : Operand<f32>;
85
86 // Unsigned Operand
87 def uimm16      : Operand<i32> {
88   let PrintMethod = "printUnsignedImm";
89 }
90
91 // FSL Operand
92 def fslimm      : Operand<i32> {
93   let PrintMethod = "printFSLImm";
94   let ParserMatchClass = MBlazeFslAsmOperand;
95 }
96
97 // Address operand
98 def memri : Operand<i32> {
99   let PrintMethod = "printMemOperand";
100   let MIOperandInfo = (ops GPR, simm16);
101   let ParserMatchClass = MBlazeMemAsmOperand;
102 }
103
104 def memrr : Operand<i32> {
105   let PrintMethod = "printMemOperand";
106   let MIOperandInfo = (ops GPR, GPR);
107   let ParserMatchClass = MBlazeMemAsmOperand;
108 }
109
110 // Node immediate fits as 16-bit sign extended on target immediate.
111 def immSExt16  : PatLeaf<(imm), [{
112   return (N->getZExtValue() >> 16) == 0;
113 }]>;
114
115 // Node immediate fits as 16-bit zero extended on target immediate.
116 // The LO16 param means that only the lower 16 bits of the node
117 // immediate are caught.
118 // e.g. addiu, sltiu
119 def immZExt16  : PatLeaf<(imm), [{
120   return (N->getZExtValue() >> 16) == 0;
121 }]>;
122
123 // FSL immediate field must fit in 4 bits.
124 def immZExt4 : PatLeaf<(imm), [{
125   return N->getZExtValue() == ((N->getZExtValue()) & 0xf) ;
126 }]>;
127
128 // shamt field must fit in 5 bits.
129 def immZExt5 : PatLeaf<(imm), [{
130   return N->getZExtValue() == ((N->getZExtValue()) & 0x1f) ;
131 }]>;
132
133 // MBlaze Address Mode. SDNode frameindex could possibily be a match
134 // since load and store instructions from stack used it.
135 def iaddr : ComplexPattern<i32, 2, "SelectAddrRegImm", [frameindex], []>;
136 def xaddr : ComplexPattern<i32, 2, "SelectAddrRegReg", [], []>;
137
138 //===----------------------------------------------------------------------===//
139 // Pseudo instructions
140 //===----------------------------------------------------------------------===//
141
142 // As stack alignment is always done with addiu, we need a 16-bit immediate
143 let Defs = [R1], Uses = [R1] in {
144 def ADJCALLSTACKDOWN : MBlazePseudo<(outs), (ins simm16:$amt),
145                                   "#ADJCALLSTACKDOWN $amt",
146                                   [(callseq_start timm:$amt)]>;
147 def ADJCALLSTACKUP   : MBlazePseudo<(outs),
148                                   (ins uimm16:$amt1, simm16:$amt2),
149                                   "#ADJCALLSTACKUP $amt1",
150                                   [(callseq_end timm:$amt1, timm:$amt2)]>;
151 }
152
153 //===----------------------------------------------------------------------===//
154 // Instructions specific format
155 //===----------------------------------------------------------------------===//
156
157 //===----------------------------------------------------------------------===//
158 // Arithmetic Instructions
159 //===----------------------------------------------------------------------===//
160 class Arith<bits<6> op, bits<11> flags, string instr_asm, SDNode OpNode,
161             InstrItinClass itin> :
162             TA<op, flags, (outs GPR:$dst), (ins GPR:$b, GPR:$c),
163                !strconcat(instr_asm, "   $dst, $b, $c"),
164                [(set GPR:$dst, (OpNode GPR:$b, GPR:$c))], itin>;
165
166 class ArithI<bits<6> op, string instr_asm, SDNode OpNode,
167              Operand Od, PatLeaf imm_type> :
168              TB<op, (outs GPR:$dst), (ins GPR:$b, Od:$c),
169                 !strconcat(instr_asm, "   $dst, $b, $c"),
170                 [(set GPR:$dst, (OpNode GPR:$b, imm_type:$c))], IIAlu>;
171
172 class ShiftI<bits<6> op, bits<2> flags, string instr_asm, SDNode OpNode,
173              Operand Od, PatLeaf imm_type> :
174              SHT<op, flags, (outs GPR:$dst), (ins GPR:$b, Od:$c),
175                  !strconcat(instr_asm, "   $dst, $b, $c"),
176                  [(set GPR:$dst, (OpNode GPR:$b, imm_type:$c))], IIAlu>;
177
178 class ArithR<bits<6> op, bits<11> flags, string instr_asm, SDNode OpNode,
179             InstrItinClass itin> :
180             TAR<op, flags, (outs GPR:$dst), (ins GPR:$c, GPR:$b),
181                 !strconcat(instr_asm, "   $dst, $c, $b"),
182                 [(set GPR:$dst, (OpNode GPR:$b, GPR:$c))], itin>;
183
184 class ArithRI<bits<6> op, string instr_asm, SDNode OpNode,
185              Operand Od, PatLeaf imm_type> :
186              TBR<op, (outs GPR:$dst), (ins Od:$b, GPR:$c),
187                  !strconcat(instr_asm, "   $dst, $c, $b"),
188                  [(set GPR:$dst, (OpNode imm_type:$b, GPR:$c))], IIAlu>;
189
190 class ArithN<bits<6> op, bits<11> flags, string instr_asm,
191             InstrItinClass itin> :
192             TA<op, flags, (outs GPR:$dst), (ins GPR:$b, GPR:$c),
193                !strconcat(instr_asm, "   $dst, $b, $c"),
194                [], itin>;
195
196 class ArithNI<bits<6> op, string instr_asm,Operand Od, PatLeaf imm_type> :
197              TB<op, (outs GPR:$dst), (ins GPR:$b, Od:$c),
198                 !strconcat(instr_asm, "   $dst, $b, $c"),
199                 [], IIAlu>;
200
201 class ArithRN<bits<6> op, bits<11> flags, string instr_asm,
202             InstrItinClass itin> :
203             TAR<op, flags, (outs GPR:$dst), (ins GPR:$c, GPR:$b),
204                 !strconcat(instr_asm, "   $dst, $b, $c"),
205                 [], itin>;
206
207 class ArithRNI<bits<6> op, string instr_asm,Operand Od, PatLeaf imm_type> :
208              TBR<op, (outs GPR:$dst), (ins Od:$c, GPR:$b),
209                  !strconcat(instr_asm, "   $dst, $b, $c"),
210                  [], IIAlu>;
211
212 //===----------------------------------------------------------------------===//
213 // Misc Arithmetic Instructions
214 //===----------------------------------------------------------------------===//
215
216 class Logic<bits<6> op, bits<11> flags, string instr_asm, SDNode OpNode> :
217             TA<op, flags, (outs GPR:$dst), (ins GPR:$b, GPR:$c),
218                !strconcat(instr_asm, "   $dst, $b, $c"),
219                [(set GPR:$dst, (OpNode GPR:$b, GPR:$c))], IIAlu>;
220
221 class LogicI<bits<6> op, string instr_asm, SDNode OpNode> :
222              TB<op, (outs GPR:$dst), (ins GPR:$b, uimm16:$c),
223                 !strconcat(instr_asm, "   $dst, $b, $c"),
224                 [(set GPR:$dst, (OpNode GPR:$b, immZExt16:$c))],
225                 IIAlu>;
226
227 class PatCmp<bits<6> op, bits<11> flags, string instr_asm> :
228              TA<op, flags, (outs GPR:$dst), (ins GPR:$b, GPR:$c),
229                 !strconcat(instr_asm, "   $dst, $b, $c"),
230                  [], IIAlu>;
231
232 //===----------------------------------------------------------------------===//
233 // Memory Access Instructions
234 //===----------------------------------------------------------------------===//
235 class LoadM<bits<6> op, bits<11> flags, string instr_asm> :
236             TA<op, flags, (outs GPR:$dst), (ins memrr:$addr),
237                !strconcat(instr_asm, "   $dst, $addr"),
238                [], IILoad>;
239
240 class LoadMI<bits<6> op, string instr_asm, PatFrag OpNode> :
241              TB<op, (outs GPR:$dst), (ins memri:$addr),
242                 !strconcat(instr_asm, "   $dst, $addr"),
243                 [(set (i32 GPR:$dst), (OpNode iaddr:$addr))], IILoad>;
244
245 class StoreM<bits<6> op, bits<11> flags, string instr_asm> :
246              TA<op, flags, (outs), (ins GPR:$dst, memrr:$addr),
247                 !strconcat(instr_asm, "   $dst, $addr"),
248                 [], IIStore>;
249
250 class StoreMI<bits<6> op, string instr_asm, PatFrag OpNode> :
251               TB<op, (outs), (ins GPR:$dst, memri:$addr),
252                  !strconcat(instr_asm, "   $dst, $addr"),
253                  [(OpNode (i32 GPR:$dst), iaddr:$addr)], IIStore>;
254
255 //===----------------------------------------------------------------------===//
256 // Branch Instructions
257 //===----------------------------------------------------------------------===//
258 class Branch<bits<6> op, bits<5> br, bits<11> flags, string instr_asm> :
259              TA<op, flags, (outs), (ins GPR:$target),
260                 !strconcat(instr_asm, "   $target"),
261                 [], IIBranch> {
262   let rd = 0x0;
263   let ra = br;
264   let Form = FCCR;
265 }
266
267 class BranchI<bits<6> op, bits<5> br, string instr_asm> :
268               TB<op, (outs), (ins brtarget:$target),
269                  !strconcat(instr_asm, "   $target"),
270                  [], IIBranch> {
271   let rd = 0;
272   let ra = br;
273   let Form = FCCI;
274 }
275
276 //===----------------------------------------------------------------------===//
277 // Branch and Link Instructions
278 //===----------------------------------------------------------------------===//
279 class BranchL<bits<6> op, bits<5> br, bits<11> flags, string instr_asm> :
280               TA<op, flags, (outs), (ins GPR:$link, GPR:$target),
281                  !strconcat(instr_asm, "   $link, $target"),
282                  [], IIBranch> {
283   let ra = br;
284   let Form = FRCR;
285 }
286
287 class BranchLI<bits<6> op, bits<5> br, string instr_asm> :
288                TB<op, (outs), (ins GPR:$link, calltarget:$target),
289                   !strconcat(instr_asm, "   $link, $target"),
290                   [], IIBranch> {
291   let ra = br;
292   let Form = FRCI;
293 }
294
295 //===----------------------------------------------------------------------===//
296 // Conditional Branch Instructions
297 //===----------------------------------------------------------------------===//
298 class BranchC<bits<6> op, bits<5> br, bits<11> flags, string instr_asm> :
299               TA<op, flags, (outs),
300                  (ins GPR:$a, GPR:$b),
301                  !strconcat(instr_asm, "   $a, $b"),
302                  [], IIBranch> {
303   let rd = br;
304   let Form = FCRR;
305 }
306
307 class BranchCI<bits<6> op, bits<5> br, string instr_asm> :
308                TB<op, (outs), (ins GPR:$a, brtarget:$offset),
309                   !strconcat(instr_asm, "   $a, $offset"),
310                   [], IIBranch> {
311   let rd = br;
312   let Form = FCRI;
313 }
314
315 //===----------------------------------------------------------------------===//
316 // MBlaze arithmetic instructions
317 //===----------------------------------------------------------------------===//
318
319 let isCommutable = 1, isAsCheapAsAMove = 1 in {
320   def ADD    :  Arith<0x00, 0x000, "add    ", add,  IIAlu>;
321   def ADDC   :  Arith<0x02, 0x000, "addc   ", adde, IIAlu>;
322   def ADDK   :  Arith<0x04, 0x000, "addk   ", addc, IIAlu>;
323   def ADDKC  : ArithN<0x06, 0x000, "addkc  ", IIAlu>;
324   def AND    :  Logic<0x21, 0x000, "and    ", and>;
325   def OR     :  Logic<0x20, 0x000, "or     ", or>;
326   def XOR    :  Logic<0x22, 0x000, "xor    ", xor>;
327   def PCMPBF : PatCmp<0x20, 0x400, "pcmpbf ">;
328   def PCMPEQ : PatCmp<0x23, 0x400, "pcmpeq ">;
329   def PCMPNE : PatCmp<0x22, 0x400, "pcmpne ">;
330 }
331
332 let isAsCheapAsAMove = 1 in {
333   def ANDN   :  ArithN<0x23, 0x000, "andn   ", IIAlu>;
334   def CMP    :  ArithN<0x05, 0x001, "cmp    ", IIAlu>;
335   def CMPU   :  ArithN<0x05, 0x003, "cmpu   ", IIAlu>;
336   def RSUB   :  ArithR<0x01, 0x000, "rsub   ", sub,  IIAlu>;
337   def RSUBC  :  ArithR<0x03, 0x000, "rsubc  ", sube, IIAlu>;
338   def RSUBK  :  ArithR<0x05, 0x000, "rsubk  ", subc, IIAlu>;
339   def RSUBKC : ArithRN<0x07, 0x000, "rsubkc ", IIAlu>;
340 }
341
342 let isCommutable = 1, Predicates=[HasMul] in {
343   def MUL    : Arith<0x10, 0x000, "mul    ", mul,   IIAlu>;
344 }
345
346 let isCommutable = 1, Predicates=[HasMul,HasMul64] in {
347   def MULH   : Arith<0x10, 0x001, "mulh   ", mulhs, IIAlu>;
348   def MULHU  : Arith<0x10, 0x003, "mulhu  ", mulhu, IIAlu>;
349 }
350
351 let Predicates=[HasMul,HasMul64] in {
352   def MULHSU : ArithN<0x10, 0x002, "mulhsu ", IIAlu>;
353 }
354
355 let Predicates=[HasBarrel] in {
356   def BSRL   :   Arith<0x11, 0x000, "bsrl   ", srl, IIAlu>;
357   def BSRA   :   Arith<0x11, 0x200, "bsra   ", sra, IIAlu>;
358   def BSLL   :   Arith<0x11, 0x400, "bsll   ", shl, IIAlu>;
359   def BSRLI  :  ShiftI<0x19, 0x0, "bsrli  ", srl, uimm5, immZExt5>;
360   def BSRAI  :  ShiftI<0x19, 0x1, "bsrai  ", sra, uimm5, immZExt5>;
361   def BSLLI  :  ShiftI<0x19, 0x2, "bslli  ", shl, uimm5, immZExt5>;
362 }
363
364 let Predicates=[HasDiv] in {
365   def IDIV   :  Arith<0x12, 0x000, "idiv   ", sdiv, IIAlu>;
366   def IDIVU  :  Arith<0x12, 0x002, "idivu  ", udiv, IIAlu>;
367 }
368
369 //===----------------------------------------------------------------------===//
370 // MBlaze immediate mode arithmetic instructions
371 //===----------------------------------------------------------------------===//
372
373 let isAsCheapAsAMove = 1 in {
374   def ADDI    :   ArithI<0x08, "addi   ", add,  simm16, immSExt16>;
375   def ADDIC   :  ArithNI<0x0A, "addic  ", simm16, immSExt16>;
376   def ADDIK   :  ArithNI<0x0C, "addik  ", simm16, immSExt16>;
377   def ADDIKC  :   ArithI<0x0E, "addikc ", addc, simm16, immSExt16>;
378   def RSUBI   :  ArithRI<0x09, "rsubi  ", sub,  simm16, immSExt16>;
379   def RSUBIC  : ArithRNI<0x0B, "rsubi  ", simm16, immSExt16>;
380   def RSUBIK  : ArithRNI<0x0E, "rsubic ", simm16, immSExt16>;
381   def RSUBIKC :  ArithRI<0x0F, "rsubikc", subc, simm16, immSExt16>;
382   def ANDNI   :  ArithNI<0x2B, "andni  ", uimm16, immZExt16>;
383   def ANDI    :   LogicI<0x29, "andi   ", and>;
384   def ORI     :   LogicI<0x28, "ori    ", or>;
385   def XORI    :   LogicI<0x2A, "xori   ", xor>;
386 }
387
388 let Predicates=[HasMul] in {
389   def MULI    :   ArithI<0x18, "muli   ", mul, simm16, immSExt16>;
390 }
391
392 //===----------------------------------------------------------------------===//
393 // MBlaze memory access instructions
394 //===----------------------------------------------------------------------===//
395
396 let canFoldAsLoad = 1, isReMaterializable = 1 in {
397   def LBU  :  LoadM<0x30, 0x000, "lbu    ">;
398   def LBUR :  LoadM<0x30, 0x200, "lbur   ">;
399
400   def LHU  :  LoadM<0x31, 0x000, "lhu    ">;
401   def LHUR :  LoadM<0x31, 0x200, "lhur   ">;
402
403   def LW   :  LoadM<0x32, 0x000, "lw     ">;
404   def LWR  :  LoadM<0x32, 0x200, "lwr    ">;
405   def LWX  :  LoadM<0x32, 0x400, "lwx    ">;
406
407   def LBUI : LoadMI<0x38, "lbui   ", zextloadi8>;
408   def LHUI : LoadMI<0x39, "lhui   ", zextloadi16>;
409   def LWI  : LoadMI<0x3A, "lwi    ", load>;
410 }
411
412   def SB  :  StoreM<0x34, 0x000, "sb     ">;
413   def SBR :  StoreM<0x34, 0x200, "sbr    ">;
414
415   def SH  :  StoreM<0x35, 0x000, "sh     ">;
416   def SHR :  StoreM<0x35, 0x200, "shr    ">;
417
418   def SW  :  StoreM<0x36, 0x000, "sw     ">;
419   def SWR :  StoreM<0x36, 0x200, "swr    ">;
420   def SWX :  StoreM<0x36, 0x400, "swx    ">;
421
422   def SBI : StoreMI<0x3C, "sbi    ", truncstorei8>;
423   def SHI : StoreMI<0x3D, "shi    ", truncstorei16>;
424   def SWI : StoreMI<0x3E, "swi    ", store>;
425
426 //===----------------------------------------------------------------------===//
427 // MBlaze branch instructions
428 //===----------------------------------------------------------------------===//
429
430 let isBranch = 1, isTerminator = 1, hasCtrlDep = 1, isBarrier = 1 in {
431   def BRI    :  BranchI<0x2E, 0x00, "bri    ">;
432   def BRAI   :  BranchI<0x2E, 0x08, "brai   ">;
433 }
434
435 let isBranch = 1, isTerminator = 1, hasCtrlDep = 1 in {
436   def BEQI   : BranchCI<0x2F, 0x00, "beqi   ">;
437   def BNEI   : BranchCI<0x2F, 0x01, "bnei   ">;
438   def BLTI   : BranchCI<0x2F, 0x02, "blti   ">;
439   def BLEI   : BranchCI<0x2F, 0x03, "blei   ">;
440   def BGTI   : BranchCI<0x2F, 0x04, "bgti   ">;
441   def BGEI   : BranchCI<0x2F, 0x05, "bgei   ">;
442 }
443
444 let isBranch = 1, isIndirectBranch = 1, isTerminator = 1, hasCtrlDep = 1,
445     isBarrier = 1 in {
446   def BR     :   Branch<0x26, 0x00, 0x000, "br     ">;
447   def BRA    :   Branch<0x26, 0x08, 0x000, "bra    ">;
448 }
449
450 let isBranch = 1, isIndirectBranch = 1, isTerminator = 1, hasCtrlDep = 1 in {
451   def BEQ    :  BranchC<0x27, 0x00, 0x000, "beq    ">;
452   def BNE    :  BranchC<0x27, 0x01, 0x000, "bne    ">;
453   def BLT    :  BranchC<0x27, 0x02, 0x000, "blt    ">;
454   def BLE    :  BranchC<0x27, 0x03, 0x000, "ble    ">;
455   def BGT    :  BranchC<0x27, 0x04, 0x000, "bgt    ">;
456   def BGE    :  BranchC<0x27, 0x05, 0x000, "bge    ">;
457 }
458
459 let isBranch = 1, isTerminator = 1, hasDelaySlot = 1, hasCtrlDep = 1,
460     isBarrier = 1 in {
461   def BRID   :  BranchI<0x2E, 0x10, "brid   ">;
462   def BRAID  :  BranchI<0x2E, 0x18, "braid  ">;
463 }
464
465 let isBranch = 1, isTerminator = 1, hasDelaySlot = 1, hasCtrlDep = 1 in {
466   def BEQID  : BranchCI<0x2F, 0x10, "beqid  ">;
467   def BNEID  : BranchCI<0x2F, 0x11, "bneid  ">;
468   def BLTID  : BranchCI<0x2F, 0x12, "bltid  ">;
469   def BLEID  : BranchCI<0x2F, 0x13, "bleid  ">;
470   def BGTID  : BranchCI<0x2F, 0x14, "bgtid  ">;
471   def BGEID  : BranchCI<0x2F, 0x15, "bgeid  ">;
472 }
473
474 let isBranch = 1, isIndirectBranch = 1, isTerminator = 1,
475     hasDelaySlot = 1, hasCtrlDep = 1, isBarrier = 1 in {
476   def BRD    :   Branch<0x26, 0x10, 0x000, "brd    ">;
477   def BRAD   :   Branch<0x26, 0x18, 0x000, "brad   ">;
478 }
479
480 let isBranch = 1, isIndirectBranch = 1, isTerminator = 1,
481     hasDelaySlot = 1, hasCtrlDep = 1 in {
482   def BEQD   :  BranchC<0x27, 0x10, 0x000, "beqd   ">;
483   def BNED   :  BranchC<0x27, 0x11, 0x000, "bned   ">;
484   def BLTD   :  BranchC<0x27, 0x12, 0x000, "bltd   ">;
485   def BLED   :  BranchC<0x27, 0x13, 0x000, "bled   ">;
486   def BGTD   :  BranchC<0x27, 0x14, 0x000, "bgtd   ">;
487   def BGED   :  BranchC<0x27, 0x15, 0x000, "bged   ">;
488 }
489
490 let isCall = 1, hasDelaySlot = 1, hasCtrlDep = 1, isBarrier = 1,
491     Defs = [R3,R4,R5,R6,R7,R8,R9,R10,R11,R12],
492     Uses = [R1,R5,R6,R7,R8,R9,R10] in {
493   def BRLID  : BranchLI<0x2E, 0x14, "brlid  ">;
494   def BRALID : BranchLI<0x2E, 0x1C, "bralid ">;
495 }
496
497 let isCall = 1, hasDelaySlot = 1, hasCtrlDep = 1, isIndirectBranch = 1,
498     isBarrier = 1,
499     Defs = [R3,R4,R5,R6,R7,R8,R9,R10,R11,R12],
500     Uses = [R1,R5,R6,R7,R8,R9,R10] in {
501   def BRLD   : BranchL<0x26, 0x14, 0x000, "brld   ">;
502   def BRALD  : BranchL<0x26, 0x1C, 0x000, "brald  ">;
503 }
504
505 let isReturn=1, isTerminator=1, hasDelaySlot=1, isBarrier=1,
506     hasCtrlDep=1, rd=0x10, Form=FCRI in {
507   def RTSD   : TB<0x2D, (outs), (ins GPR:$target, simm16:$imm),
508                   "rtsd      $target, $imm",
509                   [],
510                   IIBranch>;
511 }
512
513 let isReturn=1, isTerminator=1, hasDelaySlot=1, isBarrier=1,
514     hasCtrlDep=1, rd=0x11, Form=FCRI in {
515   def RTID   : TB<0x2D, (outs), (ins GPR:$target, simm16:$imm),
516                   "rtid      $target, $imm",
517                   [],
518                   IIBranch>;
519 }
520
521 let isReturn=1, isTerminator=1, hasDelaySlot=1, isBarrier=1,
522     hasCtrlDep=1, rd=0x12, Form=FCRI in {
523   def RTBD   : TB<0x2D, (outs), (ins GPR:$target, simm16:$imm),
524                   "rtbd      $target, $imm",
525                   [],
526                   IIBranch>;
527 }
528
529 let isReturn=1, isTerminator=1, hasDelaySlot=1, isBarrier=1,
530     hasCtrlDep=1, rd=0x14, Form=FCRI in {
531   def RTED   : TB<0x2D, (outs), (ins GPR:$target, simm16:$imm),
532                   "rted      $target, $imm",
533                   [],
534                   IIBranch>;
535 }
536
537 //===----------------------------------------------------------------------===//
538 // MBlaze misc instructions
539 //===----------------------------------------------------------------------===//
540
541 let neverHasSideEffects = 1 in {
542   def NOP :  MBlazeInst< 0x20, FC, (outs), (ins), "nop    ", [], IIAlu>;
543 }
544
545 let usesCustomInserter = 1 in {
546   def Select_CC : MBlazePseudo<(outs GPR:$dst),
547     (ins GPR:$T, GPR:$F, GPR:$CMP, i32imm:$CC),
548     "; SELECT_CC PSEUDO!",
549     []>;
550
551   def ShiftL : MBlazePseudo<(outs GPR:$dst),
552     (ins GPR:$L, GPR:$R),
553     "; ShiftL PSEUDO!",
554     []>;
555
556   def ShiftRA : MBlazePseudo<(outs GPR:$dst),
557     (ins GPR:$L, GPR:$R),
558     "; ShiftRA PSEUDO!",
559     []>;
560
561   def ShiftRL : MBlazePseudo<(outs GPR:$dst),
562     (ins GPR:$L, GPR:$R),
563     "; ShiftRL PSEUDO!",
564     []>;
565 }
566
567
568 let rb = 0 in {
569   def SEXT16 : TA<0x24, 0x061, (outs GPR:$dst), (ins GPR:$src),
570                   "sext16    $dst, $src", [], IIAlu>;
571   def SEXT8  : TA<0x24, 0x060, (outs GPR:$dst), (ins GPR:$src),
572                   "sext8     $dst, $src", [], IIAlu>;
573   def SRL    : TA<0x24, 0x041, (outs GPR:$dst), (ins GPR:$src),
574                   "srl       $dst, $src", [], IIAlu>;
575   def SRA    : TA<0x24, 0x001, (outs GPR:$dst), (ins GPR:$src),
576                   "sra       $dst, $src", [], IIAlu>;
577   def SRC    : TA<0x24, 0x021, (outs GPR:$dst), (ins GPR:$src),
578                   "src       $dst, $src", [], IIAlu>;
579 }
580
581 let opcode=0x08, isCodeGenOnly=1 in {
582   def LEA_ADDI : TB<0x08, (outs GPR:$dst), (ins memri:$addr),
583                     "addi     $dst, ${addr:stackloc}",
584                     [(set GPR:$dst, iaddr:$addr)], IIAlu>;
585 }
586
587 //===----------------------------------------------------------------------===//
588 // Misc. instructions
589 //===----------------------------------------------------------------------===//
590 def MFS : SPC<0x25, 0x2, (outs GPR:$dst), (ins uimm14:$rg),
591               "mfs       $dst, $rg", [], IIAlu>;
592
593 def MTS : SPC<0x25, 0x3, (outs), (ins uimm14:$dst, GPR:$rg),
594               "mts       $dst, $rg", [], IIAlu>;
595
596 def MSRSET : MSR<0x25, 0x20, (outs GPR:$dst), (ins uimm15:$set),
597                  "msrset    $dst, $set", [], IIAlu>;
598
599 def MSRCLR : MSR<0x25, 0x22, (outs GPR:$dst), (ins uimm15:$clr),
600                  "msrclr    $dst, $clr", [], IIAlu>;
601
602 let rd=0x0, Form=FCRR in {
603   def WDC  : TA<0x24, 0x64, (outs), (ins GPR:$a, GPR:$b),
604                 "wdc       $a, $b", [], IIAlu>;
605   def WDCF : TA<0x24, 0x74, (outs), (ins GPR:$a, GPR:$b),
606                 "wdc.flush $a, $b", [], IIAlu>;
607   def WDCC : TA<0x24, 0x66, (outs), (ins GPR:$a, GPR:$b),
608                 "wdc.clear $a, $b", [], IIAlu>;
609   def WIC  : TA<0x24, 0x68, (outs), (ins GPR:$a, GPR:$b),
610                 "wic       $a, $b", [], IIAlu>;
611 }
612
613 def BRK  :  BranchL<0x26, 0x0C, 0x000, "brk    ">;
614 def BRKI : BranchLI<0x2E, 0x0C, "brki   ">;
615
616 def IMM : MBlazeInst<0x2C, FCCI, (outs), (ins simm16:$imm),
617                      "imm       $imm", [], IIAlu>;
618
619 //===----------------------------------------------------------------------===//
620 //  Arbitrary patterns that map to one or more instructions
621 //===----------------------------------------------------------------------===//
622
623 // Small immediates
624 def : Pat<(i32 0), (ADD (i32 R0), (i32 R0))>;
625 def : Pat<(i32 immSExt16:$imm), (ADDI (i32 R0), imm:$imm)>;
626 def : Pat<(i32 immZExt16:$imm), (ORI (i32 R0), imm:$imm)>;
627
628 // Arbitrary immediates
629 def : Pat<(i32 imm:$imm), (ADDI (i32 R0), imm:$imm)>;
630
631 // In register sign extension
632 def : Pat<(sext_inreg GPR:$src, i16), (SEXT16 GPR:$src)>;
633 def : Pat<(sext_inreg GPR:$src, i8),  (SEXT8 GPR:$src)>;
634
635 // Call
636 def : Pat<(MBlazeJmpLink (i32 tglobaladdr:$dst)),
637           (BRLID (i32 R15), tglobaladdr:$dst)>;
638
639 def : Pat<(MBlazeJmpLink (i32 texternalsym:$dst)),
640           (BRLID (i32 R15), texternalsym:$dst)>;
641
642 def : Pat<(MBlazeJmpLink GPR:$dst),
643           (BRLD (i32 R15), GPR:$dst)>;
644
645 // Shift Instructions
646 def : Pat<(shl GPR:$L, GPR:$R), (ShiftL GPR:$L, GPR:$R)>;
647 def : Pat<(sra GPR:$L, GPR:$R), (ShiftRA GPR:$L, GPR:$R)>;
648 def : Pat<(srl GPR:$L, GPR:$R), (ShiftRL GPR:$L, GPR:$R)>;
649
650 // SET_CC operations
651 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETEQ),
652           (Select_CC (ADDI (i32 R0), 1), (ADDI (i32 R0), 0),
653                      (CMP GPR:$L, GPR:$R), 1)>;
654 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETNE),
655           (Select_CC (ADDI (i32 R0), 1), (ADDI (i32 R0), 0),
656                      (CMP GPR:$L, GPR:$R), 2)>;
657 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETGT),
658           (Select_CC (ADDI (i32 R0), 1), (ADDI (i32 R0), 0),
659                      (CMP GPR:$L, GPR:$R), 3)>;
660 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETLT),
661           (Select_CC (ADDI (i32 R0), 1), (ADDI (i32 R0), 0),
662                      (CMP GPR:$L, GPR:$R), 4)>;
663 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETGE),
664           (Select_CC (ADDI (i32 R0), 1), (ADDI (i32 R0), 0),
665                      (CMP GPR:$L, GPR:$R), 5)>;
666 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETLE),
667           (Select_CC (ADDI (i32 R0), 1), (ADDI (i32 R0), 0),
668                      (CMP GPR:$L, GPR:$R), 6)>;
669 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETUGT),
670           (Select_CC (ADDI (i32 R0), 1), (ADDI (i32 R0), 0),
671                      (CMPU GPR:$L, GPR:$R), 3)>;
672 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETULT),
673           (Select_CC (ADDI (i32 R0), 1), (ADDI (i32 R0), 0),
674                      (CMPU GPR:$L, GPR:$R), 4)>;
675 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETUGE),
676           (Select_CC (ADDI (i32 R0), 1), (ADDI (i32 R0), 0),
677                      (CMPU GPR:$L, GPR:$R), 5)>;
678 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETULE),
679           (Select_CC (ADDI (i32 R0), 1), (ADDI (i32 R0), 0),
680                      (CMPU GPR:$L, GPR:$R), 6)>;
681
682 // SELECT operations
683 def : Pat<(select (i32 GPR:$C), (i32 GPR:$T), (i32 GPR:$F)),
684           (Select_CC GPR:$T, GPR:$F, GPR:$C, 2)>;
685
686 // SELECT_CC
687 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
688                     (i32 GPR:$T), (i32 GPR:$F), SETEQ),
689           (Select_CC GPR:$T, GPR:$F, (CMP GPR:$L, GPR:$R), 1)>;
690 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
691                     (i32 GPR:$T), (i32 GPR:$F), SETNE),
692           (Select_CC GPR:$T, GPR:$F, (CMP GPR:$L, GPR:$R), 2)>;
693 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
694                     (i32 GPR:$T), (i32 GPR:$F), SETGT),
695           (Select_CC GPR:$T, GPR:$F, (CMP GPR:$L, GPR:$R), 3)>;
696 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
697                     (i32 GPR:$T), (i32 GPR:$F), SETLT),
698           (Select_CC GPR:$T, GPR:$F, (CMP GPR:$L, GPR:$R), 4)>;
699 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
700                     (i32 GPR:$T), (i32 GPR:$F), SETGE),
701           (Select_CC GPR:$T, GPR:$F, (CMP GPR:$L, GPR:$R), 5)>;
702 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
703                     (i32 GPR:$T), (i32 GPR:$F), SETLE),
704           (Select_CC GPR:$T, GPR:$F, (CMP GPR:$L, GPR:$R), 6)>;
705 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
706                     (i32 GPR:$T), (i32 GPR:$F), SETUGT),
707           (Select_CC GPR:$T, GPR:$F, (CMPU GPR:$L, GPR:$R), 3)>;
708 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
709                     (i32 GPR:$T), (i32 GPR:$F), SETULT),
710           (Select_CC GPR:$T, GPR:$F, (CMPU GPR:$L, GPR:$R), 4)>;
711 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
712                     (i32 GPR:$T), (i32 GPR:$F), SETUGE),
713           (Select_CC GPR:$T, GPR:$F, (CMPU GPR:$L, GPR:$R), 5)>;
714 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
715                     (i32 GPR:$T), (i32 GPR:$F), SETULE),
716           (Select_CC GPR:$T, GPR:$F, (CMPU GPR:$L, GPR:$R), 6)>;
717
718 // Ret instructions
719 def : Pat<(MBlazeRet GPR:$target), (RTSD GPR:$target, 0x8)>;
720
721 // BR instructions
722 def : Pat<(br bb:$T), (BRID bb:$T)>;
723 def : Pat<(brind GPR:$T), (BRD GPR:$T)>;
724
725 // BRCOND instructions
726 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETEQ), bb:$T),
727           (BEQID (CMP GPR:$R, GPR:$L), bb:$T)>;
728 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETNE), bb:$T),
729           (BNEID (CMP GPR:$R, GPR:$L), bb:$T)>;
730 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETGT), bb:$T),
731           (BGTID (CMP GPR:$R, GPR:$L), bb:$T)>;
732 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETLT), bb:$T),
733           (BLTID (CMP GPR:$R, GPR:$L), bb:$T)>;
734 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETGE), bb:$T),
735           (BGEID (CMP GPR:$R, GPR:$L), bb:$T)>;
736 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETLE), bb:$T),
737           (BLEID (CMP GPR:$R, GPR:$L), bb:$T)>;
738 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETUGT), bb:$T),
739           (BGTID (CMPU GPR:$R, GPR:$L), bb:$T)>;
740 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETULT), bb:$T),
741           (BLTID (CMPU GPR:$R, GPR:$L), bb:$T)>;
742 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETUGE), bb:$T),
743           (BGEID (CMPU GPR:$R, GPR:$L), bb:$T)>;
744 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETULE), bb:$T),
745           (BLEID (CMPU GPR:$R, GPR:$L), bb:$T)>;
746 def : Pat<(brcond (i32 GPR:$C), bb:$T),
747           (BNEID GPR:$C, bb:$T)>;
748
749 // Jump tables, global addresses, and constant pools
750 def : Pat<(MBWrapper tglobaladdr:$in), (ORI (i32 R0), tglobaladdr:$in)>;
751 def : Pat<(MBWrapper tjumptable:$in),  (ORI (i32 R0), tjumptable:$in)>;
752 def : Pat<(MBWrapper tconstpool:$in),  (ORI (i32 R0), tconstpool:$in)>;
753
754 // Misc instructions
755 def : Pat<(and (i32 GPR:$lh), (not (i32 GPR:$rh))),(ANDN GPR:$lh, GPR:$rh)>;
756
757 // Arithmetic with immediates
758 def : Pat<(add (i32 GPR:$in), imm:$imm),(ADDI GPR:$in, imm:$imm)>;
759 def : Pat<(or (i32 GPR:$in), imm:$imm),(ORI GPR:$in, imm:$imm)>;
760 def : Pat<(xor (i32 GPR:$in), imm:$imm),(XORI GPR:$in, imm:$imm)>;
761
762 // Convert any extend loads into zero extend loads
763 def : Pat<(extloadi8  iaddr:$src), (i32 (LBUI iaddr:$src))>;
764 def : Pat<(extloadi16 iaddr:$src), (i32 (LHUI iaddr:$src))>;
765 def : Pat<(extloadi8  xaddr:$src), (i32 (LBU xaddr:$src))>;
766 def : Pat<(extloadi16 xaddr:$src), (i32 (LHU xaddr:$src))>;
767
768 // 32-bit load and store
769 def : Pat<(store (i32 GPR:$dst), xaddr:$addr), (SW GPR:$dst, xaddr:$addr)>;
770 def : Pat<(load xaddr:$addr), (i32 (LW xaddr:$addr))>;
771
772 // 16-bit load and store
773 def : Pat<(truncstorei16 (i32 GPR:$dst), xaddr:$addr), (SH GPR:$dst, xaddr:$addr)>;
774 def : Pat<(zextloadi16 xaddr:$addr), (i32 (LHU xaddr:$addr))>;
775
776 // 8-bit load and store
777 def : Pat<(truncstorei8 (i32 GPR:$dst), xaddr:$addr), (SB GPR:$dst, xaddr:$addr)>;
778 def : Pat<(zextloadi8 xaddr:$addr), (i32 (LBU xaddr:$addr))>;
779
780 // Peepholes
781 def : Pat<(store (i32 0), iaddr:$dst), (SWI (i32 R0), iaddr:$dst)>;
782
783 //===----------------------------------------------------------------------===//
784 // Floating Point Support
785 //===----------------------------------------------------------------------===//
786 include "MBlazeInstrFSL.td"
787 include "MBlazeInstrFPU.td"