Emacs-tag and some comment fix for all ARM, CellSPU, Hexagon, MBlaze, MSP430, PPC...
[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_MBlazeIRet    : SDTypeProfile<0, 1, [SDTCisInt<0>]>;
22 def SDT_MBlazeJmpLink : SDTypeProfile<0, -1, [SDTCisVT<0, i32>]>;
23 def SDT_MBCallSeqStart : SDCallSeqStart<[SDTCisVT<0, i32>]>;
24 def SDT_MBCallSeqEnd   : SDCallSeqEnd<[SDTCisVT<0, i32>, SDTCisVT<1, i32>]>;
25
26 //===----------------------------------------------------------------------===//
27 // MBlaze specific nodes
28 //===----------------------------------------------------------------------===//
29
30 def MBlazeRet     : SDNode<"MBlazeISD::Ret", SDT_MBlazeRet,
31                            [SDNPHasChain, SDNPOptInGlue]>;
32 def MBlazeIRet    : SDNode<"MBlazeISD::IRet", SDT_MBlazeIRet,
33                            [SDNPHasChain, SDNPOptInGlue]>;
34
35 def MBlazeJmpLink : SDNode<"MBlazeISD::JmpLink",SDT_MBlazeJmpLink,
36                            [SDNPHasChain,SDNPOptInGlue,SDNPOutGlue,
37                             SDNPVariadic]>;
38
39 def MBWrapper   : SDNode<"MBlazeISD::Wrap", SDTIntUnaryOp>;
40
41 def callseq_start : SDNode<"ISD::CALLSEQ_START", SDT_MBCallSeqStart,
42                            [SDNPHasChain, SDNPOutGlue]>;
43
44 def callseq_end   : SDNode<"ISD::CALLSEQ_END", SDT_MBCallSeqEnd,
45                            [SDNPHasChain, SDNPOptInGlue, SDNPOutGlue]>;
46
47 //===----------------------------------------------------------------------===//
48 // MBlaze Instruction Predicate Definitions.
49 //===----------------------------------------------------------------------===//
50 // def HasPipe3     : Predicate<"Subtarget.hasPipe3()">;
51 def HasBarrel    : Predicate<"Subtarget.hasBarrel()">;
52 // def NoBarrel     : Predicate<"!Subtarget.hasBarrel()">;
53 def HasDiv       : Predicate<"Subtarget.hasDiv()">;
54 def HasMul       : Predicate<"Subtarget.hasMul()">;
55 // def HasFSL       : Predicate<"Subtarget.hasFSL()">;
56 // def HasEFSL      : Predicate<"Subtarget.hasEFSL()">;
57 // def HasMSRSet    : Predicate<"Subtarget.hasMSRSet()">;
58 // def HasException : Predicate<"Subtarget.hasException()">;
59 def HasPatCmp    : Predicate<"Subtarget.hasPatCmp()">;
60 def HasFPU       : Predicate<"Subtarget.hasFPU()">;
61 // def HasESR       : Predicate<"Subtarget.hasESR()">;
62 // def HasPVR       : Predicate<"Subtarget.hasPVR()">;
63 def HasMul64     : Predicate<"Subtarget.hasMul64()">;
64 def HasSqrt      : Predicate<"Subtarget.hasSqrt()">;
65 // def HasMMU       : Predicate<"Subtarget.hasMMU()">;
66
67 //===----------------------------------------------------------------------===//
68 // MBlaze Operand, Complex Patterns and Transformations Definitions.
69 //===----------------------------------------------------------------------===//
70
71 def MBlazeMemAsmOperand : AsmOperandClass {
72   let Name = "Mem";
73   let SuperClasses = [];
74 }
75
76 def MBlazeFslAsmOperand : AsmOperandClass {
77   let Name = "Fsl";
78   let SuperClasses = [];
79 }
80
81 // Instruction operand types
82 def brtarget    : Operand<OtherVT>;
83 def calltarget  : Operand<i32>;
84 def simm16      : Operand<i32>;
85 def uimm5       : Operand<i32>;
86 def uimm15      : Operand<i32>;
87 def fimm        : Operand<f32>;
88
89 // Unsigned Operand
90 def uimm16      : Operand<i32> {
91   let PrintMethod = "printUnsignedImm";
92 }
93
94 // FSL Operand
95 def fslimm      : Operand<i32> {
96   let PrintMethod = "printFSLImm";
97   let ParserMatchClass = MBlazeFslAsmOperand;
98 }
99
100 // Address operand
101 def memri : Operand<i32> {
102   let PrintMethod = "printMemOperand";
103   let MIOperandInfo = (ops GPR, simm16);
104   let ParserMatchClass = MBlazeMemAsmOperand;
105 }
106
107 def memrr : Operand<i32> {
108   let PrintMethod = "printMemOperand";
109   let MIOperandInfo = (ops GPR, GPR);
110   let ParserMatchClass = MBlazeMemAsmOperand;
111 }
112
113 // Node immediate fits as 16-bit sign extended on target immediate.
114 def immSExt16  : PatLeaf<(imm), [{
115   return (N->getZExtValue() >> 16) == 0;
116 }]>;
117
118 // Node immediate fits as 16-bit zero extended on target immediate.
119 // The LO16 param means that only the lower 16 bits of the node
120 // immediate are caught.
121 // e.g. addiu, sltiu
122 def immZExt16  : PatLeaf<(imm), [{
123   return (N->getZExtValue() >> 16) == 0;
124 }]>;
125
126 // FSL immediate field must fit in 4 bits.
127 def immZExt4 : PatLeaf<(imm), [{
128   return N->getZExtValue() == ((N->getZExtValue()) & 0xf) ;
129 }]>;
130
131 // shamt field must fit in 5 bits.
132 def immZExt5 : PatLeaf<(imm), [{
133   return N->getZExtValue() == ((N->getZExtValue()) & 0x1f) ;
134 }]>;
135
136 // MBlaze Address Mode. SDNode frameindex could possibily be a match
137 // since load and store instructions from stack used it.
138 def iaddr : ComplexPattern<i32, 2, "SelectAddrRegImm", [frameindex], []>;
139 def xaddr : ComplexPattern<i32, 2, "SelectAddrRegReg", [], []>;
140
141 //===----------------------------------------------------------------------===//
142 // Pseudo instructions
143 //===----------------------------------------------------------------------===//
144
145 // As stack alignment is always done with addiu, we need a 16-bit immediate
146 let Defs = [R1], Uses = [R1] in {
147 def ADJCALLSTACKDOWN : MBlazePseudo<(outs), (ins simm16:$amt),
148                                   "#ADJCALLSTACKDOWN $amt",
149                                   [(callseq_start timm:$amt)]>;
150 def ADJCALLSTACKUP   : MBlazePseudo<(outs),
151                                   (ins uimm16:$amt1, simm16:$amt2),
152                                   "#ADJCALLSTACKUP $amt1",
153                                   [(callseq_end timm:$amt1, timm:$amt2)]>;
154 }
155
156 //===----------------------------------------------------------------------===//
157 // Instructions specific format
158 //===----------------------------------------------------------------------===//
159
160 //===----------------------------------------------------------------------===//
161 // Arithmetic Instructions
162 //===----------------------------------------------------------------------===//
163 class Arith<bits<6> op, bits<11> flags, string instr_asm, SDNode OpNode,
164             InstrItinClass itin> :
165             TA<op, flags, (outs GPR:$dst), (ins GPR:$b, GPR:$c),
166                !strconcat(instr_asm, "   $dst, $b, $c"),
167                [(set GPR:$dst, (OpNode GPR:$b, GPR:$c))], itin>;
168
169 class ArithI<bits<6> op, string instr_asm, SDNode OpNode,
170              Operand Od, PatLeaf imm_type> :
171              TB<op, (outs GPR:$dst), (ins GPR:$b, Od:$c),
172                 !strconcat(instr_asm, "   $dst, $b, $c"),
173                 [(set GPR:$dst, (OpNode GPR:$b, imm_type:$c))], IIC_ALU>;
174
175 class ArithI32<bits<6> op, string instr_asm,Operand Od, PatLeaf imm_type> :
176                TB<op, (outs GPR:$dst), (ins GPR:$b, Od:$c),
177                   !strconcat(instr_asm, "   $dst, $b, $c"),
178                   [], IIC_ALU>;
179
180 class ShiftI<bits<6> op, bits<2> flags, string instr_asm, SDNode OpNode,
181              Operand Od, PatLeaf imm_type> :
182              SHT<op, flags, (outs GPR:$dst), (ins GPR:$b, Od:$c),
183                  !strconcat(instr_asm, "   $dst, $b, $c"),
184                  [(set GPR:$dst, (OpNode GPR:$b, imm_type:$c))], IIC_SHT>;
185
186 class ArithR<bits<6> op, bits<11> flags, string instr_asm, SDNode OpNode,
187             InstrItinClass itin> :
188             TAR<op, flags, (outs GPR:$dst), (ins GPR:$b, GPR:$c),
189                 !strconcat(instr_asm, "   $dst, $c, $b"),
190                 [(set GPR:$dst, (OpNode GPR:$b, GPR:$c))], itin>;
191
192 class ArithRI<bits<6> op, string instr_asm, SDNode OpNode,
193              Operand Od, PatLeaf imm_type> :
194              TBR<op, (outs GPR:$dst), (ins Od:$b, GPR:$c),
195                  !strconcat(instr_asm, "   $dst, $c, $b"),
196                  [(set GPR:$dst, (OpNode imm_type:$b, GPR:$c))], IIC_ALU>;
197
198 class ArithN<bits<6> op, bits<11> flags, string instr_asm,
199             InstrItinClass itin> :
200             TA<op, flags, (outs GPR:$dst), (ins GPR:$b, GPR:$c),
201                !strconcat(instr_asm, "   $dst, $b, $c"),
202                [], itin>;
203
204 class ArithNI<bits<6> op, string instr_asm,Operand Od, PatLeaf imm_type> :
205              TB<op, (outs GPR:$dst), (ins GPR:$b, Od:$c),
206                 !strconcat(instr_asm, "   $dst, $b, $c"),
207                 [], IIC_ALU>;
208
209 class ArithRN<bits<6> op, bits<11> flags, string instr_asm,
210             InstrItinClass itin> :
211             TAR<op, flags, (outs GPR:$dst), (ins GPR:$c, GPR:$b),
212                 !strconcat(instr_asm, "   $dst, $b, $c"),
213                 [], itin>;
214
215 class ArithRNI<bits<6> op, string instr_asm,Operand Od, PatLeaf imm_type> :
216              TBR<op, (outs GPR:$dst), (ins Od:$c, GPR:$b),
217                  !strconcat(instr_asm, "   $dst, $b, $c"),
218                  [], IIC_ALU>;
219
220 //===----------------------------------------------------------------------===//
221 // Misc Arithmetic Instructions
222 //===----------------------------------------------------------------------===//
223
224 class Logic<bits<6> op, bits<11> flags, string instr_asm, SDNode OpNode> :
225             TA<op, flags, (outs GPR:$dst), (ins GPR:$b, GPR:$c),
226                !strconcat(instr_asm, "   $dst, $b, $c"),
227                [(set GPR:$dst, (OpNode GPR:$b, GPR:$c))], IIC_ALU>;
228
229 class LogicI<bits<6> op, string instr_asm, SDNode OpNode> :
230              TB<op, (outs GPR:$dst), (ins GPR:$b, uimm16:$c),
231                 !strconcat(instr_asm, "   $dst, $b, $c"),
232                 [(set GPR:$dst, (OpNode GPR:$b, immZExt16:$c))],
233                 IIC_ALU>;
234
235 class LogicI32<bits<6> op, string instr_asm> :
236                TB<op, (outs GPR:$dst), (ins GPR:$b, uimm16:$c),
237                   !strconcat(instr_asm, "   $dst, $b, $c"),
238                   [], IIC_ALU>;
239
240 class PatCmp<bits<6> op, bits<11> flags, string instr_asm> :
241              TA<op, flags, (outs GPR:$dst), (ins GPR:$b, GPR:$c),
242                 !strconcat(instr_asm, "   $dst, $b, $c"),
243                  [], IIC_ALU>;
244
245 //===----------------------------------------------------------------------===//
246 // Memory Access Instructions
247 //===----------------------------------------------------------------------===//
248
249 let mayLoad = 1 in {
250 class LoadM<bits<6> op, bits<11> flags, string instr_asm> :
251             TA<op, flags, (outs GPR:$dst), (ins memrr:$addr),
252                !strconcat(instr_asm, "   $dst, $addr"),
253                [], IIC_MEMl>;
254 }
255
256 class LoadMI<bits<6> op, string instr_asm, PatFrag OpNode> :
257              TB<op, (outs GPR:$dst), (ins memri:$addr),
258                 !strconcat(instr_asm, "   $dst, $addr"),
259                 [(set (i32 GPR:$dst), (OpNode iaddr:$addr))], IIC_MEMl>;
260
261 let mayStore = 1 in {
262 class StoreM<bits<6> op, bits<11> flags, string instr_asm> :
263              TA<op, flags, (outs), (ins GPR:$dst, memrr:$addr),
264                 !strconcat(instr_asm, "   $dst, $addr"),
265                 [], IIC_MEMs>;
266 }
267
268 class StoreMI<bits<6> op, string instr_asm, PatFrag OpNode> :
269               TB<op, (outs), (ins GPR:$dst, memri:$addr),
270                  !strconcat(instr_asm, "   $dst, $addr"),
271                  [(OpNode (i32 GPR:$dst), iaddr:$addr)], IIC_MEMs>;
272
273 //===----------------------------------------------------------------------===//
274 // Branch Instructions
275 //===----------------------------------------------------------------------===//
276 class Branch<bits<6> op, bits<5> br, bits<11> flags, string instr_asm> :
277              TA<op, flags, (outs), (ins GPR:$target),
278                 !strconcat(instr_asm, "   $target"),
279                 [], IIC_BR> {
280   let rd = 0x0;
281   let ra = br;
282   let Form = FCCR;
283 }
284
285 class BranchI<bits<6> op, bits<5> br, string instr_asm> :
286               TB<op, (outs), (ins brtarget:$target),
287                  !strconcat(instr_asm, "   $target"),
288                  [], IIC_BR> {
289   let rd = 0;
290   let ra = br;
291   let Form = FCCI;
292 }
293
294 //===----------------------------------------------------------------------===//
295 // Branch and Link Instructions
296 //===----------------------------------------------------------------------===//
297 class BranchL<bits<6> op, bits<5> br, bits<11> flags, string instr_asm> :
298               TA<op, flags, (outs), (ins GPR:$link, GPR:$target, variable_ops),
299                  !strconcat(instr_asm, "   $link, $target"),
300                  [], IIC_BRl> {
301   let ra = br;
302   let Form = FRCR;
303 }
304
305 class BranchLI<bits<6> op, bits<5> br, string instr_asm> :
306                TB<op, (outs), (ins GPR:$link, calltarget:$target, variable_ops),
307                   !strconcat(instr_asm, "   $link, $target"),
308                   [], IIC_BRl> {
309   let ra = br;
310   let Form = FRCI;
311 }
312
313 //===----------------------------------------------------------------------===//
314 // Conditional Branch Instructions
315 //===----------------------------------------------------------------------===//
316 class BranchC<bits<6> op, bits<5> br, bits<11> flags, string instr_asm> :
317               TA<op, flags, (outs),
318                  (ins GPR:$a, GPR:$b),
319                  !strconcat(instr_asm, "   $a, $b"),
320                  [], IIC_BRc> {
321   let rd = br;
322   let Form = FCRR;
323 }
324
325 class BranchCI<bits<6> op, bits<5> br, string instr_asm> :
326                TB<op, (outs), (ins GPR:$a, brtarget:$offset),
327                   !strconcat(instr_asm, "   $a, $offset"),
328                   [], IIC_BRc> {
329   let rd = br;
330   let Form = FCRI;
331 }
332
333 //===----------------------------------------------------------------------===//
334 // MBlaze arithmetic instructions
335 //===----------------------------------------------------------------------===//
336
337 let isCommutable = 1, isAsCheapAsAMove = 1 in {
338   def ADDK   :  Arith<0x04, 0x000, "addk   ", add,  IIC_ALU>;
339   def AND    :  Logic<0x21, 0x000, "and    ", and>;
340   def OR     :  Logic<0x20, 0x000, "or     ", or>;
341   def XOR    :  Logic<0x22, 0x000, "xor    ", xor>;
342
343   let Predicates=[HasPatCmp] in {
344     def PCMPBF : PatCmp<0x20, 0x400, "pcmpbf ">;
345     def PCMPEQ : PatCmp<0x22, 0x400, "pcmpeq ">;
346     def PCMPNE : PatCmp<0x23, 0x400, "pcmpne ">;
347   }
348
349   let Defs = [CARRY] in {
350     def ADD    :  Arith<0x00, 0x000, "add    ", addc, IIC_ALU>;
351
352     let Uses = [CARRY] in {
353       def ADDC   :  Arith<0x02, 0x000, "addc   ", adde, IIC_ALU>;
354     }
355   }
356
357   let Uses = [CARRY] in {
358     def ADDKC  : ArithN<0x06, 0x000, "addkc  ", IIC_ALU>;
359   }
360 }
361
362 let isAsCheapAsAMove = 1 in {
363   def ANDN   :  ArithN<0x23, 0x000, "andn   ", IIC_ALU>;
364   def CMP    :  ArithN<0x05, 0x001, "cmp    ", IIC_ALU>;
365   def CMPU   :  ArithN<0x05, 0x003, "cmpu   ", IIC_ALU>;
366   def RSUBK  :  ArithR<0x05, 0x000, "rsubk  ", sub,  IIC_ALU>;
367
368   let Defs = [CARRY] in {
369     def RSUB   :  ArithR<0x01, 0x000, "rsub   ", subc, IIC_ALU>;
370
371     let Uses = [CARRY] in {
372       def RSUBC  :  ArithR<0x03, 0x000, "rsubc  ", sube, IIC_ALU>;
373     }
374   }
375
376   let Uses = [CARRY] in {
377     def RSUBKC : ArithRN<0x07, 0x000, "rsubkc ", IIC_ALU>;
378   }
379 }
380
381 let isCommutable = 1, Predicates=[HasMul] in {
382   def MUL    : Arith<0x10, 0x000, "mul    ", mul,   IIC_ALUm>;
383 }
384
385 let isCommutable = 1, Predicates=[HasMul,HasMul64] in {
386   def MULH   : Arith<0x10, 0x001, "mulh   ", mulhs, IIC_ALUm>;
387   def MULHU  : Arith<0x10, 0x003, "mulhu  ", mulhu, IIC_ALUm>;
388 }
389
390 let Predicates=[HasMul,HasMul64] in {
391   def MULHSU : ArithN<0x10, 0x002, "mulhsu ", IIC_ALUm>;
392 }
393
394 let Predicates=[HasBarrel] in {
395   def BSRL   :   Arith<0x11, 0x000, "bsrl   ", srl, IIC_SHT>;
396   def BSRA   :   Arith<0x11, 0x200, "bsra   ", sra, IIC_SHT>;
397   def BSLL   :   Arith<0x11, 0x400, "bsll   ", shl, IIC_SHT>;
398   def BSRLI  :  ShiftI<0x19, 0x0, "bsrli  ", srl, uimm5, immZExt5>;
399   def BSRAI  :  ShiftI<0x19, 0x1, "bsrai  ", sra, uimm5, immZExt5>;
400   def BSLLI  :  ShiftI<0x19, 0x2, "bslli  ", shl, uimm5, immZExt5>;
401 }
402
403 let Predicates=[HasDiv] in {
404   def IDIV   :  ArithR<0x12, 0x000, "idiv   ", sdiv, IIC_ALUd>;
405   def IDIVU  :  ArithR<0x12, 0x002, "idivu  ", udiv, IIC_ALUd>;
406 }
407
408 //===----------------------------------------------------------------------===//
409 // MBlaze immediate mode arithmetic instructions
410 //===----------------------------------------------------------------------===//
411
412 let isAsCheapAsAMove = 1 in {
413   def ADDIK   :   ArithI<0x0C, "addik  ", add,  simm16, immSExt16>;
414   def RSUBIK  :  ArithRI<0x0D, "rsubik ", sub, simm16, immSExt16>;
415   def ANDNI   :  ArithNI<0x2B, "andni  ", uimm16, immZExt16>;
416   def ANDI    :   LogicI<0x29, "andi   ", and>;
417   def ORI     :   LogicI<0x28, "ori    ", or>;
418   def XORI    :   LogicI<0x2A, "xori   ", xor>;
419
420   let Defs = [CARRY] in {
421     def ADDI    :   ArithI<0x08, "addi   ", addc, simm16, immSExt16>;
422     def RSUBI   :  ArithRI<0x09, "rsubi  ", subc,  simm16, immSExt16>;
423
424     let Uses = [CARRY] in {
425       def ADDIC   :   ArithI<0x0A, "addic  ", adde, simm16, immSExt16>;
426       def RSUBIC  :  ArithRI<0x0B, "rsubic ", sube, simm16, immSExt16>;
427     }
428   }
429
430   let Uses = [CARRY] in {
431     def ADDIKC  :  ArithNI<0x0E, "addikc ", simm16, immSExt16>;
432     def RSUBIKC : ArithRNI<0x0F, "rsubikc", simm16, immSExt16>;
433   }
434 }
435
436 let Predicates=[HasMul] in {
437   def MULI    :   ArithI<0x18, "muli   ", mul, simm16, immSExt16>;
438 }
439
440 //===----------------------------------------------------------------------===//
441 // MBlaze memory access instructions
442 //===----------------------------------------------------------------------===//
443
444 let canFoldAsLoad = 1, isReMaterializable = 1 in {
445   let neverHasSideEffects = 1 in {
446     def LBU  :  LoadM<0x30, 0x000, "lbu    ">;
447     def LBUR :  LoadM<0x30, 0x200, "lbur   ">;
448
449     def LHU  :  LoadM<0x31, 0x000, "lhu    ">;
450     def LHUR :  LoadM<0x31, 0x200, "lhur   ">;
451
452     def LW   :  LoadM<0x32, 0x000, "lw     ">;
453     def LWR  :  LoadM<0x32, 0x200, "lwr    ">;
454
455     let Defs = [CARRY] in {
456       def LWX  :  LoadM<0x32, 0x400, "lwx    ">;
457     }
458   }
459
460   def LBUI : LoadMI<0x38, "lbui   ", zextloadi8>;
461   def LHUI : LoadMI<0x39, "lhui   ", zextloadi16>;
462   def LWI  : LoadMI<0x3A, "lwi    ", load>;
463 }
464
465 def SB  :  StoreM<0x34, 0x000, "sb     ">;
466 def SBR :  StoreM<0x34, 0x200, "sbr    ">;
467
468 def SH  :  StoreM<0x35, 0x000, "sh     ">;
469 def SHR :  StoreM<0x35, 0x200, "shr    ">;
470
471 def SW  :  StoreM<0x36, 0x000, "sw     ">;
472 def SWR :  StoreM<0x36, 0x200, "swr    ">;
473
474 let Defs = [CARRY] in {
475   def SWX :  StoreM<0x36, 0x400, "swx    ">;
476 }
477
478 def SBI : StoreMI<0x3C, "sbi    ", truncstorei8>;
479 def SHI : StoreMI<0x3D, "shi    ", truncstorei16>;
480 def SWI : StoreMI<0x3E, "swi    ", store>;
481
482 //===----------------------------------------------------------------------===//
483 // MBlaze branch instructions
484 //===----------------------------------------------------------------------===//
485
486 let isBranch = 1, isTerminator = 1, hasCtrlDep = 1, isBarrier = 1 in {
487   def BRI    :  BranchI<0x2E, 0x00, "bri    ">;
488   def BRAI   :  BranchI<0x2E, 0x08, "brai   ">;
489 }
490
491 let isBranch = 1, isTerminator = 1, hasCtrlDep = 1 in {
492   def BEQI   : BranchCI<0x2F, 0x00, "beqi   ">;
493   def BNEI   : BranchCI<0x2F, 0x01, "bnei   ">;
494   def BLTI   : BranchCI<0x2F, 0x02, "blti   ">;
495   def BLEI   : BranchCI<0x2F, 0x03, "blei   ">;
496   def BGTI   : BranchCI<0x2F, 0x04, "bgti   ">;
497   def BGEI   : BranchCI<0x2F, 0x05, "bgei   ">;
498 }
499
500 let isBranch = 1, isIndirectBranch = 1, isTerminator = 1, hasCtrlDep = 1,
501     isBarrier = 1 in {
502   def BR     :   Branch<0x26, 0x00, 0x000, "br     ">;
503   def BRA    :   Branch<0x26, 0x08, 0x000, "bra    ">;
504 }
505
506 let isBranch = 1, isIndirectBranch = 1, isTerminator = 1, hasCtrlDep = 1 in {
507   def BEQ    :  BranchC<0x27, 0x00, 0x000, "beq    ">;
508   def BNE    :  BranchC<0x27, 0x01, 0x000, "bne    ">;
509   def BLT    :  BranchC<0x27, 0x02, 0x000, "blt    ">;
510   def BLE    :  BranchC<0x27, 0x03, 0x000, "ble    ">;
511   def BGT    :  BranchC<0x27, 0x04, 0x000, "bgt    ">;
512   def BGE    :  BranchC<0x27, 0x05, 0x000, "bge    ">;
513 }
514
515 let isBranch = 1, isTerminator = 1, hasDelaySlot = 1, hasCtrlDep = 1,
516     isBarrier = 1 in {
517   def BRID   :  BranchI<0x2E, 0x10, "brid   ">;
518   def BRAID  :  BranchI<0x2E, 0x18, "braid  ">;
519 }
520
521 let isBranch = 1, isTerminator = 1, hasDelaySlot = 1, hasCtrlDep = 1 in {
522   def BEQID  : BranchCI<0x2F, 0x10, "beqid  ">;
523   def BNEID  : BranchCI<0x2F, 0x11, "bneid  ">;
524   def BLTID  : BranchCI<0x2F, 0x12, "bltid  ">;
525   def BLEID  : BranchCI<0x2F, 0x13, "bleid  ">;
526   def BGTID  : BranchCI<0x2F, 0x14, "bgtid  ">;
527   def BGEID  : BranchCI<0x2F, 0x15, "bgeid  ">;
528 }
529
530 let isBranch = 1, isIndirectBranch = 1, isTerminator = 1,
531     hasDelaySlot = 1, hasCtrlDep = 1, isBarrier = 1 in {
532   def BRD    :   Branch<0x26, 0x10, 0x000, "brd    ">;
533   def BRAD   :   Branch<0x26, 0x18, 0x000, "brad   ">;
534 }
535
536 let isBranch = 1, isIndirectBranch = 1, isTerminator = 1,
537     hasDelaySlot = 1, hasCtrlDep = 1 in {
538   def BEQD   :  BranchC<0x27, 0x10, 0x000, "beqd   ">;
539   def BNED   :  BranchC<0x27, 0x11, 0x000, "bned   ">;
540   def BLTD   :  BranchC<0x27, 0x12, 0x000, "bltd   ">;
541   def BLED   :  BranchC<0x27, 0x13, 0x000, "bled   ">;
542   def BGTD   :  BranchC<0x27, 0x14, 0x000, "bgtd   ">;
543   def BGED   :  BranchC<0x27, 0x15, 0x000, "bged   ">;
544 }
545
546 let isCall =1, hasDelaySlot = 1,
547     Defs = [R3,R4,R5,R6,R7,R8,R9,R10,R11,R12,CARRY],
548     Uses = [R1] in {
549   def BRLID  : BranchLI<0x2E, 0x14, "brlid  ">;
550   def BRALID : BranchLI<0x2E, 0x1C, "bralid ">;
551 }
552
553 let isCall = 1, hasDelaySlot = 1,
554     Defs = [R3,R4,R5,R6,R7,R8,R9,R10,R11,R12,CARRY],
555     Uses = [R1] in {
556   def BRLD   : BranchL<0x26, 0x14, 0x000, "brld   ">;
557   def BRALD  : BranchL<0x26, 0x1C, 0x000, "brald  ">;
558 }
559
560 let isReturn=1, isTerminator=1, hasDelaySlot=1, isBarrier=1,
561     rd=0x10, Form=FCRI in {
562   def RTSD   : TB<0x2D, (outs), (ins GPR:$target, simm16:$imm),
563                   "rtsd      $target, $imm",
564                   [],
565                   IIC_BR>;
566 }
567
568 let isReturn=1, isTerminator=1, hasDelaySlot=1, isBarrier=1,
569     rd=0x11, Form=FCRI in {
570   def RTID   : TB<0x2D, (outs), (ins GPR:$target, simm16:$imm),
571                   "rtid      $target, $imm",
572                   [],
573                   IIC_BR>;
574 }
575
576 let isReturn=1, isTerminator=1, hasDelaySlot=1, isBarrier=1,
577     rd=0x12, Form=FCRI in {
578   def RTBD   : TB<0x2D, (outs), (ins GPR:$target, simm16:$imm),
579                   "rtbd      $target, $imm",
580                   [],
581                   IIC_BR>;
582 }
583
584 let isReturn=1, isTerminator=1, hasDelaySlot=1, isBarrier=1,
585     rd=0x14, Form=FCRI in {
586   def RTED   : TB<0x2D, (outs), (ins GPR:$target, simm16:$imm),
587                   "rted      $target, $imm",
588                   [],
589                   IIC_BR>;
590 }
591
592 //===----------------------------------------------------------------------===//
593 // MBlaze misc instructions
594 //===----------------------------------------------------------------------===//
595
596 let neverHasSideEffects = 1 in {
597   def NOP :  MBlazeInst<0x20, FC, (outs), (ins), "nop    ", [], IIC_ALU>;
598 }
599
600 let Predicates=[HasPatCmp] in {
601   def CLZ :  TCLZ<0x24, 0x00E0, (outs GPR:$dst), (ins GPR:$src),
602                   "clz    $dst, $src", [], IIC_ALU>;
603 }
604
605 def IMEMBAR  : MBAR<0x2E, 0x0420004, (outs), (ins), "mbar   2", [], IIC_ALU>;
606 def DMEMBAR  : MBAR<0x2E, 0x0220004, (outs), (ins), "mbar   1", [], IIC_ALU>;
607 def IDMEMBAR : MBAR<0x2E, 0x0020004, (outs), (ins), "mbar   0", [], IIC_ALU>;
608
609 let usesCustomInserter = 1 in {
610   def Select_CC : MBlazePseudo<(outs GPR:$dst),
611     (ins GPR:$T, GPR:$F, GPR:$CMP, i32imm:$CC), // F T reversed
612     "; SELECT_CC PSEUDO!",
613     []>;
614
615   def ShiftL : MBlazePseudo<(outs GPR:$dst),
616     (ins GPR:$L, GPR:$R),
617     "; ShiftL PSEUDO!",
618     []>;
619
620   def ShiftRA : MBlazePseudo<(outs GPR:$dst),
621     (ins GPR:$L, GPR:$R),
622     "; ShiftRA PSEUDO!",
623     []>;
624
625   def ShiftRL : MBlazePseudo<(outs GPR:$dst),
626     (ins GPR:$L, GPR:$R),
627     "; ShiftRL PSEUDO!",
628     []>;
629 }
630
631 let rb = 0 in {
632   def SEXT16 : TA<0x24, 0x061, (outs GPR:$dst), (ins GPR:$src),
633                   "sext16    $dst, $src", [], IIC_ALU>;
634   def SEXT8  : TA<0x24, 0x060, (outs GPR:$dst), (ins GPR:$src),
635                   "sext8     $dst, $src", [], IIC_ALU>;
636   let Defs = [CARRY] in {
637     def SRL    : TA<0x24, 0x041, (outs GPR:$dst), (ins GPR:$src),
638                     "srl       $dst, $src", [], IIC_ALU>;
639     def SRA    : TA<0x24, 0x001, (outs GPR:$dst), (ins GPR:$src),
640                     "sra       $dst, $src", [], IIC_ALU>;
641     let Uses = [CARRY] in {
642       def SRC    : TA<0x24, 0x021, (outs GPR:$dst), (ins GPR:$src),
643                       "src       $dst, $src", [], IIC_ALU>;
644     }
645   }
646 }
647
648 let isCodeGenOnly=1 in {
649   def ADDIK32 : ArithI32<0x08, "addik  ", simm16, immSExt16>;
650   def ORI32   : LogicI32<0x28, "ori    ">;
651   def BRLID32 : BranchLI<0x2E, 0x14, "brlid  ">;
652 }
653
654 //===----------------------------------------------------------------------===//
655 // Misc. instructions
656 //===----------------------------------------------------------------------===//
657 let Form=FRCS in {
658   def MFS : SPC<0x25, 0x2, (outs GPR:$dst), (ins SPR:$src),
659                 "mfs       $dst, $src", [], IIC_ALU>;
660 }
661
662 let Form=FCRCS in {
663   def MTS : SPC<0x25, 0x3, (outs SPR:$dst), (ins GPR:$src),
664                 "mts       $dst, $src", [], IIC_ALU>;
665 }
666
667 def MSRSET : MSR<0x25, 0x20, (outs GPR:$dst), (ins uimm15:$set),
668                  "msrset    $dst, $set", [], IIC_ALU>;
669
670 def MSRCLR : MSR<0x25, 0x22, (outs GPR:$dst), (ins uimm15:$clr),
671                  "msrclr    $dst, $clr", [], IIC_ALU>;
672
673 let rd=0x0, Form=FCRR in {
674   def WDC  : TA<0x24, 0x64, (outs), (ins GPR:$a, GPR:$b),
675                 "wdc       $a, $b", [], IIC_WDC>;
676   def WDCF : TA<0x24, 0x74, (outs), (ins GPR:$a, GPR:$b),
677                 "wdc.flush $a, $b", [], IIC_WDC>;
678   def WDCC : TA<0x24, 0x66, (outs), (ins GPR:$a, GPR:$b),
679                 "wdc.clear $a, $b", [], IIC_WDC>;
680   def WIC  : TA<0x24, 0x68, (outs), (ins GPR:$a, GPR:$b),
681                 "wic       $a, $b", [], IIC_WDC>;
682 }
683
684 def BRK  :  BranchL<0x26, 0x0C, 0x000, "brk    ">;
685 def BRKI : BranchLI<0x2E, 0x0C, "brki   ">;
686
687 def IMM : MBlazeInst<0x2C, FCCI, (outs), (ins simm16:$imm),
688                      "imm       $imm", [], IIC_ALU>;
689
690 //===----------------------------------------------------------------------===//
691 // Pseudo instructions for atomic operations
692 //===----------------------------------------------------------------------===//
693 let usesCustomInserter=1 in {
694   def CAS32 : MBlazePseudo<(outs GPR:$dst), (ins GPR:$ptr, GPR:$cmp, GPR:$swp),
695     "# atomic compare and swap",
696     [(set GPR:$dst, (atomic_cmp_swap_32 GPR:$ptr, GPR:$cmp, GPR:$swp))]>;
697
698   def SWP32 : MBlazePseudo<(outs GPR:$dst), (ins GPR:$ptr, GPR:$swp),
699     "# atomic swap",
700     [(set GPR:$dst, (atomic_swap_32 GPR:$ptr, GPR:$swp))]>;
701
702   def LAA32 : MBlazePseudo<(outs GPR:$dst), (ins GPR:$ptr, GPR:$val),
703     "# atomic load and add",
704     [(set GPR:$dst, (atomic_load_add_32 GPR:$ptr, GPR:$val))]>;
705
706   def LAS32 : MBlazePseudo<(outs GPR:$dst), (ins GPR:$ptr, GPR:$val),
707     "# atomic load and sub",
708     [(set GPR:$dst, (atomic_load_sub_32 GPR:$ptr, GPR:$val))]>;
709
710   def LAD32 : MBlazePseudo<(outs GPR:$dst), (ins GPR:$ptr, GPR:$val),
711     "# atomic load and and",
712     [(set GPR:$dst, (atomic_load_and_32 GPR:$ptr, GPR:$val))]>;
713
714   def LAO32 : MBlazePseudo<(outs GPR:$dst), (ins GPR:$ptr, GPR:$val),
715     "# atomic load and or",
716     [(set GPR:$dst, (atomic_load_or_32 GPR:$ptr, GPR:$val))]>;
717
718   def LAX32 : MBlazePseudo<(outs GPR:$dst), (ins GPR:$ptr, GPR:$val),
719     "# atomic load and xor",
720     [(set GPR:$dst, (atomic_load_xor_32 GPR:$ptr, GPR:$val))]>;
721
722   def LAN32 : MBlazePseudo<(outs GPR:$dst), (ins GPR:$ptr, GPR:$val),
723     "# atomic load and nand",
724     [(set GPR:$dst, (atomic_load_nand_32 GPR:$ptr, GPR:$val))]>;
725
726   def MEMBARRIER : MBlazePseudo<(outs), (ins),
727     "# memory barrier",
728     [(membarrier (i32 imm), (i32 imm), (i32 imm), (i32 imm), (i32 imm))]>;
729 }
730
731 //===----------------------------------------------------------------------===//
732 //  Arbitrary patterns that map to one or more instructions
733 //===----------------------------------------------------------------------===//
734
735 // Small immediates
736 def : Pat<(i32 0), (ADDK (i32 R0), (i32 R0))>;
737 def : Pat<(i32 immSExt16:$imm), (ADDIK (i32 R0), imm:$imm)>;
738 def : Pat<(i32 immZExt16:$imm), (ORI (i32 R0), imm:$imm)>;
739
740 // Arbitrary immediates
741 def : Pat<(i32 imm:$imm), (ADDIK (i32 R0), imm:$imm)>;
742
743 // In register sign extension
744 def : Pat<(sext_inreg GPR:$src, i16), (SEXT16 GPR:$src)>;
745 def : Pat<(sext_inreg GPR:$src, i8),  (SEXT8 GPR:$src)>;
746
747 // Call
748 def : Pat<(MBlazeJmpLink (i32 tglobaladdr:$dst)),
749           (BRLID (i32 R15), tglobaladdr:$dst)>;
750
751 def : Pat<(MBlazeJmpLink (i32 texternalsym:$dst)),
752           (BRLID (i32 R15), texternalsym:$dst)>;
753
754 def : Pat<(MBlazeJmpLink GPR:$dst),
755           (BRALD (i32 R15), GPR:$dst)>;
756
757 // Shift Instructions
758 def : Pat<(shl GPR:$L, GPR:$R), (ShiftL GPR:$L, GPR:$R)>;
759 def : Pat<(sra GPR:$L, GPR:$R), (ShiftRA GPR:$L, GPR:$R)>;
760 def : Pat<(srl GPR:$L, GPR:$R), (ShiftRL GPR:$L, GPR:$R)>;
761
762 // SET_CC operations
763 def : Pat<(setcc (i32 GPR:$L), (i32 0), SETEQ),
764           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0), GPR:$L, 1)>;
765 def : Pat<(setcc (i32 GPR:$L), (i32 0), SETNE),
766           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0), GPR:$L, 2)>;
767 def : Pat<(setcc (i32 GPR:$L), (i32 0), SETGT),
768           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0), GPR:$L, 3)>;
769 def : Pat<(setcc (i32 GPR:$L), (i32 0), SETLT),
770           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0), GPR:$L, 4)>;
771 def : Pat<(setcc (i32 GPR:$L), (i32 0), SETGE),
772           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0), GPR:$L, 5)>;
773 def : Pat<(setcc (i32 GPR:$L), (i32 0), SETLE),
774           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0), GPR:$L, 6)>;
775 def : Pat<(setcc (i32 GPR:$L), (i32 0), SETUGT),
776           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
777                      (CMPU (i32 R0), GPR:$L), 3)>;
778 def : Pat<(setcc (i32 GPR:$L), (i32 0), SETULT),
779           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
780                      (CMPU (i32 R0), GPR:$L), 4)>;
781 def : Pat<(setcc (i32 GPR:$L), (i32 0), SETUGE),
782           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
783                      (CMPU (i32 R0), GPR:$L), 5)>;
784 def : Pat<(setcc (i32 GPR:$L), (i32 0), SETULE),
785           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
786                      (CMPU (i32 R0), GPR:$L), 6)>;
787
788 def : Pat<(setcc (i32 0), (i32 GPR:$R), SETEQ),
789           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0), GPR:$R, 1)>;
790 def : Pat<(setcc (i32 0), (i32 GPR:$R), SETNE),
791           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0), GPR:$R, 2)>;
792 def : Pat<(setcc (i32 0), (i32 GPR:$R), SETGT),
793           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0), GPR:$R, 3)>;
794 def : Pat<(setcc (i32 0), (i32 GPR:$R), SETLT),
795           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0), GPR:$R, 4)>;
796 def : Pat<(setcc (i32 0), (i32 GPR:$R), SETGE),
797           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0), GPR:$R, 5)>;
798 def : Pat<(setcc (i32 0), (i32 GPR:$R), SETLE),
799           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0), GPR:$R, 6)>;
800 def : Pat<(setcc (i32 0), (i32 GPR:$R), SETUGT),
801           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
802                      (CMPU GPR:$R, (i32 R0)), 3)>;
803 def : Pat<(setcc (i32 0), (i32 GPR:$R), SETULT),
804           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
805                      (CMPU GPR:$R, (i32 R0)), 4)>;
806 def : Pat<(setcc (i32 0), (i32 GPR:$R), SETUGE),
807           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
808                      (CMPU GPR:$R, (i32 R0)), 5)>;
809 def : Pat<(setcc (i32 0), (i32 GPR:$R), SETULE),
810           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
811                      (CMPU GPR:$R, (i32 R0)), 6)>;
812
813 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETEQ),
814           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
815                      (CMP GPR:$R, GPR:$L), 1)>;
816 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETNE),
817           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
818                      (CMP GPR:$R, GPR:$L), 2)>;
819 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETGT),
820           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
821                      (CMP GPR:$R, GPR:$L), 3)>;
822 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETLT),
823           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
824                      (CMP GPR:$R, GPR:$L), 4)>;
825 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETGE),
826           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
827                      (CMP GPR:$R, GPR:$L), 5)>;
828 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETLE),
829           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
830                      (CMP GPR:$R, GPR:$L), 6)>;
831 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETUGT),
832           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
833                      (CMPU GPR:$R, GPR:$L), 3)>;
834 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETULT),
835           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
836                      (CMPU GPR:$R, GPR:$L), 4)>;
837 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETUGE),
838           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
839                      (CMPU GPR:$R, GPR:$L), 5)>;
840 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETULE),
841           (Select_CC (ADDIK (i32 R0), 1), (ADDIK (i32 R0), 0),
842                      (CMPU GPR:$R, GPR:$L), 6)>;
843
844 // SELECT operations
845 def : Pat<(select (i32 GPR:$C), (i32 GPR:$T), (i32 GPR:$F)),
846           (Select_CC GPR:$T, GPR:$F, GPR:$C, 2)>;
847
848 // SELECT_CC
849 def : Pat<(selectcc (i32 GPR:$L), (i32 0),
850                     (i32 GPR:$T), (i32 GPR:$F), SETEQ),
851           (Select_CC GPR:$T, GPR:$F, GPR:$L, 1)>;
852 def : Pat<(selectcc (i32 GPR:$L), (i32 0),
853                     (i32 GPR:$T), (i32 GPR:$F), SETNE),
854           (Select_CC GPR:$T, GPR:$F, GPR:$L, 2)>;
855 def : Pat<(selectcc (i32 GPR:$L), (i32 0),
856                     (i32 GPR:$T), (i32 GPR:$F), SETGT),
857           (Select_CC GPR:$T, GPR:$F, GPR:$L, 3)>;
858 def : Pat<(selectcc (i32 GPR:$L), (i32 0),
859                     (i32 GPR:$T), (i32 GPR:$F), SETLT),
860           (Select_CC GPR:$T, GPR:$F, GPR:$L, 4)>;
861 def : Pat<(selectcc (i32 GPR:$L), (i32 0),
862                     (i32 GPR:$T), (i32 GPR:$F), SETGE),
863           (Select_CC GPR:$T, GPR:$F, GPR:$L, 5)>;
864 def : Pat<(selectcc (i32 GPR:$L), (i32 0),
865                     (i32 GPR:$T), (i32 GPR:$F), SETLE),
866           (Select_CC GPR:$T, GPR:$F, GPR:$L, 6)>;
867 def : Pat<(selectcc (i32 GPR:$L), (i32 0),
868                     (i32 GPR:$T), (i32 GPR:$F), SETUGT),
869           (Select_CC GPR:$T, GPR:$F, (CMPU (i32 R0), GPR:$L), 3)>;
870 def : Pat<(selectcc (i32 GPR:$L), (i32 0),
871                     (i32 GPR:$T), (i32 GPR:$F), SETULT),
872           (Select_CC GPR:$T, GPR:$F, (CMPU (i32 R0), GPR:$L), 4)>;
873 def : Pat<(selectcc (i32 GPR:$L), (i32 0),
874                     (i32 GPR:$T), (i32 GPR:$F), SETUGE),
875           (Select_CC GPR:$T, GPR:$F, (CMPU (i32 R0), GPR:$L), 5)>;
876 def : Pat<(selectcc (i32 GPR:$L), (i32 0),
877                     (i32 GPR:$T), (i32 GPR:$F), SETULE),
878           (Select_CC GPR:$T, GPR:$F, (CMPU (i32 R0), GPR:$L), 6)>;
879
880 def : Pat<(selectcc (i32 0), (i32 GPR:$R),
881                     (i32 GPR:$T), (i32 GPR:$F), SETEQ),
882           (Select_CC GPR:$T, GPR:$F, GPR:$R, 1)>;
883 def : Pat<(selectcc (i32 0), (i32 GPR:$R),
884                     (i32 GPR:$T), (i32 GPR:$F), SETNE),
885           (Select_CC GPR:$T, GPR:$F, GPR:$R, 2)>;
886 def : Pat<(selectcc (i32 0), (i32 GPR:$R),
887                     (i32 GPR:$T), (i32 GPR:$F), SETGT),
888           (Select_CC GPR:$T, GPR:$F, GPR:$R, 3)>;
889 def : Pat<(selectcc (i32 0), (i32 GPR:$R),
890                     (i32 GPR:$T), (i32 GPR:$F), SETLT),
891           (Select_CC GPR:$T, GPR:$F, GPR:$R, 4)>;
892 def : Pat<(selectcc (i32 0), (i32 GPR:$R),
893                     (i32 GPR:$T), (i32 GPR:$F), SETGE),
894           (Select_CC GPR:$T, GPR:$F, GPR:$R, 5)>;
895 def : Pat<(selectcc (i32 0), (i32 GPR:$R),
896                     (i32 GPR:$T), (i32 GPR:$F), SETLE),
897           (Select_CC GPR:$T, GPR:$F, GPR:$R, 6)>;
898 def : Pat<(selectcc (i32 0), (i32 GPR:$R),
899                     (i32 GPR:$T), (i32 GPR:$F), SETUGT),
900           (Select_CC GPR:$T, GPR:$F, (CMPU GPR:$R, (i32 R0)), 3)>;
901 def : Pat<(selectcc (i32 0), (i32 GPR:$R),
902                     (i32 GPR:$T), (i32 GPR:$F), SETULT),
903           (Select_CC GPR:$T, GPR:$F, (CMPU GPR:$R, (i32 R0)), 4)>;
904 def : Pat<(selectcc (i32 0), (i32 GPR:$R),
905                     (i32 GPR:$T), (i32 GPR:$F), SETUGE),
906           (Select_CC GPR:$T, GPR:$F, (CMPU GPR:$R, (i32 R0)), 5)>;
907 def : Pat<(selectcc (i32 0), (i32 GPR:$R),
908                     (i32 GPR:$T), (i32 GPR:$F), SETULE),
909           (Select_CC GPR:$T, GPR:$F, (CMPU GPR:$R, (i32 R0)), 6)>;
910
911 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
912                     (i32 GPR:$T), (i32 GPR:$F), SETEQ),
913           (Select_CC GPR:$T, GPR:$F, (CMP GPR:$R, GPR:$L), 1)>;
914 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
915                     (i32 GPR:$T), (i32 GPR:$F), SETNE),
916           (Select_CC GPR:$T, GPR:$F, (CMP GPR:$R, GPR:$L), 2)>;
917 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
918                     (i32 GPR:$T), (i32 GPR:$F), SETGT),
919           (Select_CC GPR:$T, GPR:$F, (CMP GPR:$R, GPR:$L), 3)>;
920 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
921                     (i32 GPR:$T), (i32 GPR:$F), SETLT),
922           (Select_CC GPR:$T, GPR:$F, (CMP GPR:$R, GPR:$L), 4)>;
923 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
924                     (i32 GPR:$T), (i32 GPR:$F), SETGE),
925           (Select_CC GPR:$T, GPR:$F, (CMP GPR:$R, GPR:$L), 5)>;
926 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
927                     (i32 GPR:$T), (i32 GPR:$F), SETLE),
928           (Select_CC GPR:$T, GPR:$F, (CMP GPR:$R, GPR:$L), 6)>;
929 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
930                     (i32 GPR:$T), (i32 GPR:$F), SETUGT),
931           (Select_CC GPR:$T, GPR:$F, (CMPU GPR:$R, GPR:$L), 3)>;
932 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
933                     (i32 GPR:$T), (i32 GPR:$F), SETULT),
934           (Select_CC GPR:$T, GPR:$F, (CMPU GPR:$R, GPR:$L), 4)>;
935 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
936                     (i32 GPR:$T), (i32 GPR:$F), SETUGE),
937           (Select_CC GPR:$T, GPR:$F, (CMPU GPR:$R, GPR:$L), 5)>;
938 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
939                     (i32 GPR:$T), (i32 GPR:$F), SETULE),
940           (Select_CC GPR:$T, GPR:$F, (CMPU GPR:$R, GPR:$L), 6)>;
941
942 // Ret instructions
943 def : Pat<(MBlazeRet GPR:$target), (RTSD GPR:$target, 0x8)>;
944 def : Pat<(MBlazeIRet GPR:$target), (RTID GPR:$target, 0x0)>;
945
946 // BR instructions
947 def : Pat<(br bb:$T), (BRID bb:$T)>;
948 def : Pat<(brind GPR:$T), (BRAD GPR:$T)>;
949
950 // BRCOND instructions
951 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 0), SETEQ), bb:$T),
952           (BEQID GPR:$L, bb:$T)>;
953 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 0), SETNE), bb:$T),
954           (BNEID GPR:$L, bb:$T)>;
955 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 0), SETGT), bb:$T),
956           (BGTID GPR:$L, bb:$T)>;
957 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 0), SETLT), bb:$T),
958           (BLTID GPR:$L, bb:$T)>;
959 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 0), SETGE), bb:$T),
960           (BGEID GPR:$L, bb:$T)>;
961 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 0), SETLE), bb:$T),
962           (BLEID GPR:$L, bb:$T)>;
963 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 0), SETUGT), bb:$T),
964           (BGTID (CMPU (i32 R0), GPR:$L), bb:$T)>;
965 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 0), SETULT), bb:$T),
966           (BLTID (CMPU (i32 R0), GPR:$L), bb:$T)>;
967 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 0), SETUGE), bb:$T),
968           (BGEID (CMPU (i32 R0), GPR:$L), bb:$T)>;
969 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 0), SETULE), bb:$T),
970           (BLEID (CMPU (i32 R0), GPR:$L), bb:$T)>;
971
972 def : Pat<(brcond (setcc (i32 0), (i32 GPR:$R), SETEQ), bb:$T),
973           (BEQID GPR:$R, bb:$T)>;
974 def : Pat<(brcond (setcc (i32 0), (i32 GPR:$R), SETNE), bb:$T),
975           (BNEID GPR:$R, bb:$T)>;
976 def : Pat<(brcond (setcc (i32 0), (i32 GPR:$R), SETGT), bb:$T),
977           (BGTID GPR:$R, bb:$T)>;
978 def : Pat<(brcond (setcc (i32 0), (i32 GPR:$R), SETLT), bb:$T),
979           (BLTID GPR:$R, bb:$T)>;
980 def : Pat<(brcond (setcc (i32 0), (i32 GPR:$R), SETGE), bb:$T),
981           (BGEID GPR:$R, bb:$T)>;
982 def : Pat<(brcond (setcc (i32 0), (i32 GPR:$R), SETLE), bb:$T),
983           (BLEID GPR:$R, bb:$T)>;
984 def : Pat<(brcond (setcc (i32 0), (i32 GPR:$R), SETUGT), bb:$T),
985           (BGTID (CMPU GPR:$R, (i32 R0)), bb:$T)>;
986 def : Pat<(brcond (setcc (i32 0), (i32 GPR:$R), SETULT), bb:$T),
987           (BLTID (CMPU GPR:$R, (i32 R0)), bb:$T)>;
988 def : Pat<(brcond (setcc (i32 0), (i32 GPR:$R), SETUGE), bb:$T),
989           (BGEID (CMPU GPR:$R, (i32 R0)), bb:$T)>;
990 def : Pat<(brcond (setcc (i32 0), (i32 GPR:$R), SETULE), bb:$T),
991           (BLEID (CMPU GPR:$R, (i32 R0)), bb:$T)>;
992
993 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETEQ), bb:$T),
994           (BEQID (CMP GPR:$R, GPR:$L), bb:$T)>;
995 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETNE), bb:$T),
996           (BNEID (CMP GPR:$R, GPR:$L), bb:$T)>;
997 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETGT), bb:$T),
998           (BGTID (CMP GPR:$R, GPR:$L), bb:$T)>;
999 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETLT), bb:$T),
1000           (BLTID (CMP GPR:$R, GPR:$L), bb:$T)>;
1001 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETGE), bb:$T),
1002           (BGEID (CMP GPR:$R, GPR:$L), bb:$T)>;
1003 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETLE), bb:$T),
1004           (BLEID (CMP GPR:$R, GPR:$L), bb:$T)>;
1005 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETUGT), bb:$T),
1006           (BGTID (CMPU GPR:$R, GPR:$L), bb:$T)>;
1007 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETULT), bb:$T),
1008           (BLTID (CMPU GPR:$R, GPR:$L), bb:$T)>;
1009 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETUGE), bb:$T),
1010           (BGEID (CMPU GPR:$R, GPR:$L), bb:$T)>;
1011 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETULE), bb:$T),
1012           (BLEID (CMPU GPR:$R, GPR:$L), bb:$T)>;
1013 def : Pat<(brcond (i32 GPR:$C), bb:$T),
1014           (BNEID GPR:$C, bb:$T)>;
1015
1016 // Jump tables, global addresses, and constant pools
1017 def : Pat<(MBWrapper tglobaladdr:$in), (ORI (i32 R0), tglobaladdr:$in)>;
1018 def : Pat<(MBWrapper tjumptable:$in),  (ORI (i32 R0), tjumptable:$in)>;
1019 def : Pat<(MBWrapper tconstpool:$in),  (ORI (i32 R0), tconstpool:$in)>;
1020
1021 // Misc instructions
1022 def : Pat<(and (i32 GPR:$lh), (not (i32 GPR:$rh))),(ANDN GPR:$lh, GPR:$rh)>;
1023
1024 // Convert any extend loads into zero extend loads
1025 def : Pat<(extloadi8  iaddr:$src), (i32 (LBUI iaddr:$src))>;
1026 def : Pat<(extloadi16 iaddr:$src), (i32 (LHUI iaddr:$src))>;
1027 def : Pat<(extloadi8  xaddr:$src), (i32 (LBU xaddr:$src))>;
1028 def : Pat<(extloadi16 xaddr:$src), (i32 (LHU xaddr:$src))>;
1029
1030 // 32-bit load and store
1031 def : Pat<(store (i32 GPR:$dst), xaddr:$addr), (SW GPR:$dst, xaddr:$addr)>;
1032 def : Pat<(load xaddr:$addr), (i32 (LW xaddr:$addr))>;
1033
1034 // 16-bit load and store
1035 def : Pat<(truncstorei16 (i32 GPR:$dst), xaddr:$ad), (SH GPR:$dst, xaddr:$ad)>;
1036 def : Pat<(zextloadi16 xaddr:$addr), (i32 (LHU xaddr:$addr))>;
1037
1038 // 8-bit load and store
1039 def : Pat<(truncstorei8 (i32 GPR:$dst), xaddr:$ad), (SB GPR:$dst, xaddr:$ad)>;
1040 def : Pat<(zextloadi8 xaddr:$addr), (i32 (LBU xaddr:$addr))>;
1041
1042 // Peepholes
1043 def : Pat<(store (i32 0), iaddr:$dst), (SWI (i32 R0), iaddr:$dst)>;
1044
1045 // Atomic fence
1046 def : Pat<(atomic_fence (imm), (imm)), (MEMBARRIER)>;
1047
1048 //===----------------------------------------------------------------------===//
1049 // Floating Point Support
1050 //===----------------------------------------------------------------------===//
1051 include "MBlazeInstrFSL.td"
1052 include "MBlazeInstrFPU.td"