1 //===- MBlazeInstrInfo.td - MBlaze Instruction defs --------*- tablegen -*-===//
3 // The LLVM Compiler Infrastructure
5 // This file is distributed under the University of Illinois Open Source
6 // License. See LICENSE.TXT for details.
8 //===----------------------------------------------------------------------===//
10 //===----------------------------------------------------------------------===//
11 // Instruction format superclass
12 //===----------------------------------------------------------------------===//
13 include "MBlazeInstrFormats.td"
15 //===----------------------------------------------------------------------===//
16 // MBlaze type profiles
17 //===----------------------------------------------------------------------===//
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>]>;
25 //===----------------------------------------------------------------------===//
26 // MBlaze specific nodes
27 //===----------------------------------------------------------------------===//
29 def MBlazeRet : SDNode<"MBlazeISD::Ret", SDT_MBlazeRet,
30 [SDNPHasChain, SDNPOptInFlag]>;
32 def MBlazeJmpLink : SDNode<"MBlazeISD::JmpLink",SDT_MBlazeJmpLink,
33 [SDNPHasChain,SDNPOptInFlag,SDNPOutFlag]>;
35 def MBWrapper : SDNode<"MBlazeISD::Wrap", SDTIntUnaryOp>;
37 def callseq_start : SDNode<"ISD::CALLSEQ_START", SDT_MBCallSeqStart,
38 [SDNPHasChain, SDNPOutFlag]>;
40 def callseq_end : SDNode<"ISD::CALLSEQ_END", SDT_MBCallSeqEnd,
41 [SDNPHasChain, SDNPOptInFlag, SDNPOutFlag]>;
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()">;
63 //===----------------------------------------------------------------------===//
64 // MBlaze Operand, Complex Patterns and Transformations Definitions.
65 //===----------------------------------------------------------------------===//
67 // Instruction operand types
68 def brtarget : Operand<OtherVT>;
69 def calltarget : Operand<i32>;
70 def simm16 : Operand<i32>;
71 def uimm5 : Operand<i32>;
72 def fimm : Operand<f32>;
75 def uimm16 : Operand<i32> {
76 let PrintMethod = "printUnsignedImm";
80 def fslimm : Operand<i32> {
81 let PrintMethod = "printFSLImm";
85 def memri : Operand<i32> {
86 let PrintMethod = "printMemOperand";
87 let MIOperandInfo = (ops simm16, GPR);
90 def memrr : Operand<i32> {
91 let PrintMethod = "printMemOperand";
92 let MIOperandInfo = (ops GPR, GPR);
95 // Node immediate fits as 16-bit sign extended on target immediate.
96 def immSExt16 : PatLeaf<(imm), [{
97 return (N->getZExtValue() >> 16) == 0;
100 // Node immediate fits as 16-bit zero extended on target immediate.
101 // The LO16 param means that only the lower 16 bits of the node
102 // immediate are caught.
104 def immZExt16 : PatLeaf<(imm), [{
105 return (N->getZExtValue() >> 16) == 0;
108 // FSL immediate field must fit in 4 bits.
109 def immZExt4 : PatLeaf<(imm), [{
110 return N->getZExtValue() == ((N->getZExtValue()) & 0xf) ;
113 // shamt field must fit in 5 bits.
114 def immZExt5 : PatLeaf<(imm), [{
115 return N->getZExtValue() == ((N->getZExtValue()) & 0x1f) ;
118 // MBlaze Address Mode. SDNode frameindex could possibily be a match
119 // since load and store instructions from stack used it.
120 def iaddr : ComplexPattern<i32, 2, "SelectAddrRegImm", [frameindex], []>;
121 def xaddr : ComplexPattern<i32, 2, "SelectAddrRegReg", [], []>;
123 //===----------------------------------------------------------------------===//
124 // Pseudo instructions
125 //===----------------------------------------------------------------------===//
127 // As stack alignment is always done with addiu, we need a 16-bit immediate
128 let Defs = [R1], Uses = [R1] in {
129 def ADJCALLSTACKDOWN : MBlazePseudo<(outs), (ins simm16:$amt),
130 "#ADJCALLSTACKDOWN $amt",
131 [(callseq_start timm:$amt)]>;
132 def ADJCALLSTACKUP : MBlazePseudo<(outs),
133 (ins uimm16:$amt1, simm16:$amt2),
134 "#ADJCALLSTACKUP $amt1",
135 [(callseq_end timm:$amt1, timm:$amt2)]>;
138 //===----------------------------------------------------------------------===//
139 // Instructions specific format
140 //===----------------------------------------------------------------------===//
142 //===----------------------------------------------------------------------===//
143 // Arithmetic Instructions
144 //===----------------------------------------------------------------------===//
145 class Arith<bits<6> op, bits<11> flags, string instr_asm, SDNode OpNode,
146 InstrItinClass itin> :
147 TA<op, flags, (outs GPR:$dst), (ins GPR:$b, GPR:$c),
148 !strconcat(instr_asm, " $dst, $b, $c"),
149 [(set GPR:$dst, (OpNode GPR:$b, GPR:$c))], itin>;
151 class ArithI<bits<6> op, string instr_asm, SDNode OpNode,
152 Operand Od, PatLeaf imm_type> :
153 TB<op, (outs GPR:$dst), (ins GPR:$b, Od:$c),
154 !strconcat(instr_asm, " $dst, $b, $c"),
155 [(set GPR:$dst, (OpNode GPR:$b, imm_type:$c))], IIAlu>;
157 class ArithR<bits<6> op, bits<11> flags, string instr_asm, SDNode OpNode,
158 InstrItinClass itin> :
159 TA<op, flags, (outs GPR:$dst), (ins GPR:$c, GPR:$b),
160 !strconcat(instr_asm, " $dst, $c, $b"),
161 [(set GPR:$dst, (OpNode GPR:$b, GPR:$c))], itin>;
163 class ArithRI<bits<6> op, string instr_asm, SDNode OpNode,
164 Operand Od, PatLeaf imm_type> :
165 TBR<op, (outs GPR:$dst), (ins Od:$b, GPR:$c),
166 !strconcat(instr_asm, " $dst, $c, $b"),
167 [(set GPR:$dst, (OpNode imm_type:$b, GPR:$c))], IIAlu>;
169 class ArithN<bits<6> op, bits<11> flags, string instr_asm,
170 InstrItinClass itin> :
171 TA<op, flags, (outs GPR:$dst), (ins GPR:$b, GPR:$c),
172 !strconcat(instr_asm, " $dst, $b, $c"),
175 class ArithNI<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"),
180 class ArithRN<bits<6> op, bits<11> flags, string instr_asm,
181 InstrItinClass itin> :
182 TA<op, flags, (outs GPR:$dst), (ins GPR:$c, GPR:$b),
183 !strconcat(instr_asm, " $dst, $b, $c"),
186 class ArithRNI<bits<6> op, string instr_asm,Operand Od, PatLeaf imm_type> :
187 TB<op, (outs GPR:$dst), (ins Od:$c, GPR:$b),
188 !strconcat(instr_asm, " $dst, $b, $c"),
191 //===----------------------------------------------------------------------===//
192 // Misc Arithmetic Instructions
193 //===----------------------------------------------------------------------===//
195 class Logic<bits<6> op, bits<11> flags, string instr_asm, SDNode OpNode> :
196 TA<op, flags, (outs GPR:$dst), (ins GPR:$b, GPR:$c),
197 !strconcat(instr_asm, " $dst, $b, $c"),
198 [(set GPR:$dst, (OpNode GPR:$b, GPR:$c))], IIAlu>;
200 class LogicI<bits<6> op, string instr_asm, SDNode OpNode> :
201 TB<op, (outs GPR:$dst), (ins GPR:$b, uimm16:$c),
202 !strconcat(instr_asm, " $dst, $b, $c"),
203 [(set GPR:$dst, (OpNode GPR:$b, immZExt16:$c))],
206 class PatCmp<bits<6> op, bits<11> flags, string instr_asm> :
207 TA<op, flags, (outs GPR:$dst), (ins GPR:$b, GPR:$c),
208 !strconcat(instr_asm, " $dst, $b, $c"),
211 //===----------------------------------------------------------------------===//
212 // Memory Access Instructions
213 //===----------------------------------------------------------------------===//
214 class LoadM<bits<6> op, string instr_asm, PatFrag OpNode> :
215 TA<op, 0x000, (outs GPR:$dst), (ins memrr:$addr),
216 !strconcat(instr_asm, " $dst, $addr"),
217 [(set (i32 GPR:$dst), (OpNode xaddr:$addr))], IILoad>;
219 class LoadW<bits<6> op, bits<11> flags, string instr_asm> :
220 TA<op, flags, (outs GPR:$dst), (ins memrr:$addr),
221 !strconcat(instr_asm, " $dst, $addr"),
224 class LoadMI<bits<6> op, string instr_asm, PatFrag OpNode> :
225 TBR<op, (outs GPR:$dst), (ins memri:$addr),
226 !strconcat(instr_asm, " $dst, $addr"),
227 [(set (i32 GPR:$dst), (OpNode iaddr:$addr))], IILoad>;
229 class StoreM<bits<6> op, string instr_asm, PatFrag OpNode> :
230 TA<op, 0x000, (outs), (ins GPR:$dst, memrr:$addr),
231 !strconcat(instr_asm, " $dst, $addr"),
232 [(OpNode (i32 GPR:$dst), xaddr:$addr)], IIStore>;
234 class StoreW<bits<6> op, bits<11> flags, string instr_asm> :
235 TA<op, flags, (outs), (ins GPR:$dst, memrr:$addr),
236 !strconcat(instr_asm, " $dst, $addr"),
239 class StoreMI<bits<6> op, string instr_asm, PatFrag OpNode> :
240 TBR<op, (outs), (ins GPR:$dst, memri:$addr),
241 !strconcat(instr_asm, " $dst, $addr"),
242 [(OpNode (i32 GPR:$dst), iaddr:$addr)], IIStore>;
244 //===----------------------------------------------------------------------===//
245 // Branch Instructions
246 //===----------------------------------------------------------------------===//
247 class Branch<bits<6> op, bits<5> br, bits<11> flags, string instr_asm> :
248 TA<op, flags, (outs), (ins GPR:$target),
249 !strconcat(instr_asm, " $target"),
256 class BranchI<bits<6> op, bits<5> br, string instr_asm> :
257 TB<op, (outs), (ins brtarget:$target),
258 !strconcat(instr_asm, " $target"),
265 //===----------------------------------------------------------------------===//
266 // Branch and Link Instructions
267 //===----------------------------------------------------------------------===//
268 class BranchL<bits<6> op, bits<5> br, bits<11> flags, string instr_asm> :
269 TA<op, flags, (outs), (ins GPR:$link, GPR:$target),
270 !strconcat(instr_asm, " $link, $target"),
276 class BranchLI<bits<6> op, bits<5> br, string instr_asm> :
277 TB<op, (outs), (ins GPR:$link, calltarget:$target),
278 !strconcat(instr_asm, " $link, $target"),
284 //===----------------------------------------------------------------------===//
285 // Conditional Branch Instructions
286 //===----------------------------------------------------------------------===//
287 class BranchC<bits<6> op, bits<5> br, bits<11> flags, string instr_asm,
289 TA<op, flags, (outs),
290 (ins GPR:$a, GPR:$b, brtarget:$offset),
291 !strconcat(instr_asm, " $a, $b, $offset"),
297 class BranchCI<bits<6> op, bits<5> br, string instr_asm, PatFrag cond_op> :
298 TB<op, (outs), (ins GPR:$a, brtarget:$offset),
299 !strconcat(instr_asm, " $a, $offset"),
305 //===----------------------------------------------------------------------===//
306 // MBlaze arithmetic instructions
307 //===----------------------------------------------------------------------===//
309 let isCommutable = 1, isAsCheapAsAMove = 1 in {
310 def ADD : Arith<0x00, 0x000, "add ", add, IIAlu>;
311 def ADDC : Arith<0x02, 0x000, "addc ", adde, IIAlu>;
312 def ADDK : Arith<0x04, 0x000, "addk ", addc, IIAlu>;
313 def ADDKC : ArithN<0x06, 0x000, "addkc ", IIAlu>;
314 def AND : Logic<0x21, 0x000, "and ", and>;
315 def OR : Logic<0x20, 0x000, "or ", or>;
316 def XOR : Logic<0x22, 0x000, "xor ", xor>;
317 def PCMPBF : PatCmp<0x20, 0x400, "pcmpbf ">;
318 def PCMPEQ : PatCmp<0x23, 0x400, "pcmpeq ">;
319 def PCMPNE : PatCmp<0x22, 0x400, "pcmpne ">;
322 let isAsCheapAsAMove = 1 in {
323 def ANDN : ArithN<0x23, 0x000, "andn ", IIAlu>;
324 def CMP : ArithN<0x05, 0x001, "cmp ", IIAlu>;
325 def CMPU : ArithN<0x05, 0x003, "cmpu ", IIAlu>;
326 def RSUB : ArithR<0x01, 0x000, "rsub ", sub, IIAlu>;
327 def RSUBC : ArithR<0x03, 0x000, "rsubc ", sube, IIAlu>;
328 def RSUBK : ArithR<0x05, 0x000, "rsubk ", subc, IIAlu>;
329 def RSUBKC : ArithRN<0x07, 0x000, "rsubkc ", IIAlu>;
332 let isCommutable = 1, Predicates=[HasMul] in {
333 def MUL : Arith<0x10, 0x000, "mul ", mul, IIAlu>;
336 let isCommutable = 1, Predicates=[HasMul,HasMul64] in {
337 def MULH : Arith<0x10, 0x001, "mulh ", mulhs, IIAlu>;
338 def MULHU : Arith<0x10, 0x003, "mulhu ", mulhu, IIAlu>;
341 let Predicates=[HasMul,HasMul64] in {
342 def MULHSU : ArithN<0x10, 0x002, "mulhsu ", IIAlu>;
345 let Predicates=[HasBarrel] in {
346 def BSRL : Arith<0x11, 0x000, "bsrl ", srl, IIAlu>;
347 def BSRA : Arith<0x11, 0x200, "bsra ", sra, IIAlu>;
348 def BSLL : Arith<0x11, 0x400, "bsll ", shl, IIAlu>;
349 def BSRLI : ArithI<0x11, "bsrli ", srl, uimm5, immZExt5>;
350 def BSRAI : ArithI<0x11, "bsrai ", sra, uimm5, immZExt5>;
351 def BSLLI : ArithI<0x11, "bslli ", shl, uimm5, immZExt5>;
354 let Predicates=[HasDiv] in {
355 def IDIV : Arith<0x12, 0x000, "idiv ", sdiv, IIAlu>;
356 def IDIVU : Arith<0x12, 0x002, "idivu ", udiv, IIAlu>;
359 //===----------------------------------------------------------------------===//
360 // MBlaze immediate mode arithmetic instructions
361 //===----------------------------------------------------------------------===//
363 let isAsCheapAsAMove = 1 in {
364 def ADDI : ArithI<0x08, "addi ", add, simm16, immSExt16>;
365 def ADDIC : ArithNI<0x0A, "addic ", simm16, immSExt16>;
366 def ADDIK : ArithNI<0x0C, "addik ", simm16, immSExt16>;
367 def ADDIKC : ArithI<0x0E, "addikc ", addc, simm16, immSExt16>;
368 def RSUBI : ArithRI<0x09, "rsubi ", sub, simm16, immSExt16>;
369 def RSUBIC : ArithRNI<0x0B, "rsubi ", simm16, immSExt16>;
370 def RSUBIK : ArithRNI<0x0E, "rsubic ", simm16, immSExt16>;
371 def RSUBIKC : ArithRI<0x0F, "rsubikc", subc, simm16, immSExt16>;
372 def ANDNI : ArithNI<0x2B, "andni ", uimm16, immZExt16>;
373 def ANDI : LogicI<0x29, "andi ", and>;
374 def ORI : LogicI<0x28, "ori ", or>;
375 def XORI : LogicI<0x2A, "xori ", xor>;
378 let Predicates=[HasMul] in {
379 def MULI : ArithI<0x18, "muli ", mul, simm16, immSExt16>;
382 //===----------------------------------------------------------------------===//
383 // MBlaze memory access instructions
384 //===----------------------------------------------------------------------===//
386 let canFoldAsLoad = 1, isReMaterializable = 1 in {
387 def LBU : LoadM<0x30, "lbu ", zextloadi8>;
388 def LHU : LoadM<0x31, "lhu ", zextloadi16>;
390 def LW : LoadW<0x32, 0x0, "lw ">;
391 def LWR : LoadW<0x32, 0x2, "lwr ">;
392 def LWX : LoadW<0x32, 0x4, "lwx ">;
394 def LBUI : LoadMI<0x38, "lbui ", zextloadi8>;
395 def LHUI : LoadMI<0x39, "lhui ", zextloadi16>;
396 def LWI : LoadMI<0x3A, "lwi ", load>;
399 def SB : StoreM<0x34, "sb ", truncstorei8>;
400 def SH : StoreM<0x35, "sh ", truncstorei16>;
402 def SW : StoreW<0x36, 0x0, "sw ">;
403 def SWR : StoreW<0x36, 0x2, "swr ">;
404 def SWX : StoreW<0x36, 0x4, "swx ">;
406 def SBI : StoreMI<0x3C, "sbi ", truncstorei8>;
407 def SHI : StoreMI<0x3D, "shi ", truncstorei16>;
408 def SWI : StoreMI<0x3E, "swi ", store>;
410 //===----------------------------------------------------------------------===//
411 // MBlaze branch instructions
412 //===----------------------------------------------------------------------===//
414 let isBranch = 1, isTerminator = 1, hasCtrlDep = 1, isBarrier = 1 in {
415 def BRI : BranchI<0x2E, 0x00, "bri ">;
416 def BRAI : BranchI<0x2E, 0x08, "brai ">;
419 let isBranch = 1, isTerminator = 1, hasCtrlDep = 1 in {
420 def BEQI : BranchCI<0x2F, 0x00, "beqi ", seteq>;
421 def BNEI : BranchCI<0x2F, 0x01, "bnei ", setne>;
422 def BLTI : BranchCI<0x2F, 0x02, "blti ", setlt>;
423 def BLEI : BranchCI<0x2F, 0x03, "blei ", setle>;
424 def BGTI : BranchCI<0x2F, 0x04, "bgti ", setgt>;
425 def BGEI : BranchCI<0x2F, 0x05, "bgei ", setge>;
428 let isBranch = 1, isIndirectBranch = 1, isTerminator = 1, hasCtrlDep = 1,
430 def BR : Branch<0x26, 0x00, 0x000, "br ">;
431 def BRA : Branch<0x26, 0x08, 0x000, "bra ">;
434 let isBranch = 1, isIndirectBranch = 1, isTerminator = 1, hasCtrlDep = 1 in {
435 def BEQ : BranchC<0x27, 0x00, 0x000, "beq ", seteq>;
436 def BNE : BranchC<0x27, 0x01, 0x000, "bne ", setne>;
437 def BLT : BranchC<0x27, 0x02, 0x000, "blt ", setlt>;
438 def BLE : BranchC<0x27, 0x03, 0x000, "ble ", setle>;
439 def BGT : BranchC<0x27, 0x04, 0x000, "bgt ", setgt>;
440 def BGE : BranchC<0x27, 0x05, 0x000, "bge ", setge>;
443 let isBranch = 1, isTerminator = 1, hasDelaySlot = 1, hasCtrlDep = 1,
445 def BRID : BranchI<0x2E, 0x10, "brid ">;
446 def BRAID : BranchI<0x2E, 0x18, "braid ">;
449 let isBranch = 1, isTerminator = 1, hasDelaySlot = 1, hasCtrlDep = 1 in {
450 def BEQID : BranchCI<0x2F, 0x10, "beqid ", seteq>;
451 def BNEID : BranchCI<0x2F, 0x11, "bneid ", setne>;
452 def BLTID : BranchCI<0x2F, 0x12, "bltid ", setlt>;
453 def BLEID : BranchCI<0x2F, 0x13, "bleid ", setle>;
454 def BGTID : BranchCI<0x2F, 0x14, "bgtid ", setgt>;
455 def BGEID : BranchCI<0x2F, 0x15, "bgeid ", setge>;
458 let isBranch = 1, isIndirectBranch = 1, isTerminator = 1,
459 hasDelaySlot = 1, hasCtrlDep = 1, isBarrier = 1 in {
460 def BRD : Branch<0x26, 0x10, 0x000, "brd ">;
461 def BRAD : Branch<0x26, 0x18, 0x000, "brad ">;
464 let isBranch = 1, isIndirectBranch = 1, isTerminator = 1,
465 hasDelaySlot = 1, hasCtrlDep = 1 in {
466 def BEQD : BranchC<0x27, 0x10, 0x000, "beqd ", seteq>;
467 def BNED : BranchC<0x27, 0x11, 0x000, "bned ", setne>;
468 def BLTD : BranchC<0x27, 0x12, 0x000, "bltd ", setlt>;
469 def BLED : BranchC<0x27, 0x13, 0x000, "bled ", setle>;
470 def BGTD : BranchC<0x27, 0x14, 0x000, "bgtd ", setgt>;
471 def BGED : BranchC<0x27, 0x15, 0x000, "bged ", setge>;
474 let isCall = 1, hasDelaySlot = 1, hasCtrlDep = 1, isBarrier = 1,
475 Defs = [R3,R4,R5,R6,R7,R8,R9,R10,R11,R12],
476 Uses = [R1,R5,R6,R7,R8,R9,R10] in {
477 def BRLID : BranchLI<0x2E, 0x14, "brlid ">;
478 def BRALID : BranchLI<0x2E, 0x1C, "bralid ">;
481 let isCall = 1, hasDelaySlot = 1, hasCtrlDep = 1, isIndirectBranch = 1,
483 Defs = [R3,R4,R5,R6,R7,R8,R9,R10,R11,R12],
484 Uses = [R1,R5,R6,R7,R8,R9,R10] in {
485 def BRLD : BranchL<0x26, 0x14, 0x000, "brld ">;
486 def BRALD : BranchL<0x26, 0x1C, 0x000, "brald ">;
489 let isReturn=1, isTerminator=1, hasDelaySlot=1, isBarrier=1,
490 hasCtrlDep=1, rd=0x10, Form=FCRI in {
491 def RTSD : TB<0x2D, (outs), (ins GPR:$target, simm16:$imm),
492 "rtsd $target, $imm",
497 let isReturn=1, isTerminator=1, hasDelaySlot=1, isBarrier=1,
498 hasCtrlDep=1, rd=0x11, Form=FCRI in {
499 def RTID : TB<0x2D, (outs), (ins GPR:$target, simm16:$imm),
500 "rtsd $target, $imm",
505 let isReturn=1, isTerminator=1, hasDelaySlot=1, isBarrier=1,
506 hasCtrlDep=1, rd=0x12, Form=FCRI in {
507 def RTBD : TB<0x2D, (outs), (ins GPR:$target, simm16:$imm),
508 "rtsd $target, $imm",
513 let isReturn=1, isTerminator=1, hasDelaySlot=1, isBarrier=1,
514 hasCtrlDep=1, rd=0x14, Form=FCRI in {
515 def RTED : TB<0x2D, (outs), (ins GPR:$target, simm16:$imm),
516 "rtsd $target, $imm",
521 //===----------------------------------------------------------------------===//
522 // MBlaze misc instructions
523 //===----------------------------------------------------------------------===//
525 let neverHasSideEffects = 1 in {
526 def NOP : MBlazeInst< 0x20, FC, (outs), (ins), "nop ", [], IIAlu>;
529 let usesCustomInserter = 1 in {
530 def Select_CC : MBlazePseudo<(outs GPR:$dst),
531 (ins GPR:$T, GPR:$F, GPR:$CMP, i32imm:$CC),
532 "; SELECT_CC PSEUDO!",
535 def ShiftL : MBlazePseudo<(outs GPR:$dst),
536 (ins GPR:$L, GPR:$R),
540 def ShiftRA : MBlazePseudo<(outs GPR:$dst),
541 (ins GPR:$L, GPR:$R),
545 def ShiftRL : MBlazePseudo<(outs GPR:$dst),
546 (ins GPR:$L, GPR:$R),
553 def SEXT16 : TA<0x24, 0x061, (outs GPR:$dst), (ins GPR:$src),
554 "sext16 $dst, $src", [], IIAlu>;
555 def SEXT8 : TA<0x24, 0x060, (outs GPR:$dst), (ins GPR:$src),
556 "sext8 $dst, $src", [], IIAlu>;
557 def SRL : TA<0x24, 0x041, (outs GPR:$dst), (ins GPR:$src),
558 "srl $dst, $src", [], IIAlu>;
559 def SRA : TA<0x24, 0x001, (outs GPR:$dst), (ins GPR:$src),
560 "sra $dst, $src", [], IIAlu>;
561 def SRC : TA<0x24, 0x021, (outs GPR:$dst), (ins GPR:$src),
562 "src $dst, $src", [], IIAlu>;
565 let opcode=0x08, isCodeGenOnly=1 in {
566 def LEA_ADDI : TB<0x08, (outs GPR:$dst), (ins memri:$addr),
567 "addi $dst, ${addr:stackloc}",
568 [(set GPR:$dst, iaddr:$addr)], IIAlu>;
571 //===----------------------------------------------------------------------===//
572 // Misc. instructions
573 //===----------------------------------------------------------------------===//
574 def MFS : MBlazeInst<0x25, FPseudo, (outs), (ins), "mfs", [], IIAlu> {
577 def MTS : MBlazeInst<0x25, FPseudo, (outs), (ins), "mts", [], IIAlu> {
580 def MSRSET : MBlazeInst<0x25, FPseudo, (outs), (ins), "msrset", [], IIAlu> {
583 def MSRCLR : MBlazeInst<0x25, FPseudo, (outs), (ins), "msrclr", [], IIAlu> {
586 let rd=0x0, Form=FCRR in {
587 def WDC : TA<0x24, 0x64, (outs), (ins GPR:$a, GPR:$b),
588 "wdc $a, $b", [], IIAlu>;
589 def WDCF : TA<0x24, 0x74, (outs), (ins GPR:$a, GPR:$b),
590 "wdc.flush $a, $b", [], IIAlu>;
591 def WDCC : TA<0x24, 0x66, (outs), (ins GPR:$a, GPR:$b),
592 "wdc.clear $a, $b", [], IIAlu>;
593 def WIC : TA<0x24, 0x68, (outs), (ins GPR:$a, GPR:$b),
594 "wic $a, $b", [], IIAlu>;
597 def BRK : Branch<0x26, 0x0C, 0x000, "brk ">;
598 def BRKI : BranchI<0x2E, 0x0C, "brki ">;
600 def IMM : MBlazeInst<0x2C, FCCI, (outs), (ins simm16:$imm),
601 "imm $imm", [], IIAlu>;
603 //===----------------------------------------------------------------------===//
604 // Arbitrary patterns that map to one or more instructions
605 //===----------------------------------------------------------------------===//
608 def : Pat<(i32 0), (ADD (i32 R0), (i32 R0))>;
609 def : Pat<(i32 immSExt16:$imm), (ADDI (i32 R0), imm:$imm)>;
610 def : Pat<(i32 immZExt16:$imm), (ORI (i32 R0), imm:$imm)>;
612 // Arbitrary immediates
613 def : Pat<(i32 imm:$imm), (ADDI (i32 R0), imm:$imm)>;
615 // In register sign extension
616 def : Pat<(sext_inreg GPR:$src, i16), (SEXT16 GPR:$src)>;
617 def : Pat<(sext_inreg GPR:$src, i8), (SEXT8 GPR:$src)>;
620 def : Pat<(MBlazeJmpLink (i32 tglobaladdr:$dst)),
621 (BRLID (i32 R15), tglobaladdr:$dst)>;
623 def : Pat<(MBlazeJmpLink (i32 texternalsym:$dst)),
624 (BRLID (i32 R15), texternalsym:$dst)>;
626 def : Pat<(MBlazeJmpLink GPR:$dst),
627 (BRLD (i32 R15), GPR:$dst)>;
629 // Shift Instructions
630 def : Pat<(shl GPR:$L, GPR:$R), (ShiftL GPR:$L, GPR:$R)>;
631 def : Pat<(sra GPR:$L, GPR:$R), (ShiftRA GPR:$L, GPR:$R)>;
632 def : Pat<(srl GPR:$L, GPR:$R), (ShiftRL GPR:$L, GPR:$R)>;
635 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETEQ),
636 (Select_CC (ADDI (i32 R0), 1), (ADDI (i32 R0), 0),
637 (CMP GPR:$L, GPR:$R), 1)>;
638 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETNE),
639 (Select_CC (ADDI (i32 R0), 1), (ADDI (i32 R0), 0),
640 (CMP GPR:$L, GPR:$R), 2)>;
641 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETGT),
642 (Select_CC (ADDI (i32 R0), 1), (ADDI (i32 R0), 0),
643 (CMP GPR:$L, GPR:$R), 3)>;
644 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETLT),
645 (Select_CC (ADDI (i32 R0), 1), (ADDI (i32 R0), 0),
646 (CMP GPR:$L, GPR:$R), 4)>;
647 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETGE),
648 (Select_CC (ADDI (i32 R0), 1), (ADDI (i32 R0), 0),
649 (CMP GPR:$L, GPR:$R), 5)>;
650 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETLE),
651 (Select_CC (ADDI (i32 R0), 1), (ADDI (i32 R0), 0),
652 (CMP GPR:$L, GPR:$R), 6)>;
653 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETUGT),
654 (Select_CC (ADDI (i32 R0), 1), (ADDI (i32 R0), 0),
655 (CMPU GPR:$L, GPR:$R), 3)>;
656 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETULT),
657 (Select_CC (ADDI (i32 R0), 1), (ADDI (i32 R0), 0),
658 (CMPU GPR:$L, GPR:$R), 4)>;
659 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETUGE),
660 (Select_CC (ADDI (i32 R0), 1), (ADDI (i32 R0), 0),
661 (CMPU GPR:$L, GPR:$R), 5)>;
662 def : Pat<(setcc (i32 GPR:$L), (i32 GPR:$R), SETULE),
663 (Select_CC (ADDI (i32 R0), 1), (ADDI (i32 R0), 0),
664 (CMPU GPR:$L, GPR:$R), 6)>;
667 def : Pat<(select (i32 GPR:$C), (i32 GPR:$T), (i32 GPR:$F)),
668 (Select_CC GPR:$T, GPR:$F, GPR:$C, 2)>;
671 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
672 (i32 GPR:$T), (i32 GPR:$F), SETEQ),
673 (Select_CC GPR:$T, GPR:$F, (CMP GPR:$L, GPR:$R), 1)>;
674 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
675 (i32 GPR:$T), (i32 GPR:$F), SETNE),
676 (Select_CC GPR:$T, GPR:$F, (CMP GPR:$L, GPR:$R), 2)>;
677 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
678 (i32 GPR:$T), (i32 GPR:$F), SETGT),
679 (Select_CC GPR:$T, GPR:$F, (CMP GPR:$L, GPR:$R), 3)>;
680 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
681 (i32 GPR:$T), (i32 GPR:$F), SETLT),
682 (Select_CC GPR:$T, GPR:$F, (CMP GPR:$L, GPR:$R), 4)>;
683 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
684 (i32 GPR:$T), (i32 GPR:$F), SETGE),
685 (Select_CC GPR:$T, GPR:$F, (CMP GPR:$L, GPR:$R), 5)>;
686 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
687 (i32 GPR:$T), (i32 GPR:$F), SETLE),
688 (Select_CC GPR:$T, GPR:$F, (CMP GPR:$L, GPR:$R), 6)>;
689 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
690 (i32 GPR:$T), (i32 GPR:$F), SETUGT),
691 (Select_CC GPR:$T, GPR:$F, (CMPU GPR:$L, GPR:$R), 3)>;
692 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
693 (i32 GPR:$T), (i32 GPR:$F), SETULT),
694 (Select_CC GPR:$T, GPR:$F, (CMPU GPR:$L, GPR:$R), 4)>;
695 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
696 (i32 GPR:$T), (i32 GPR:$F), SETUGE),
697 (Select_CC GPR:$T, GPR:$F, (CMPU GPR:$L, GPR:$R), 5)>;
698 def : Pat<(selectcc (i32 GPR:$L), (i32 GPR:$R),
699 (i32 GPR:$T), (i32 GPR:$F), SETULE),
700 (Select_CC GPR:$T, GPR:$F, (CMPU GPR:$L, GPR:$R), 6)>;
703 def : Pat<(MBlazeRet GPR:$target), (RTSD GPR:$target, 0x8)>;
706 def : Pat<(br bb:$T), (BRID bb:$T)>;
707 def : Pat<(brind GPR:$T), (BRD GPR:$T)>;
709 // BRCOND instructions
710 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETEQ), bb:$T),
711 (BEQID (CMP GPR:$R, GPR:$L), bb:$T)>;
712 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETNE), bb:$T),
713 (BNEID (CMP GPR:$R, GPR:$L), bb:$T)>;
714 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETGT), bb:$T),
715 (BGTID (CMP GPR:$R, GPR:$L), bb:$T)>;
716 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETLT), bb:$T),
717 (BLTID (CMP GPR:$R, GPR:$L), bb:$T)>;
718 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETGE), bb:$T),
719 (BGEID (CMP GPR:$R, GPR:$L), bb:$T)>;
720 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETLE), bb:$T),
721 (BLEID (CMP GPR:$R, GPR:$L), bb:$T)>;
722 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETUGT), bb:$T),
723 (BGTID (CMPU GPR:$R, GPR:$L), bb:$T)>;
724 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETULT), bb:$T),
725 (BLTID (CMPU GPR:$R, GPR:$L), bb:$T)>;
726 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETUGE), bb:$T),
727 (BGEID (CMPU GPR:$R, GPR:$L), bb:$T)>;
728 def : Pat<(brcond (setcc (i32 GPR:$L), (i32 GPR:$R), SETULE), bb:$T),
729 (BLEID (CMPU GPR:$R, GPR:$L), bb:$T)>;
730 def : Pat<(brcond (i32 GPR:$C), bb:$T),
731 (BNEID GPR:$C, bb:$T)>;
733 // Jump tables, global addresses, and constant pools
734 def : Pat<(MBWrapper tglobaladdr:$in), (ORI (i32 R0), tglobaladdr:$in)>;
735 def : Pat<(MBWrapper tjumptable:$in), (ORI (i32 R0), tjumptable:$in)>;
736 def : Pat<(MBWrapper tconstpool:$in), (ORI (i32 R0), tconstpool:$in)>;
739 def : Pat<(and (i32 GPR:$lh), (not (i32 GPR:$rh))),(ANDN GPR:$lh, GPR:$rh)>;
741 // Arithmetic with immediates
742 def : Pat<(add (i32 GPR:$in), imm:$imm),(ADDI GPR:$in, imm:$imm)>;
743 def : Pat<(or (i32 GPR:$in), imm:$imm),(ORI GPR:$in, imm:$imm)>;
744 def : Pat<(xor (i32 GPR:$in), imm:$imm),(XORI GPR:$in, imm:$imm)>;
746 // Convert any extend loads into zero extend loads
747 def : Pat<(extloadi8 iaddr:$src), (i32 (LBUI iaddr:$src))>;
748 def : Pat<(extloadi16 iaddr:$src), (i32 (LHUI iaddr:$src))>;
749 def : Pat<(extloadi8 xaddr:$src), (i32 (LBU xaddr:$src))>;
750 def : Pat<(extloadi16 xaddr:$src), (i32 (LHU xaddr:$src))>;
752 // 32-bit load and store
753 def : Pat<(store (i32 GPR:$dst), xaddr:$addr), (SW GPR:$dst, xaddr:$addr)>;
754 def : Pat<(load xaddr:$addr), (i32 (LW xaddr:$addr))>;
757 def : Pat<(store (i32 0), iaddr:$dst), (SWI (i32 R0), iaddr:$dst)>;
759 //===----------------------------------------------------------------------===//
760 // Floating Point Support
761 //===----------------------------------------------------------------------===//
762 include "MBlazeInstrFSL.td"
763 include "MBlazeInstrFPU.td"