Reverting the commit 116986. It was breaking the build on llvm-x86_64-linux though it
[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 profiles and nodes
17 //===----------------------------------------------------------------------===//
18 def SDT_MBlazeRet     : SDTypeProfile<0, 1, [SDTCisInt<0>]>;
19 def SDT_MBlazeJmpLink : SDTypeProfile<0, 1, [SDTCisVT<0, i32>]>;
20
21 // Call
22 def MBlazeJmpLink : SDNode<"MBlazeISD::JmpLink",SDT_MBlazeJmpLink,
23                                [SDNPHasChain,SDNPOptInFlag,SDNPOutFlag]>;
24
25 // Return
26 def MBlazeRet : SDNode<"MBlazeISD::Ret", SDT_MBlazeRet,
27                            [SDNPHasChain, SDNPOptInFlag]>;
28
29 // Hi and Lo nodes are used to handle global addresses. Used on 
30 // MBlazeISelLowering to lower stuff like GlobalAddress, ExternalSymbol 
31 // static model.
32 def MBWrapper   : SDNode<"MBlazeISD::Wrap", SDTIntUnaryOp>;
33 def MBlazeGPRel : SDNode<"MBlazeISD::GPRel", SDTIntUnaryOp>;
34
35 def SDT_MBCallSeqStart : SDCallSeqStart<[SDTCisVT<0, i32>]>;
36 def SDT_MBCallSeqEnd   : SDCallSeqEnd<[SDTCisVT<0, i32>, SDTCisVT<1, i32>]>;
37
38 // These are target-independent nodes, but have target-specific formats.
39 def callseq_start : SDNode<"ISD::CALLSEQ_START", SDT_MBCallSeqStart,
40                            [SDNPHasChain, SDNPOutFlag]>;
41 def callseq_end   : SDNode<"ISD::CALLSEQ_END", SDT_MBCallSeqEnd,
42                            [SDNPHasChain, SDNPOptInFlag, SDNPOutFlag]>;
43
44 def SDTMBlazeSelectCC : SDTypeProfile<1, 3, [SDTCisSameAs<0, 1>]>;
45
46 //===----------------------------------------------------------------------===//
47 // MBlaze Instruction Predicate Definitions.
48 //===----------------------------------------------------------------------===//
49 def HasPipe3     : Predicate<"Subtarget.hasPipe3()">;
50 def HasBarrel    : Predicate<"Subtarget.hasBarrel()">;
51 def NoBarrel     : Predicate<"!Subtarget.hasBarrel()">;
52 def HasDiv       : Predicate<"Subtarget.hasDiv()">;
53 def HasMul       : Predicate<"Subtarget.hasMul()">;
54 def HasFSL       : Predicate<"Subtarget.hasFSL()">;
55 def HasEFSL      : Predicate<"Subtarget.hasEFSL()">;
56 def HasMSRSet    : Predicate<"Subtarget.hasMSRSet()">;
57 def HasException : Predicate<"Subtarget.hasException()">;
58 def HasPatCmp    : Predicate<"Subtarget.hasPatCmp()">;
59 def HasFPU       : Predicate<"Subtarget.hasFPU()">;
60 def HasESR       : Predicate<"Subtarget.hasESR()">;
61 def HasPVR       : Predicate<"Subtarget.hasPVR()">;
62 def HasMul64     : Predicate<"Subtarget.hasMul64()">;
63 def HasSqrt      : Predicate<"Subtarget.hasSqrt()">;
64 def HasMMU       : Predicate<"Subtarget.hasMMU()">;
65
66 //===----------------------------------------------------------------------===//
67 // MBlaze Operand, Complex Patterns and Transformations Definitions.
68 //===----------------------------------------------------------------------===//
69
70 // Instruction operand types
71 def brtarget    : Operand<OtherVT>;
72 def calltarget  : Operand<i32>;
73 def simm16      : Operand<i32>;
74 def uimm5       : Operand<i32>;
75 def fimm        : Operand<f32>;
76
77 // Unsigned Operand
78 def uimm16      : Operand<i32> {
79   let PrintMethod = "printUnsignedImm";
80 }
81
82 // FSL Operand
83 def fslimm      : Operand<i32> {
84   let PrintMethod = "printFSLImm";
85 }
86
87 // Address operand
88 def memri : Operand<i32> {
89   let PrintMethod = "printMemOperand";
90   let MIOperandInfo = (ops simm16, CPURegs);
91 }
92
93 def memrr : Operand<i32> {
94   let PrintMethod = "printMemOperand";
95   let MIOperandInfo = (ops CPURegs, CPURegs);
96 }
97
98 // Transformation Function - get the lower 16 bits.
99 def LO16 : SDNodeXForm<imm, [{
100   return getI32Imm((unsigned)N->getZExtValue() & 0xFFFF);
101 }]>;
102
103 // Transformation Function - get the higher 16 bits.
104 def HI16 : SDNodeXForm<imm, [{
105   return getI32Imm((unsigned)N->getZExtValue() >> 16);
106 }]>;
107
108 // Node immediate fits as 16-bit sign extended on target immediate.
109 // e.g. addi, andi
110 def immSExt16  : PatLeaf<(imm), [{
111   return (N->getZExtValue() >> 16) == 0;
112 }]>;
113
114 // Node immediate fits as 16-bit zero extended on target immediate.
115 // The LO16 param means that only the lower 16 bits of the node
116 // immediate are caught.
117 // e.g. addiu, sltiu
118 def immZExt16  : PatLeaf<(imm), [{
119   return (N->getZExtValue() >> 16) == 0;
120 }], LO16>;
121
122 // FSL immediate field must fit in 4 bits.
123 def immZExt4 : PatLeaf<(imm), [{
124       return N->getZExtValue() == ((N->getZExtValue()) & 0xf) ;
125 }]>;
126
127 // shamt field must fit in 5 bits.
128 def immZExt5 : PatLeaf<(imm), [{
129       return N->getZExtValue() == ((N->getZExtValue()) & 0x1f) ;
130 }]>;
131
132 // MBlaze Address Mode! SDNode frameindex could possibily be a match
133 // since load and store instructions from stack used it.
134 def iaddr : ComplexPattern<i32, 2, "SelectAddrRegImm", [frameindex], []>;
135 def xaddr : ComplexPattern<i32, 2, "SelectAddrRegReg", [], []>;
136
137 //===----------------------------------------------------------------------===//
138 // Pseudo instructions
139 //===----------------------------------------------------------------------===//
140
141 // As stack alignment is always done with addiu, we need a 16-bit immediate
142 let Defs = [R1], Uses = [R1] in {
143 def ADJCALLSTACKDOWN : MBlazePseudo<(outs), (ins simm16:$amt),
144                                   "${:comment} ADJCALLSTACKDOWN $amt",
145                                   [(callseq_start timm:$amt)]>;
146 def ADJCALLSTACKUP   : MBlazePseudo<(outs),
147                                   (ins uimm16:$amt1, simm16:$amt2),
148                                   "${:comment} ADJCALLSTACKUP $amt1",
149                                   [(callseq_end timm:$amt1, timm:$amt2)]>;
150 }
151
152 // Some assembly macros need to avoid pseudoinstructions and assembler
153 // automatic reodering, we should reorder ourselves.
154 def MACRO     : MBlazePseudo<(outs), (ins), ".set macro",     []>;
155 def REORDER   : MBlazePseudo<(outs), (ins), ".set reorder",   []>;
156 def NOMACRO   : MBlazePseudo<(outs), (ins), ".set nomacro",   []>;
157 def NOREORDER : MBlazePseudo<(outs), (ins), ".set noreorder", []>;
158
159 // When handling PIC code the assembler needs .cpload and .cprestore
160 // directives. If the real instructions corresponding these directives
161 // are used, we have the same behavior, but get also a bunch of warnings
162 // from the assembler.
163 def CPLOAD : MBlazePseudo<(outs), (ins CPURegs:$reg), ".cpload $reg", []>;
164 def CPRESTORE : MBlazePseudo<(outs), (ins uimm16:$l), ".cprestore $l\n", []>;
165
166 //===----------------------------------------------------------------------===//
167 // Instructions specific format
168 //===----------------------------------------------------------------------===//
169
170 //===----------------------------------------------------------------------===//
171 // Arithmetic Instructions
172 //===----------------------------------------------------------------------===//
173 class Arith<bits<6> op, bits<11> flags, string instr_asm, SDNode OpNode,
174             InstrItinClass itin> :
175             TA<op, flags, (outs CPURegs:$dst), (ins CPURegs:$b, CPURegs:$c),
176                !strconcat(instr_asm, "   $dst, $b, $c"),
177                [(set CPURegs:$dst, (OpNode CPURegs:$b, CPURegs:$c))], itin>;
178
179 class ArithI<bits<6> op, string instr_asm, SDNode OpNode,
180              Operand Od, PatLeaf imm_type> :
181              TAI<op, (outs CPURegs:$dst), (ins CPURegs:$b, Od:$c),
182                  !strconcat(instr_asm, "   $dst, $b, $c"),
183                  [(set CPURegs:$dst, (OpNode CPURegs:$b, imm_type:$c))], IIAlu>;
184
185 class ArithR<bits<6> op, bits<11> flags, string instr_asm, SDNode OpNode,
186             InstrItinClass itin> :
187             TA<op, flags, (outs CPURegs:$dst), (ins CPURegs:$c, CPURegs:$b),
188                !strconcat(instr_asm, "   $dst, $c, $b"),
189                [(set CPURegs:$dst, (OpNode CPURegs:$b, CPURegs:$c))], itin>;
190
191 class ArithRI<bits<6> op, string instr_asm, SDNode OpNode,
192              Operand Od, PatLeaf imm_type> :
193              TAI<op, (outs CPURegs:$dst), (ins Od:$b, CPURegs:$c),
194                  !strconcat(instr_asm, "   $dst, $c, $b"),
195                  [(set CPURegs:$dst, (OpNode imm_type:$b, CPURegs:$c))], IIAlu>;
196
197 class ArithN<bits<6> op, bits<11> flags, string instr_asm,
198             InstrItinClass itin> :
199             TA<op, flags, (outs CPURegs:$dst), (ins CPURegs:$b, CPURegs:$c),
200                !strconcat(instr_asm, "   $dst, $b, $c"),
201                [], itin>;
202
203 class ArithNI<bits<6> op, string instr_asm,Operand Od, PatLeaf imm_type> :
204              TAI<op, (outs CPURegs:$dst), (ins CPURegs:$b, Od:$c),
205                  !strconcat(instr_asm, "   $dst, $b, $c"),
206                  [], IIAlu>;
207
208 class ArithRN<bits<6> op, bits<11> flags, string instr_asm,
209             InstrItinClass itin> :
210             TA<op, flags, (outs CPURegs:$dst), (ins CPURegs:$c, CPURegs:$b),
211                !strconcat(instr_asm, "   $dst, $b, $c"),
212                [], itin>;
213
214 class ArithRNI<bits<6> op, string instr_asm,Operand Od, PatLeaf imm_type> :
215              TAI<op, (outs CPURegs:$dst), (ins Od:$c, CPURegs:$b),
216                  !strconcat(instr_asm, "   $dst, $b, $c"),
217                  [], IIAlu>;
218
219 //===----------------------------------------------------------------------===//
220 // Misc Arithmetic Instructions
221 //===----------------------------------------------------------------------===//
222
223 class Logic<bits<6> op, bits<11> flags, string instr_asm, SDNode OpNode> :
224             TA<op, flags, (outs CPURegs:$dst), (ins CPURegs:$b, CPURegs:$c),
225                !strconcat(instr_asm, "   $dst, $b, $c"),
226                [(set CPURegs:$dst, (OpNode CPURegs:$b, CPURegs:$c))], IIAlu>;
227
228 class LogicI<bits<6> op, string instr_asm, SDNode OpNode> :
229              TAI<op, (outs CPURegs:$dst), (ins CPURegs:$b, uimm16:$c),
230                  !strconcat(instr_asm, "   $dst, $b, $c"),
231                  [(set CPURegs:$dst, (OpNode CPURegs:$b, immZExt16:$c))],
232                  IIAlu>;
233
234 class EffectiveAddress<string instr_asm> :
235           TAI<0x08, (outs CPURegs:$dst), (ins memri:$addr),
236               instr_asm, [(set CPURegs:$dst, iaddr:$addr)], IIAlu>;
237
238 //===----------------------------------------------------------------------===//
239 // Memory Access Instructions
240 //===----------------------------------------------------------------------===//
241 class LoadM<bits<6> op, string instr_asm, PatFrag OpNode> :
242             TA<op, 0x000, (outs CPURegs:$dst), (ins memrr:$addr),
243                !strconcat(instr_asm, "   $dst, $addr"),
244                [(set CPURegs:$dst, (OpNode xaddr:$addr))], IILoad>;
245
246 class LoadMI<bits<6> op, string instr_asm, PatFrag OpNode> :
247              TAI<op, (outs CPURegs:$dst), (ins memri:$addr),
248                  !strconcat(instr_asm, "   $dst, $addr"),
249                  [(set CPURegs:$dst, (OpNode iaddr:$addr))], IILoad>;
250
251 class StoreM<bits<6> op, string instr_asm, PatFrag OpNode> :
252              TA<op, 0x000, (outs), (ins CPURegs:$dst, memrr:$addr),
253                 !strconcat(instr_asm, "   $dst, $addr"),
254                 [(OpNode CPURegs:$dst, xaddr:$addr)], IIStore>;
255
256 class StoreMI<bits<6> op, string instr_asm, PatFrag OpNode> :
257               TAI<op, (outs), (ins CPURegs:$dst, memri:$addr),
258                   !strconcat(instr_asm, "   $dst, $addr"),
259                   [(OpNode CPURegs:$dst, iaddr:$addr)], IIStore>;
260
261 //===----------------------------------------------------------------------===//
262 // Branch Instructions
263 //===----------------------------------------------------------------------===//
264 class Branch<bits<6> op, bits<5> br, bits<11> flags, string instr_asm> :
265              TBR<op, br, flags, (outs), (ins CPURegs:$target),
266                  !strconcat(instr_asm, "   $target"),
267                  [(brind CPURegs:$target)], IIBranch>;
268
269 class BranchI<bits<6> op, bits<5> brf, string instr_asm> :
270               TBRI<op, brf, (outs), (ins brtarget:$target),
271                    !strconcat(instr_asm, "   $target"),
272                    [(br bb:$target)], IIBranch>;
273
274 //===----------------------------------------------------------------------===//
275 // Branch and Link Instructions
276 //===----------------------------------------------------------------------===//
277 class BranchL<bits<6> op, bits<5> br, bits<11> flags, string instr_asm> :
278               TBRL<op, br, flags, (outs), (ins CPURegs:$target),
279                    !strconcat(instr_asm, "   r15, $target"),
280                    [], IIBranch>;
281
282 class BranchLI<bits<6> op, bits<5> br, string instr_asm> :
283                TBRLI<op, br, (outs), (ins calltarget:$target),
284                      !strconcat(instr_asm, "   r15, $target"),
285                      [], IIBranch>;
286
287 //===----------------------------------------------------------------------===//
288 // Conditional Branch Instructions
289 //===----------------------------------------------------------------------===//
290 class BranchC<bits<6> op, bits<5> br, bits<11> flags, string instr_asm,
291               PatFrag cond_op> :
292               TBRC<op, br, flags, (outs),
293                    (ins CPURegs:$a, CPURegs:$b, brtarget:$offset),
294                    !strconcat(instr_asm, "   $a, $b, $offset"),
295                    [], IIBranch>; 
296                    //(brcond (cond_op CPURegs:$a, CPURegs:$b), bb:$offset)],
297                    //IIBranch>;
298
299 class BranchCI<bits<6> op, bits<5> br, string instr_asm, PatFrag cond_op> :
300                TBRCI<op, br, (outs), (ins CPURegs:$a, brtarget:$offset),
301                      !strconcat(instr_asm, "   $a, $offset"),
302                      [], IIBranch>;
303
304 //===----------------------------------------------------------------------===//
305 // MBlaze arithmetic instructions
306 //===----------------------------------------------------------------------===//
307
308 let isCommutable = 1, isAsCheapAsAMove = 1 in {
309     def ADD    :  Arith<0x00, 0x000, "add    ", add,  IIAlu>;
310     def ADDC   :  Arith<0x02, 0x000, "addc   ", adde, IIAlu>;
311     def ADDK   :  Arith<0x04, 0x000, "addk   ", addc, IIAlu>;
312     def ADDKC  : ArithN<0x06, 0x000, "addkc  ", IIAlu>;
313     def AND    :  Logic<0x21, 0x000, "and    ", and>;
314     def OR     :  Logic<0x20, 0x000, "or     ", or>;
315     def XOR    :  Logic<0x22, 0x000, "xor    ", xor>;
316 }
317
318 let isAsCheapAsAMove = 1 in {
319     def ANDN   :  ArithN<0x23, 0x000, "andn   ", IIAlu>;
320     def CMP    :  ArithN<0x05, 0x001, "cmp    ", IIAlu>;
321     def CMPU   :  ArithN<0x05, 0x003, "cmpu   ", IIAlu>;
322     def RSUB   :  ArithR<0x01, 0x000, "rsub   ", sub,  IIAlu>;
323     def RSUBC  :  ArithR<0x03, 0x000, "rsubc  ", sube, IIAlu>;
324     def RSUBK  :  ArithR<0x05, 0x000, "rsubk  ", subc, IIAlu>;
325     def RSUBKC : ArithRN<0x07, 0x000, "rsubkc ", IIAlu>;
326 }
327
328 let isCommutable = 1, Predicates=[HasMul] in {
329     def MUL    : Arith<0x10, 0x000, "mul    ", mul,   IIAlu>;
330 }
331
332 let isCommutable = 1, Predicates=[HasMul,HasMul64] in {
333     def MULH   : Arith<0x10, 0x001, "mulh   ", mulhs, IIAlu>;
334     def MULHU  : Arith<0x10, 0x003, "mulhu  ", mulhu, IIAlu>;
335 }
336
337 let Predicates=[HasMul,HasMul64] in {
338     def MULHSU : ArithN<0x10, 0x002, "mulhsu ", IIAlu>;
339 }
340
341 let Predicates=[HasBarrel] in {
342     def BSRL   :   Arith<0x11, 0x000, "bsrl   ", srl, IIAlu>;
343     def BSRA   :   Arith<0x11, 0x200, "bsra   ", sra, IIAlu>;
344     def BSLL   :   Arith<0x11, 0x400, "bsll   ", shl, IIAlu>;
345     def BSRLI  :  ArithI<0x11, "bsrli  ", srl, uimm5, immZExt5>;
346     def BSRAI  :  ArithI<0x11, "bsrai  ", sra, uimm5, immZExt5>;
347     def BSLLI  :  ArithI<0x11, "bslli  ", shl, uimm5, immZExt5>;
348 }
349
350 let Predicates=[HasDiv] in {
351     def IDIV   :  Arith<0x12, 0x000, "idiv   ", sdiv, IIAlu>;
352     def IDIVU  :  Arith<0x12, 0x002, "idivu  ", udiv, IIAlu>;
353 }
354
355 //===----------------------------------------------------------------------===//
356 // MBlaze immediate mode arithmetic instructions
357 //===----------------------------------------------------------------------===//
358
359 let isAsCheapAsAMove = 1 in {
360     def ADDI    :   ArithI<0x08, "addi   ", add,  simm16, immSExt16>;
361     def ADDIC   :  ArithNI<0x0A, "addic  ", simm16, immSExt16>;
362     def ADDIK   :  ArithNI<0x0C, "addik  ", simm16, immSExt16>;
363     def ADDIKC  :   ArithI<0x0E, "addikc ", addc, simm16, immSExt16>;
364     def RSUBI   :   ArithRI<0x09, "rsubi  ", sub,  simm16, immSExt16>;
365     def RSUBIC  :  ArithRNI<0x0B, "rsubi  ", simm16, immSExt16>;
366     def RSUBIK  :  ArithRNI<0x0E, "rsubic ", simm16, immSExt16>;
367     def RSUBIKC :   ArithRI<0x0F, "rsubikc", subc, simm16, immSExt16>;
368     def ANDNI   :  ArithNI<0x2B, "andni  ", uimm16, immZExt16>;
369     def ANDI    :   LogicI<0x29, "andi   ", and>;
370     def ORI     :   LogicI<0x28, "ori    ", or>;
371     def XORI    :   LogicI<0x2A, "xori   ", xor>;
372 }
373
374 let Predicates=[HasMul] in {
375     def MULI    :   ArithI<0x18, "muli   ", mul, simm16, immSExt16>;
376 }
377
378 //===----------------------------------------------------------------------===//
379 // MBlaze memory access instructions
380 //===----------------------------------------------------------------------===//
381
382 let canFoldAsLoad = 1, isReMaterializable = 1 in {
383     def LBU  :  LoadM<0x30, "lbu    ", zextloadi8>;
384     def LHU  :  LoadM<0x31, "lhu    ", zextloadi16>;
385     def LW   :  LoadM<0x32, "lw     ", load>;
386
387     def LBUI : LoadMI<0x30, "lbui   ", zextloadi8>;
388     def LHUI : LoadMI<0x31, "lhui   ", zextloadi16>;
389     def LWI  : LoadMI<0x32, "lwi    ", load>;
390 }
391
392     def SB  :  StoreM<0x34, "sb     ", truncstorei8>;
393     def SH  :  StoreM<0x35, "sh     ", truncstorei16>;
394     def SW  :  StoreM<0x36, "sw     ", store>;
395
396     def SBI : StoreMI<0x34, "sbi    ", truncstorei8>;
397     def SHI : StoreMI<0x35, "shi    ", truncstorei16>;
398     def SWI : StoreMI<0x36, "swi    ", store>;
399
400 //===----------------------------------------------------------------------===//
401 // MBlaze branch instructions
402 //===----------------------------------------------------------------------===//
403
404 let isBranch = 1, isTerminator = 1, hasCtrlDep = 1 in {
405     def BRI    :  BranchI<0x2E, 0x00, "bri    ">;
406     def BRAI   :  BranchI<0x2E, 0x08, "brai   ">;
407     def BEQI   : BranchCI<0x2F, 0x00, "beqi   ", seteq>;
408     def BNEI   : BranchCI<0x2F, 0x01, "bnei   ", setne>;
409     def BLTI   : BranchCI<0x2F, 0x02, "blti   ", setlt>;
410     def BLEI   : BranchCI<0x2F, 0x03, "blei   ", setle>;
411     def BGTI   : BranchCI<0x2F, 0x04, "bgti   ", setgt>;
412     def BGEI   : BranchCI<0x2F, 0x05, "bgei   ", setge>;
413 }
414
415 let isBranch = 1, isIndirectBranch = 1, isTerminator = 1, hasCtrlDep = 1 in {
416     def BR     :   Branch<0x26, 0x00, 0x000, "br     ">;
417     def BRA    :   Branch<0x26, 0x08, 0x000, "bra    ">;
418     def BEQ    :  BranchC<0x27, 0x00, 0x000, "beq    ", seteq>;
419     def BNE    :  BranchC<0x27, 0x01, 0x000, "bne    ", setne>;
420     def BLT    :  BranchC<0x27, 0x02, 0x000, "blt    ", setlt>;
421     def BLE    :  BranchC<0x27, 0x03, 0x000, "ble    ", setle>;
422     def BGT    :  BranchC<0x27, 0x04, 0x000, "bgt    ", setgt>;
423     def BGE    :  BranchC<0x27, 0x05, 0x000, "bge    ", setge>;
424 }
425
426 let isBranch = 1, isTerminator = 1, hasDelaySlot = 1, hasCtrlDep = 1 in {
427     def BRID   :  BranchI<0x2E, 0x10, "brid   ">;
428     def BRAID  :  BranchI<0x2E, 0x18, "braid  ">;
429     def BEQID  : BranchCI<0x2F, 0x10, "beqid  ", seteq>;
430     def BNEID  : BranchCI<0x2F, 0x11, "bneid  ", setne>;
431     def BLTID  : BranchCI<0x2F, 0x12, "bltid  ", setlt>;
432     def BLEID  : BranchCI<0x2F, 0x13, "bleid  ", setle>;
433     def BGTID  : BranchCI<0x2F, 0x14, "bgtid  ", setgt>;
434     def BGEID  : BranchCI<0x2F, 0x15, "bgeid  ", setge>;
435 }
436
437 let isBranch = 1, isIndirectBranch = 1, isTerminator = 1,
438     hasDelaySlot = 1, hasCtrlDep = 1 in {
439     def BRD    :   Branch<0x26, 0x10, 0x000, "brd    ">;
440     def BRAD   :   Branch<0x26, 0x18, 0x000, "brad   ">;
441     def BEQD   :  BranchC<0x27, 0x10, 0x000, "beqd   ", seteq>;
442     def BNED   :  BranchC<0x27, 0x11, 0x000, "bned   ", setne>;
443     def BLTD   :  BranchC<0x27, 0x12, 0x000, "bltd   ", setlt>;
444     def BLED   :  BranchC<0x27, 0x13, 0x000, "bled   ", setle>;
445     def BGTD   :  BranchC<0x27, 0x14, 0x000, "bgtd   ", setgt>;
446     def BGED   :  BranchC<0x27, 0x15, 0x000, "bged   ", setge>;
447 }
448
449 let isCall = 1, hasCtrlDep = 1, isIndirectBranch = 1,
450     Defs = [R3,R4,R5,R6,R7,R8,R9,R10,R11,R12],
451     Uses = [R1,R5,R6,R7,R8,R9,R10] in {
452     def BRL    : BranchL<0x26, 0x04, 0x000, "brl    ">;
453     def BRAL   : BranchL<0x26, 0x0C, 0x000, "bral   ">;
454 }
455
456 let isCall = 1, hasDelaySlot = 1, hasCtrlDep = 1,
457     Defs = [R3,R4,R5,R6,R7,R8,R9,R10,R11,R12],
458     Uses = [R1,R5,R6,R7,R8,R9,R10] in {
459     def BRLID  : BranchLI<0x2E, 0x14, "brlid  ">;
460     def BRALID : BranchLI<0x2E, 0x1C, "bralid ">;
461 }
462
463 let isCall = 1, hasDelaySlot = 1, hasCtrlDep = 1, isIndirectBranch = 1,
464     Defs = [R3,R4,R5,R6,R7,R8,R9,R10,R11,R12],
465     Uses = [R1,R5,R6,R7,R8,R9,R10] in {
466     def BRLD   : BranchL<0x26, 0x14, 0x000, "brld   ">;
467     def BRALD  : BranchL<0x26, 0x1C, 0x000, "brald  ">;
468 }
469
470 let isReturn=1, isTerminator=1, hasDelaySlot=1,
471     isBarrier=1, hasCtrlDep=1, imm16=0x8 in {
472     def RTSD   : TRET<0x2D, (outs), (ins CPURegs:$target),
473                       "rtsd      $target, 8",
474                       [(MBlazeRet CPURegs:$target)],
475                       IIBranch>;
476 }
477
478 //===----------------------------------------------------------------------===//
479 // MBlaze misc instructions
480 //===----------------------------------------------------------------------===//
481
482 let addr = 0 in {
483     def NOP :  TADDR<0x00, (outs), (ins), "nop    ", [], IIAlu>;
484 }
485
486 let usesCustomInserter = 1 in {
487   //class PseudoSelCC<RegisterClass RC, string asmstr>:
488   //  MBlazePseudo<(outs RC:$D), (ins RC:$T, RC:$F, CPURegs:$CMP), asmstr,
489   //  [(set RC:$D, (MBlazeSelectCC RC:$T, RC:$F, CPURegs:$CMP))]>;
490   //def Select_CC : PseudoSelCC<CPURegs, "# MBlazeSelect_CC">;
491
492   def Select_CC : MBlazePseudo<(outs CPURegs:$dst),
493     (ins CPURegs:$T, CPURegs:$F, CPURegs:$CMP, i32imm:$CC),
494     "; SELECT_CC PSEUDO!",
495     []>;
496
497   def ShiftL : MBlazePseudo<(outs CPURegs:$dst),
498     (ins CPURegs:$L, CPURegs:$R),
499     "; ShiftL PSEUDO!",
500     []>;
501
502   def ShiftRA : MBlazePseudo<(outs CPURegs:$dst),
503     (ins CPURegs:$L, CPURegs:$R),
504     "; ShiftRA PSEUDO!",
505     []>;
506
507   def ShiftRL : MBlazePseudo<(outs CPURegs:$dst),
508     (ins CPURegs:$L, CPURegs:$R),
509     "; ShiftRL PSEUDO!",
510     []>;
511 }
512
513
514 let rb = 0 in {
515     def SEXT16 : TA<0x24, 0x061, (outs CPURegs:$dst), (ins CPURegs:$src),
516                     "sext16  $dst, $src", [], IIAlu>;
517     def SEXT8  : TA<0x24, 0x060, (outs CPURegs:$dst), (ins CPURegs:$src),
518                     "sext8   $dst, $src", [], IIAlu>;
519     def SRL    : TA<0x24, 0x041, (outs CPURegs:$dst), (ins CPURegs:$src),
520                     "srl     $dst, $src", [], IIAlu>;
521     def SRA    : TA<0x24, 0x001, (outs CPURegs:$dst), (ins CPURegs:$src),
522                     "sra     $dst, $src", [], IIAlu>;
523     def SRC    : TA<0x24, 0x021, (outs CPURegs:$dst), (ins CPURegs:$src),
524                     "src     $dst, $src", [], IIAlu>;
525 }
526
527 def LEA_ADDI : EffectiveAddress<"addi    $dst, ${addr:stackloc}">;
528
529 //===----------------------------------------------------------------------===//
530 //  Arbitrary patterns that map to one or more instructions
531 //===----------------------------------------------------------------------===//
532
533 // Small immediates
534 def : Pat<(i32 0), (ADD R0, R0)>;
535 def : Pat<(i32 immSExt16:$imm), (ADDI R0, imm:$imm)>;
536 def : Pat<(i32 immZExt16:$imm), (ORI R0, imm:$imm)>;
537
538 // Arbitrary immediates
539 def : Pat<(i32 imm:$imm), (ADDI R0, imm:$imm)>;
540
541 // In register sign extension
542 def : Pat<(sext_inreg CPURegs:$src, i16), (SEXT16 CPURegs:$src)>;
543 def : Pat<(sext_inreg CPURegs:$src, i8),  (SEXT8 CPURegs:$src)>;
544
545 // Call
546 def : Pat<(MBlazeJmpLink (i32 tglobaladdr:$dst)), (BRLID tglobaladdr:$dst)>;
547 def : Pat<(MBlazeJmpLink (i32 texternalsym:$dst)),(BRLID texternalsym:$dst)>;
548 def : Pat<(MBlazeJmpLink CPURegs:$dst), (BRLD CPURegs:$dst)>;
549
550 // Shift Instructions
551 def : Pat<(shl CPURegs:$L, CPURegs:$R), (ShiftL CPURegs:$L, CPURegs:$R)>;
552 def : Pat<(sra CPURegs:$L, CPURegs:$R), (ShiftRA CPURegs:$L, CPURegs:$R)>;
553 def : Pat<(srl CPURegs:$L, CPURegs:$R), (ShiftRL CPURegs:$L, CPURegs:$R)>;
554
555 // SET_CC operations
556 def : Pat<(setcc CPURegs:$L, CPURegs:$R, SETEQ),
557           (Select_CC (ADDI R0, 1), (ADDI R0, 0), 
558                      (CMP CPURegs:$L, CPURegs:$R), 1)>;
559 def : Pat<(setcc CPURegs:$L, CPURegs:$R, SETNE),
560           (Select_CC (ADDI R0, 1), (ADDI R0, 0), 
561                      (CMP CPURegs:$L, CPURegs:$R), 2)>;
562 def : Pat<(setcc CPURegs:$L, CPURegs:$R, SETGT),
563           (Select_CC (ADDI R0, 1), (ADDI R0, 0), 
564                      (CMP CPURegs:$L, CPURegs:$R), 3)>;
565 def : Pat<(setcc CPURegs:$L, CPURegs:$R, SETLT),
566           (Select_CC (ADDI R0, 1), (ADDI R0, 0), 
567                      (CMP CPURegs:$L, CPURegs:$R), 4)>;
568 def : Pat<(setcc CPURegs:$L, CPURegs:$R, SETGE),
569           (Select_CC (ADDI R0, 1), (ADDI R0, 0), 
570                      (CMP CPURegs:$L, CPURegs:$R), 5)>;
571 def : Pat<(setcc CPURegs:$L, CPURegs:$R, SETLE),
572           (Select_CC (ADDI R0, 1), (ADDI R0, 0), 
573                      (CMP CPURegs:$L, CPURegs:$R), 6)>;
574 def : Pat<(setcc CPURegs:$L, CPURegs:$R, SETUGT),
575           (Select_CC (ADDI R0, 1), (ADDI R0, 0), 
576                      (CMPU CPURegs:$L, CPURegs:$R), 3)>;
577 def : Pat<(setcc CPURegs:$L, CPURegs:$R, SETULT),
578           (Select_CC (ADDI R0, 1), (ADDI R0, 0), 
579                      (CMPU CPURegs:$L, CPURegs:$R), 4)>;
580 def : Pat<(setcc CPURegs:$L, CPURegs:$R, SETUGE),
581           (Select_CC (ADDI R0, 1), (ADDI R0, 0), 
582                      (CMPU CPURegs:$L, CPURegs:$R), 5)>;
583 def : Pat<(setcc CPURegs:$L, CPURegs:$R, SETULE),
584           (Select_CC (ADDI R0, 1), (ADDI R0, 0), 
585                      (CMPU CPURegs:$L, CPURegs:$R), 6)>;
586
587 // SELECT operations
588 def : Pat<(select CPURegs:$C, CPURegs:$T, CPURegs:$F),
589           (Select_CC CPURegs:$T, CPURegs:$F, CPURegs:$C, 2)>;
590
591 // SELECT_CC 
592 def : Pat<(selectcc CPURegs:$L, CPURegs:$R, CPURegs:$T, CPURegs:$F, SETEQ),
593           (Select_CC CPURegs:$T, CPURegs:$F, (CMP CPURegs:$L, CPURegs:$R), 1)>;
594 def : Pat<(selectcc CPURegs:$L, CPURegs:$R, CPURegs:$T, CPURegs:$F, SETNE),
595           (Select_CC CPURegs:$T, CPURegs:$F, (CMP CPURegs:$L, CPURegs:$R), 2)>;
596 def : Pat<(selectcc CPURegs:$L, CPURegs:$R, CPURegs:$T, CPURegs:$F, SETGT),
597           (Select_CC CPURegs:$T, CPURegs:$F, (CMP CPURegs:$L, CPURegs:$R), 3)>;
598 def : Pat<(selectcc CPURegs:$L, CPURegs:$R, CPURegs:$T, CPURegs:$F, SETLT),
599           (Select_CC CPURegs:$T, CPURegs:$F, (CMP CPURegs:$L, CPURegs:$R), 4)>;
600 def : Pat<(selectcc CPURegs:$L, CPURegs:$R, CPURegs:$T, CPURegs:$F, SETGE),
601           (Select_CC CPURegs:$T, CPURegs:$F, (CMP CPURegs:$L, CPURegs:$R), 5)>;
602 def : Pat<(selectcc CPURegs:$L, CPURegs:$R, CPURegs:$T, CPURegs:$F, SETLE),
603           (Select_CC CPURegs:$T, CPURegs:$F, (CMP CPURegs:$L, CPURegs:$R), 6)>;
604 def : Pat<(selectcc CPURegs:$L, CPURegs:$R, CPURegs:$T, CPURegs:$F, SETUGT),
605           (Select_CC CPURegs:$T, CPURegs:$F, (CMPU CPURegs:$L, CPURegs:$R), 3)>;
606 def : Pat<(selectcc CPURegs:$L, CPURegs:$R, CPURegs:$T, CPURegs:$F, SETULT),
607           (Select_CC CPURegs:$T, CPURegs:$F, (CMPU CPURegs:$L, CPURegs:$R), 4)>;
608 def : Pat<(selectcc CPURegs:$L, CPURegs:$R, CPURegs:$T, CPURegs:$F, SETUGE),
609           (Select_CC CPURegs:$T, CPURegs:$F, (CMPU CPURegs:$L, CPURegs:$R), 5)>;
610 def : Pat<(selectcc CPURegs:$L, CPURegs:$R, CPURegs:$T, CPURegs:$F, SETULE),
611           (Select_CC CPURegs:$T, CPURegs:$F, (CMPU CPURegs:$L, CPURegs:$R), 6)>;
612
613 // BRCOND instructions
614 def : Pat<(brcond (setcc CPURegs:$L, CPURegs:$R, SETEQ), bb:$T),
615           (BEQID (CMP CPURegs:$R, CPURegs:$L), bb:$T)>;
616 def : Pat<(brcond (setcc CPURegs:$L, CPURegs:$R, SETNE), bb:$T),
617           (BNEID (CMP CPURegs:$R, CPURegs:$L), bb:$T)>;
618 def : Pat<(brcond (setcc CPURegs:$L, CPURegs:$R, SETGT), bb:$T),
619           (BGTID (CMP CPURegs:$R, CPURegs:$L), bb:$T)>;
620 def : Pat<(brcond (setcc CPURegs:$L, CPURegs:$R, SETLT), bb:$T),
621           (BLTID (CMP CPURegs:$R, CPURegs:$L), bb:$T)>;
622 def : Pat<(brcond (setcc CPURegs:$L, CPURegs:$R, SETGE), bb:$T),
623           (BGEID (CMP CPURegs:$R, CPURegs:$L), bb:$T)>;
624 def : Pat<(brcond (setcc CPURegs:$L, CPURegs:$R, SETLE), bb:$T),
625           (BLEID (CMP CPURegs:$R, CPURegs:$L), bb:$T)>;
626 def : Pat<(brcond (setcc CPURegs:$L, CPURegs:$R, SETUGT), bb:$T),
627           (BGTID (CMPU CPURegs:$R, CPURegs:$L), bb:$T)>;
628 def : Pat<(brcond (setcc CPURegs:$L, CPURegs:$R, SETULT), bb:$T),
629           (BLTID (CMPU CPURegs:$R, CPURegs:$L), bb:$T)>;
630 def : Pat<(brcond (setcc CPURegs:$L, CPURegs:$R, SETUGE), bb:$T),
631           (BGEID (CMPU CPURegs:$R, CPURegs:$L), bb:$T)>;
632 def : Pat<(brcond (setcc CPURegs:$L, CPURegs:$R, SETULE), bb:$T),
633           (BLEID (CMPU CPURegs:$R, CPURegs:$L), bb:$T)>;
634 def : Pat<(brcond CPURegs:$C, bb:$T),
635           (BNEID CPURegs:$C, bb:$T)>;
636
637 // Jump tables, global addresses, and constant pools
638 def : Pat<(MBWrapper tglobaladdr:$in), (ORI R0, tglobaladdr:$in)>;
639 def : Pat<(MBWrapper tjumptable:$in),  (ORI R0, tjumptable:$in)>;
640 def : Pat<(MBWrapper tconstpool:$in),  (ORI R0, tconstpool:$in)>;
641
642 // Misc instructions
643 def : Pat<(and CPURegs:$lh, (not CPURegs:$rh)),(ANDN CPURegs:$lh, CPURegs:$rh)>;
644
645 // Arithmetic with immediates
646 def : Pat<(add CPURegs:$in, imm:$imm),(ADDI CPURegs:$in, imm:$imm)>;
647 def : Pat<(or CPURegs:$in, imm:$imm),(ORI CPURegs:$in, imm:$imm)>;
648 def : Pat<(xor CPURegs:$in, imm:$imm),(XORI CPURegs:$in, imm:$imm)>;
649
650 // extended load and stores
651 def : Pat<(extloadi1  iaddr:$src), (LBUI iaddr:$src)>;
652 def : Pat<(extloadi8  iaddr:$src), (LBUI iaddr:$src)>;
653 def : Pat<(extloadi16 iaddr:$src), (LHUI iaddr:$src)>;
654 def : Pat<(extloadi1  xaddr:$src), (LBU  xaddr:$src)>;
655 def : Pat<(extloadi8  xaddr:$src), (LBU  xaddr:$src)>;
656 def : Pat<(extloadi16 xaddr:$src), (LHU  xaddr:$src)>;
657
658 def : Pat<(sextloadi1  iaddr:$src), (SEXT8  (LBUI iaddr:$src))>;
659 def : Pat<(sextloadi8  iaddr:$src), (SEXT8  (LBUI iaddr:$src))>;
660 def : Pat<(sextloadi16 iaddr:$src), (SEXT16 (LHUI iaddr:$src))>;
661 def : Pat<(sextloadi1  xaddr:$src), (SEXT8  (LBU xaddr:$src))>;
662 def : Pat<(sextloadi8  xaddr:$src), (SEXT8  (LBU xaddr:$src))>;
663 def : Pat<(sextloadi16 xaddr:$src), (SEXT16 (LHU xaddr:$src))>;
664
665 // peepholes
666 def : Pat<(store (i32 0), iaddr:$dst), (SWI R0, iaddr:$dst)>;
667
668 //===----------------------------------------------------------------------===//
669 // Floating Point Support
670 //===----------------------------------------------------------------------===//
671 include "MBlazeInstrFSL.td"
672 include "MBlazeInstrFPU.td"