[mips] Add tail call instructions.
[oota-llvm.git] / lib / Target / Mips / MipsInstrInfo.td
1 //===- MipsInstrInfo.td - Target Description for Mips Target -*- tablegen -*-=//
2 //
3 //                     The LLVM Compiler Infrastructure
4 //
5 // This file is distributed under the University of Illinois Open Source
6 // License. See LICENSE.TXT for details.
7 //
8 //===----------------------------------------------------------------------===//
9 //
10 // This file contains the Mips implementation of the TargetInstrInfo class.
11 //
12 //===----------------------------------------------------------------------===//
13
14
15 //===----------------------------------------------------------------------===//
16 // Mips profiles and nodes
17 //===----------------------------------------------------------------------===//
18
19 def SDT_MipsJmpLink      : SDTypeProfile<0, 1, [SDTCisVT<0, iPTR>]>;
20 def SDT_MipsCMov         : SDTypeProfile<1, 4, [SDTCisSameAs<0, 1>,
21                                                 SDTCisSameAs<1, 2>,
22                                                 SDTCisSameAs<3, 4>,
23                                                 SDTCisInt<4>]>;
24 def SDT_MipsCallSeqStart : SDCallSeqStart<[SDTCisVT<0, i32>]>;
25 def SDT_MipsCallSeqEnd   : SDCallSeqEnd<[SDTCisVT<0, i32>, SDTCisVT<1, i32>]>;
26 def SDT_MipsMAddMSub     : SDTypeProfile<0, 4,
27                                          [SDTCisVT<0, i32>, SDTCisSameAs<0, 1>,
28                                           SDTCisSameAs<1, 2>,
29                                           SDTCisSameAs<2, 3>]>;
30 def SDT_MipsDivRem       : SDTypeProfile<0, 2,
31                                          [SDTCisInt<0>,
32                                           SDTCisSameAs<0, 1>]>;
33
34 def SDT_MipsThreadPointer : SDTypeProfile<1, 0, [SDTCisPtrTy<0>]>;
35
36 def SDT_MipsDynAlloc    : SDTypeProfile<1, 1, [SDTCisVT<0, iPTR>,
37                                                SDTCisSameAs<0, 1>]>;
38 def SDT_Sync             : SDTypeProfile<0, 1, [SDTCisVT<0, i32>]>;
39
40 def SDT_Ext : SDTypeProfile<1, 3, [SDTCisInt<0>, SDTCisSameAs<0, 1>,
41                                    SDTCisVT<2, i32>, SDTCisSameAs<2, 3>]>;
42 def SDT_Ins : SDTypeProfile<1, 4, [SDTCisInt<0>, SDTCisSameAs<0, 1>,
43                                    SDTCisVT<2, i32>, SDTCisSameAs<2, 3>,
44                                    SDTCisSameAs<0, 4>]>;
45
46 def SDTMipsLoadLR  : SDTypeProfile<1, 2,
47                                    [SDTCisInt<0>, SDTCisPtrTy<1>,
48                                     SDTCisSameAs<0, 2>]>;
49
50 // Call
51 def MipsJmpLink : SDNode<"MipsISD::JmpLink",SDT_MipsJmpLink,
52                          [SDNPHasChain, SDNPOutGlue, SDNPOptInGlue,
53                           SDNPVariadic]>;
54
55 // Tail call
56 def MipsTailCall : SDNode<"MipsISD::TailCall", SDT_MipsJmpLink,
57                           [SDNPHasChain, SDNPOptInGlue, SDNPVariadic]>;
58
59 // Hi and Lo nodes are used to handle global addresses. Used on
60 // MipsISelLowering to lower stuff like GlobalAddress, ExternalSymbol
61 // static model. (nothing to do with Mips Registers Hi and Lo)
62 def MipsHi    : SDNode<"MipsISD::Hi", SDTIntUnaryOp>;
63 def MipsLo    : SDNode<"MipsISD::Lo", SDTIntUnaryOp>;
64 def MipsGPRel : SDNode<"MipsISD::GPRel", SDTIntUnaryOp>;
65
66 // TlsGd node is used to handle General Dynamic TLS
67 def MipsTlsGd : SDNode<"MipsISD::TlsGd", SDTIntUnaryOp>;
68
69 // TprelHi and TprelLo nodes are used to handle Local Exec TLS
70 def MipsTprelHi    : SDNode<"MipsISD::TprelHi", SDTIntUnaryOp>;
71 def MipsTprelLo    : SDNode<"MipsISD::TprelLo", SDTIntUnaryOp>;
72
73 // Thread pointer
74 def MipsThreadPointer: SDNode<"MipsISD::ThreadPointer", SDT_MipsThreadPointer>;
75
76 // Return
77 def MipsRet : SDNode<"MipsISD::Ret", SDTNone, [SDNPHasChain, SDNPOptInGlue]>;
78
79 // These are target-independent nodes, but have target-specific formats.
80 def callseq_start : SDNode<"ISD::CALLSEQ_START", SDT_MipsCallSeqStart,
81                            [SDNPHasChain, SDNPSideEffect, SDNPOutGlue]>;
82 def callseq_end   : SDNode<"ISD::CALLSEQ_END", SDT_MipsCallSeqEnd,
83                            [SDNPHasChain, SDNPSideEffect,
84                             SDNPOptInGlue, SDNPOutGlue]>;
85
86 // MAdd*/MSub* nodes
87 def MipsMAdd      : SDNode<"MipsISD::MAdd", SDT_MipsMAddMSub,
88                            [SDNPOptInGlue, SDNPOutGlue]>;
89 def MipsMAddu     : SDNode<"MipsISD::MAddu", SDT_MipsMAddMSub,
90                            [SDNPOptInGlue, SDNPOutGlue]>;
91 def MipsMSub      : SDNode<"MipsISD::MSub", SDT_MipsMAddMSub,
92                            [SDNPOptInGlue, SDNPOutGlue]>;
93 def MipsMSubu     : SDNode<"MipsISD::MSubu", SDT_MipsMAddMSub,
94                            [SDNPOptInGlue, SDNPOutGlue]>;
95
96 // DivRem(u) nodes
97 def MipsDivRem    : SDNode<"MipsISD::DivRem", SDT_MipsDivRem,
98                            [SDNPOutGlue]>;
99 def MipsDivRemU   : SDNode<"MipsISD::DivRemU", SDT_MipsDivRem,
100                            [SDNPOutGlue]>;
101
102 // Target constant nodes that are not part of any isel patterns and remain
103 // unchanged can cause instructions with illegal operands to be emitted.
104 // Wrapper node patterns give the instruction selector a chance to replace
105 // target constant nodes that would otherwise remain unchanged with ADDiu
106 // nodes. Without these wrapper node patterns, the following conditional move
107 // instrucion is emitted when function cmov2 in test/CodeGen/Mips/cmov.ll is
108 // compiled:
109 //  movn  %got(d)($gp), %got(c)($gp), $4
110 // This instruction is illegal since movn can take only register operands.
111
112 def MipsWrapper    : SDNode<"MipsISD::Wrapper", SDTIntBinOp>;
113
114 // Pointer to dynamically allocated stack area.
115 def MipsDynAlloc  : SDNode<"MipsISD::DynAlloc", SDT_MipsDynAlloc,
116                            [SDNPHasChain, SDNPInGlue]>;
117
118 def MipsSync : SDNode<"MipsISD::Sync", SDT_Sync, [SDNPHasChain,SDNPSideEffect]>;
119
120 def MipsExt :  SDNode<"MipsISD::Ext", SDT_Ext>;
121 def MipsIns :  SDNode<"MipsISD::Ins", SDT_Ins>;
122
123 def MipsLWL : SDNode<"MipsISD::LWL", SDTMipsLoadLR,
124                      [SDNPHasChain, SDNPMayLoad, SDNPMemOperand]>;
125 def MipsLWR : SDNode<"MipsISD::LWR", SDTMipsLoadLR,
126                      [SDNPHasChain, SDNPMayLoad, SDNPMemOperand]>;
127 def MipsSWL : SDNode<"MipsISD::SWL", SDTStore,
128                      [SDNPHasChain, SDNPMayStore, SDNPMemOperand]>;
129 def MipsSWR : SDNode<"MipsISD::SWR", SDTStore,
130                      [SDNPHasChain, SDNPMayStore, SDNPMemOperand]>;
131 def MipsLDL : SDNode<"MipsISD::LDL", SDTMipsLoadLR,
132                      [SDNPHasChain, SDNPMayLoad, SDNPMemOperand]>;
133 def MipsLDR : SDNode<"MipsISD::LDR", SDTMipsLoadLR,
134                      [SDNPHasChain, SDNPMayLoad, SDNPMemOperand]>;
135 def MipsSDL : SDNode<"MipsISD::SDL", SDTStore,
136                      [SDNPHasChain, SDNPMayStore, SDNPMemOperand]>;
137 def MipsSDR : SDNode<"MipsISD::SDR", SDTStore,
138                      [SDNPHasChain, SDNPMayStore, SDNPMemOperand]>;
139
140 //===----------------------------------------------------------------------===//
141 // Mips Instruction Predicate Definitions.
142 //===----------------------------------------------------------------------===//
143 def HasSEInReg  :     Predicate<"Subtarget.hasSEInReg()">,
144                       AssemblerPredicate<"FeatureSEInReg">;
145 def HasBitCount :     Predicate<"Subtarget.hasBitCount()">,
146                       AssemblerPredicate<"FeatureBitCount">;
147 def HasSwap     :     Predicate<"Subtarget.hasSwap()">,
148                       AssemblerPredicate<"FeatureSwap">;
149 def HasCondMov  :     Predicate<"Subtarget.hasCondMov()">,
150                       AssemblerPredicate<"FeatureCondMov">;
151 def HasMips32    :    Predicate<"Subtarget.hasMips32()">,
152                       AssemblerPredicate<"FeatureMips32">;
153 def HasMips32r2  :    Predicate<"Subtarget.hasMips32r2()">,
154                       AssemblerPredicate<"FeatureMips32r2">;
155 def HasMips64    :    Predicate<"Subtarget.hasMips64()">,
156                       AssemblerPredicate<"FeatureMips64">;
157 def HasMips32r2Or64 : Predicate<"Subtarget.hasMips32r2Or64()">,
158                       AssemblerPredicate<"FeatureMips32r2,FeatureMips64">;
159 def NotMips64    :    Predicate<"!Subtarget.hasMips64()">,
160                       AssemblerPredicate<"!FeatureMips64">;
161 def HasMips64r2  :    Predicate<"Subtarget.hasMips64r2()">,
162                       AssemblerPredicate<"FeatureMips64r2">;
163 def IsN64       :     Predicate<"Subtarget.isABI_N64()">,
164                       AssemblerPredicate<"FeatureN64">;
165 def NotN64      :     Predicate<"!Subtarget.isABI_N64()">,
166                       AssemblerPredicate<"!FeatureN64">;
167 def InMips16Mode :    Predicate<"Subtarget.inMips16Mode()">,
168                       AssemblerPredicate<"FeatureMips16">;
169 def RelocStatic :     Predicate<"TM.getRelocationModel() == Reloc::Static">,
170                       AssemblerPredicate<"FeatureMips32">;
171 def RelocPIC    :     Predicate<"TM.getRelocationModel() == Reloc::PIC_">,
172                       AssemblerPredicate<"FeatureMips32">;
173 def NoNaNsFPMath :    Predicate<"TM.Options.NoNaNsFPMath">,
174                       AssemblerPredicate<"FeatureMips32">;
175 def HasStandardEncoding : Predicate<"Subtarget.hasStandardEncoding()">,
176                           AssemblerPredicate<"!FeatureMips16">;
177
178 class MipsPat<dag pattern, dag result> : Pat<pattern, result> {
179   let Predicates = [HasStandardEncoding];
180 }
181
182 class IsBranch {
183   bit isBranch = 1;
184 }
185
186 class IsReturn {
187   bit isReturn = 1;
188 }
189
190 class IsCall {
191   bit isCall = 1;
192 }
193
194 class IsTailCall {
195   bit isCall = 1;
196   bit isTerminator = 1;
197   bit isReturn = 1;
198   bit isBarrier = 1;
199   bit hasExtraSrcRegAllocReq = 1;
200   bit isCodeGenOnly = 1;
201 }
202
203 //===----------------------------------------------------------------------===//
204 // Instruction format superclass
205 //===----------------------------------------------------------------------===//
206
207 include "MipsInstrFormats.td"
208
209 //===----------------------------------------------------------------------===//
210 // Mips Operand, Complex Patterns and Transformations Definitions.
211 //===----------------------------------------------------------------------===//
212
213 // Instruction operand types
214 def jmptarget   : Operand<OtherVT> {
215   let EncoderMethod = "getJumpTargetOpValue";
216 }
217 def brtarget    : Operand<OtherVT> {
218   let EncoderMethod = "getBranchTargetOpValue";
219   let OperandType = "OPERAND_PCREL";
220   let DecoderMethod = "DecodeBranchTarget";
221 }
222 def calltarget  : Operand<iPTR> {
223   let EncoderMethod = "getJumpTargetOpValue";
224 }
225 def calltarget64: Operand<i64>;
226 def simm16      : Operand<i32> {
227   let DecoderMethod= "DecodeSimm16";
228 }
229 def simm16_64   : Operand<i64>;
230 def shamt       : Operand<i32>;
231
232 // Unsigned Operand
233 def uimm16      : Operand<i32> {
234   let PrintMethod = "printUnsignedImm";
235 }
236
237 def MipsMemAsmOperand : AsmOperandClass {
238   let Name = "Mem";
239   let ParserMethod = "parseMemOperand";
240 }
241
242 // Address operand
243 def mem : Operand<i32> {
244   let PrintMethod = "printMemOperand";
245   let MIOperandInfo = (ops CPURegs, simm16);
246   let EncoderMethod = "getMemEncoding";
247   let ParserMatchClass = MipsMemAsmOperand;
248 }
249
250 def mem64 : Operand<i64> {
251   let PrintMethod = "printMemOperand";
252   let MIOperandInfo = (ops CPU64Regs, simm16_64);
253   let EncoderMethod = "getMemEncoding";
254   let ParserMatchClass = MipsMemAsmOperand;
255 }
256
257 def mem_ea : Operand<i32> {
258   let PrintMethod = "printMemOperandEA";
259   let MIOperandInfo = (ops CPURegs, simm16);
260   let EncoderMethod = "getMemEncoding";
261 }
262
263 def mem_ea_64 : Operand<i64> {
264   let PrintMethod = "printMemOperandEA";
265   let MIOperandInfo = (ops CPU64Regs, simm16_64);
266   let EncoderMethod = "getMemEncoding";
267 }
268
269 // size operand of ext instruction
270 def size_ext : Operand<i32> {
271   let EncoderMethod = "getSizeExtEncoding";
272   let DecoderMethod = "DecodeExtSize";
273 }
274
275 // size operand of ins instruction
276 def size_ins : Operand<i32> {
277   let EncoderMethod = "getSizeInsEncoding";
278   let DecoderMethod = "DecodeInsSize";
279 }
280
281 // Transformation Function - get the lower 16 bits.
282 def LO16 : SDNodeXForm<imm, [{
283   return getImm(N, N->getZExtValue() & 0xFFFF);
284 }]>;
285
286 // Transformation Function - get the higher 16 bits.
287 def HI16 : SDNodeXForm<imm, [{
288   return getImm(N, (N->getZExtValue() >> 16) & 0xFFFF);
289 }]>;
290
291 // Node immediate fits as 16-bit sign extended on target immediate.
292 // e.g. addi, andi
293 def immSExt16  : PatLeaf<(imm), [{ return isInt<16>(N->getSExtValue()); }]>;
294
295 // Node immediate fits as 16-bit zero extended on target immediate.
296 // The LO16 param means that only the lower 16 bits of the node
297 // immediate are caught.
298 // e.g. addiu, sltiu
299 def immZExt16  : PatLeaf<(imm), [{
300   if (N->getValueType(0) == MVT::i32)
301     return (uint32_t)N->getZExtValue() == (unsigned short)N->getZExtValue();
302   else
303     return (uint64_t)N->getZExtValue() == (unsigned short)N->getZExtValue();
304 }], LO16>;
305
306 // Immediate can be loaded with LUi (32-bit int with lower 16-bit cleared).
307 def immLow16Zero : PatLeaf<(imm), [{
308   int64_t Val = N->getSExtValue();
309   return isInt<32>(Val) && !(Val & 0xffff);
310 }]>;
311
312 // shamt field must fit in 5 bits.
313 def immZExt5 : ImmLeaf<i32, [{return Imm == (Imm & 0x1f);}]>;
314
315 // Mips Address Mode! SDNode frameindex could possibily be a match
316 // since load and store instructions from stack used it.
317 def addr :
318   ComplexPattern<iPTR, 2, "SelectAddr", [frameindex], [SDNPWantParent]>;
319
320 //===----------------------------------------------------------------------===//
321 // Instructions specific format
322 //===----------------------------------------------------------------------===//
323
324 /// Move Control Registers From/To CPU Registers
325 def MFC0_3OP  : MFC3OP<0x10, 0, (outs CPURegs:$rt),
326                        (ins CPURegs:$rd, uimm16:$sel),"mfc0\t$rt, $rd, $sel">;
327 def : InstAlias<"mfc0 $rt, $rd", (MFC0_3OP CPURegs:$rt, CPURegs:$rd, 0)>;
328
329 def MTC0_3OP  : MFC3OP<0x10, 4, (outs CPURegs:$rd, uimm16:$sel),
330                        (ins CPURegs:$rt),"mtc0\t$rt, $rd, $sel">;
331 def : InstAlias<"mtc0 $rt, $rd", (MTC0_3OP CPURegs:$rd, 0, CPURegs:$rt)>;
332
333 def MFC2_3OP  : MFC3OP<0x12, 0, (outs CPURegs:$rt),
334                        (ins CPURegs:$rd, uimm16:$sel),"mfc2\t$rt, $rd, $sel">;
335 def : InstAlias<"mfc2 $rt, $rd", (MFC2_3OP CPURegs:$rt, CPURegs:$rd, 0)>;
336
337 def MTC2_3OP  : MFC3OP<0x12, 4, (outs CPURegs:$rd, uimm16:$sel),
338                        (ins CPURegs:$rt),"mtc2\t$rt, $rd, $sel">;
339 def : InstAlias<"mtc2 $rt, $rd", (MTC2_3OP CPURegs:$rd, 0, CPURegs:$rt)>;
340
341 // Arithmetic and logical instructions with 3 register operands.
342 class ArithLogicR<bits<6> op, bits<6> func, string instr_asm, SDNode OpNode,
343                   InstrItinClass itin, RegisterClass RC, bit isComm = 0>:
344   FR<op, func, (outs RC:$rd), (ins RC:$rs, RC:$rt),
345      !strconcat(instr_asm, "\t$rd, $rs, $rt"),
346      [(set RC:$rd, (OpNode RC:$rs, RC:$rt))], itin> {
347   let shamt = 0;
348   let isCommutable = isComm;
349   let isReMaterializable = 1;
350 }
351
352 class ArithOverflowR<bits<6> op, bits<6> func, string instr_asm,
353                     InstrItinClass itin, RegisterClass RC, bit isComm = 0>:
354   FR<op, func, (outs RC:$rd), (ins RC:$rs, RC:$rt),
355      !strconcat(instr_asm, "\t$rd, $rs, $rt"), [], itin> {
356   let shamt = 0;
357   let isCommutable = isComm;
358 }
359
360 // Arithmetic and logical instructions with 2 register operands.
361 class ArithLogicI<bits<6> op, string instr_asm, SDNode OpNode,
362                   Operand Od, PatLeaf imm_type, RegisterClass RC> :
363   FI<op, (outs RC:$rt), (ins RC:$rs, Od:$imm16),
364      !strconcat(instr_asm, "\t$rt, $rs, $imm16"),
365      [(set RC:$rt, (OpNode RC:$rs, imm_type:$imm16))], IIAlu> {
366   let isReMaterializable = 1;
367 }
368
369 class ArithOverflowI<bits<6> op, string instr_asm, SDNode OpNode,
370                      Operand Od, PatLeaf imm_type, RegisterClass RC> :
371   FI<op, (outs RC:$rt), (ins RC:$rs, Od:$imm16),
372      !strconcat(instr_asm, "\t$rt, $rs, $imm16"), [], IIAlu>;
373
374 // Arithmetic Multiply ADD/SUB
375 let rd = 0, shamt = 0, Defs = [HI, LO], Uses = [HI, LO] in
376 class MArithR<bits<6> func, string instr_asm, SDNode op, bit isComm = 0> :
377   FR<0x1c, func, (outs), (ins CPURegs:$rs, CPURegs:$rt),
378      !strconcat(instr_asm, "\t$rs, $rt"),
379      [(op CPURegs:$rs, CPURegs:$rt, LO, HI)], IIImul> {
380   let rd = 0;
381   let shamt = 0;
382   let isCommutable = isComm;
383 }
384
385 //  Logical
386 class LogicNOR<bits<6> op, bits<6> func, string instr_asm, RegisterClass RC>:
387   FR<op, func, (outs RC:$rd), (ins RC:$rs, RC:$rt),
388      !strconcat(instr_asm, "\t$rd, $rs, $rt"),
389      [(set RC:$rd, (not (or RC:$rs, RC:$rt)))], IIAlu> {
390   let shamt = 0;
391   let isCommutable = 1;
392 }
393
394 // Shifts
395 class shift_rotate_imm<bits<6> func, bits<5> isRotate, string instr_asm,
396                        SDNode OpNode, PatFrag PF, Operand ImmOpnd,
397                        RegisterClass RC>:
398   FR<0x00, func, (outs RC:$rd), (ins RC:$rt, ImmOpnd:$shamt),
399      !strconcat(instr_asm, "\t$rd, $rt, $shamt"),
400      [(set RC:$rd, (OpNode RC:$rt, PF:$shamt))], IIAlu> {
401   let rs = isRotate;
402 }
403
404 // 32-bit shift instructions.
405 class shift_rotate_imm32<bits<6> func, bits<5> isRotate, string instr_asm,
406                          SDNode OpNode>:
407   shift_rotate_imm<func, isRotate, instr_asm, OpNode, immZExt5, shamt, CPURegs>;
408
409 class shift_rotate_reg<bits<6> func, bits<5> isRotate, string instr_asm,
410                        SDNode OpNode, RegisterClass RC>:
411   FR<0x00, func, (outs RC:$rd), (ins CPURegs:$rs, RC:$rt),
412      !strconcat(instr_asm, "\t$rd, $rt, $rs"),
413      [(set RC:$rd, (OpNode RC:$rt, CPURegs:$rs))], IIAlu> {
414   let shamt = isRotate;
415 }
416
417 // Load Upper Imediate
418 class LoadUpper<bits<6> op, string instr_asm, RegisterClass RC, Operand Imm>:
419   FI<op, (outs RC:$rt), (ins Imm:$imm16),
420      !strconcat(instr_asm, "\t$rt, $imm16"), [], IIAlu> {
421   let rs = 0;
422   let neverHasSideEffects = 1;
423   let isReMaterializable = 1;
424 }
425
426 class FMem<bits<6> op, dag outs, dag ins, string asmstr, list<dag> pattern,
427           InstrItinClass itin>: FFI<op, outs, ins, asmstr, pattern> {
428   bits<21> addr;
429   let Inst{25-21} = addr{20-16};
430   let Inst{15-0}  = addr{15-0};
431   let DecoderMethod = "DecodeMem";
432 }
433
434 // Memory Load/Store
435 let canFoldAsLoad = 1 in
436 class LoadM<bits<6> op, string instr_asm, PatFrag OpNode, RegisterClass RC,
437             Operand MemOpnd, bit Pseudo>:
438   FMem<op, (outs RC:$rt), (ins MemOpnd:$addr),
439      !strconcat(instr_asm, "\t$rt, $addr"),
440      [(set RC:$rt, (OpNode addr:$addr))], IILoad> {
441   let isPseudo = Pseudo;
442 }
443
444 class StoreM<bits<6> op, string instr_asm, PatFrag OpNode, RegisterClass RC,
445              Operand MemOpnd, bit Pseudo>:
446   FMem<op, (outs), (ins RC:$rt, MemOpnd:$addr),
447      !strconcat(instr_asm, "\t$rt, $addr"),
448      [(OpNode RC:$rt, addr:$addr)], IIStore> {
449   let isPseudo = Pseudo;
450 }
451
452 // 32-bit load.
453 multiclass LoadM32<bits<6> op, string instr_asm, PatFrag OpNode,
454                    bit Pseudo = 0> {
455   def #NAME# : LoadM<op, instr_asm, OpNode, CPURegs, mem, Pseudo>,
456                Requires<[NotN64, HasStandardEncoding]>;
457   def _P8    : LoadM<op, instr_asm, OpNode, CPURegs, mem64, Pseudo>,
458                Requires<[IsN64, HasStandardEncoding]> {
459     let DecoderNamespace = "Mips64";
460     let isCodeGenOnly = 1;
461   }
462 }
463
464 // 64-bit load.
465 multiclass LoadM64<bits<6> op, string instr_asm, PatFrag OpNode,
466                    bit Pseudo = 0> {
467   def #NAME# : LoadM<op, instr_asm, OpNode, CPU64Regs, mem, Pseudo>,
468                Requires<[NotN64, HasStandardEncoding]>;
469   def _P8    : LoadM<op, instr_asm, OpNode, CPU64Regs, mem64, Pseudo>,
470                Requires<[IsN64, HasStandardEncoding]> {
471     let DecoderNamespace = "Mips64";
472     let isCodeGenOnly = 1;
473   }
474 }
475
476 // 32-bit store.
477 multiclass StoreM32<bits<6> op, string instr_asm, PatFrag OpNode,
478                     bit Pseudo = 0> {
479   def #NAME# : StoreM<op, instr_asm, OpNode, CPURegs, mem, Pseudo>,
480                Requires<[NotN64, HasStandardEncoding]>;
481   def _P8    : StoreM<op, instr_asm, OpNode, CPURegs, mem64, Pseudo>,
482                Requires<[IsN64, HasStandardEncoding]> {
483     let DecoderNamespace = "Mips64";
484     let isCodeGenOnly = 1;
485   }
486 }
487
488 // 64-bit store.
489 multiclass StoreM64<bits<6> op, string instr_asm, PatFrag OpNode,
490                     bit Pseudo = 0> {
491   def #NAME# : StoreM<op, instr_asm, OpNode, CPU64Regs, mem, Pseudo>,
492                Requires<[NotN64, HasStandardEncoding]>;
493   def _P8    : StoreM<op, instr_asm, OpNode, CPU64Regs, mem64, Pseudo>,
494                Requires<[IsN64, HasStandardEncoding]> {
495     let DecoderNamespace = "Mips64";
496     let isCodeGenOnly = 1;
497   }
498 }
499
500 // Load/Store Left/Right
501 let canFoldAsLoad = 1 in
502 class LoadLeftRight<bits<6> op, string instr_asm, SDNode OpNode,
503                     RegisterClass RC, Operand MemOpnd> :
504   FMem<op, (outs RC:$rt), (ins MemOpnd:$addr, RC:$src),
505        !strconcat(instr_asm, "\t$rt, $addr"),
506        [(set RC:$rt, (OpNode addr:$addr, RC:$src))], IILoad> {
507   string Constraints = "$src = $rt";
508 }
509
510 class StoreLeftRight<bits<6> op, string instr_asm, SDNode OpNode,
511                      RegisterClass RC, Operand MemOpnd>:
512   FMem<op, (outs), (ins RC:$rt, MemOpnd:$addr),
513        !strconcat(instr_asm, "\t$rt, $addr"), [(OpNode RC:$rt, addr:$addr)],
514        IIStore>;
515
516 // 32-bit load left/right.
517 multiclass LoadLeftRightM32<bits<6> op, string instr_asm, SDNode OpNode> {
518   def #NAME# : LoadLeftRight<op, instr_asm, OpNode, CPURegs, mem>,
519                Requires<[NotN64, HasStandardEncoding]>;
520   def _P8    : LoadLeftRight<op, instr_asm, OpNode, CPURegs, mem64>,
521                Requires<[IsN64, HasStandardEncoding]> {
522     let DecoderNamespace = "Mips64";
523     let isCodeGenOnly = 1;
524   }
525 }
526
527 // 64-bit load left/right.
528 multiclass LoadLeftRightM64<bits<6> op, string instr_asm, SDNode OpNode> {
529   def #NAME# : LoadLeftRight<op, instr_asm, OpNode, CPU64Regs, mem>,
530                Requires<[NotN64, HasStandardEncoding]>;
531   def _P8    : LoadLeftRight<op, instr_asm, OpNode, CPU64Regs, mem64>,
532                Requires<[IsN64, HasStandardEncoding]> {
533     let DecoderNamespace = "Mips64";
534     let isCodeGenOnly = 1;
535   }
536 }
537
538 // 32-bit store left/right.
539 multiclass StoreLeftRightM32<bits<6> op, string instr_asm, SDNode OpNode> {
540   def #NAME# : StoreLeftRight<op, instr_asm, OpNode, CPURegs, mem>,
541                Requires<[NotN64, HasStandardEncoding]>;
542   def _P8    : StoreLeftRight<op, instr_asm, OpNode, CPURegs, mem64>,
543                Requires<[IsN64, HasStandardEncoding]> {
544     let DecoderNamespace = "Mips64";
545     let isCodeGenOnly = 1;
546   }
547 }
548
549 // 64-bit store left/right.
550 multiclass StoreLeftRightM64<bits<6> op, string instr_asm, SDNode OpNode> {
551   def #NAME# : StoreLeftRight<op, instr_asm, OpNode, CPU64Regs, mem>,
552                Requires<[NotN64, HasStandardEncoding]>;
553   def _P8    : StoreLeftRight<op, instr_asm, OpNode, CPU64Regs, mem64>,
554                Requires<[IsN64, HasStandardEncoding]> {
555     let DecoderNamespace = "Mips64";
556     let isCodeGenOnly = 1;
557   }
558 }
559
560 // Conditional Branch
561 class CBranch<bits<6> op, string instr_asm, PatFrag cond_op, RegisterClass RC>:
562   BranchBase<op, (outs), (ins RC:$rs, RC:$rt, brtarget:$imm16),
563              !strconcat(instr_asm, "\t$rs, $rt, $imm16"),
564              [(brcond (i32 (cond_op RC:$rs, RC:$rt)), bb:$imm16)], IIBranch> {
565   let isBranch = 1;
566   let isTerminator = 1;
567   let hasDelaySlot = 1;
568   let Defs = [AT];
569 }
570
571 class CBranchZero<bits<6> op, bits<5> _rt, string instr_asm, PatFrag cond_op,
572                   RegisterClass RC>:
573   BranchBase<op, (outs), (ins RC:$rs, brtarget:$imm16),
574              !strconcat(instr_asm, "\t$rs, $imm16"),
575              [(brcond (i32 (cond_op RC:$rs, 0)), bb:$imm16)], IIBranch> {
576   let rt = _rt;
577   let isBranch = 1;
578   let isTerminator = 1;
579   let hasDelaySlot = 1;
580   let Defs = [AT];
581 }
582
583 // SetCC
584 class SetCC_R<bits<6> op, bits<6> func, string instr_asm, PatFrag cond_op,
585               RegisterClass RC>:
586   FR<op, func, (outs CPURegs:$rd), (ins RC:$rs, RC:$rt),
587      !strconcat(instr_asm, "\t$rd, $rs, $rt"),
588      [(set CPURegs:$rd, (cond_op RC:$rs, RC:$rt))],
589      IIAlu> {
590   let shamt = 0;
591 }
592
593 class SetCC_I<bits<6> op, string instr_asm, PatFrag cond_op, Operand Od,
594               PatLeaf imm_type, RegisterClass RC>:
595   FI<op, (outs CPURegs:$rt), (ins RC:$rs, Od:$imm16),
596      !strconcat(instr_asm, "\t$rt, $rs, $imm16"),
597      [(set CPURegs:$rt, (cond_op RC:$rs, imm_type:$imm16))],
598      IIAlu>;
599
600 // Jump
601 class JumpFJ<bits<6> op, string instr_asm, SDPatternOperator operator>:
602   FJ<op, (outs), (ins jmptarget:$target), !strconcat(instr_asm, "\t$target"),
603      [(operator bb:$target)], IIBranch> {
604   let isTerminator=1;
605   let isBarrier=1;
606   let hasDelaySlot = 1;
607   let DecoderMethod = "DecodeJumpTarget";
608   let Defs = [AT];
609 }
610
611 // Unconditional branch
612 class UncondBranch<bits<6> op, string instr_asm>:
613   BranchBase<op, (outs), (ins brtarget:$imm16),
614              !strconcat(instr_asm, "\t$imm16"), [(br bb:$imm16)], IIBranch> {
615   let rs = 0;
616   let rt = 0;
617   let isBranch = 1;
618   let isTerminator = 1;
619   let isBarrier = 1;
620   let hasDelaySlot = 1;
621   let Predicates = [RelocPIC, HasStandardEncoding];
622   let Defs = [AT];
623 }
624
625 // Base class for indirect branch and return instruction classes.
626 let isTerminator=1, isBarrier=1, hasDelaySlot = 1 in
627 class JumpFR<RegisterClass RC, SDPatternOperator operator = null_frag>:
628   FR<0, 0x8, (outs), (ins RC:$rs), "jr\t$rs", [(operator RC:$rs)], IIBranch> {
629   let rt = 0;
630   let rd = 0;
631   let shamt = 0;
632 }
633
634 // Indirect branch
635 class IndirectBranch<RegisterClass RC>: JumpFR<RC, brind> {
636   let isBranch = 1;
637   let isIndirectBranch = 1;
638 }
639
640 // Return instruction
641 class RetBase<RegisterClass RC>: JumpFR<RC> {
642   let isReturn = 1;
643   let isCodeGenOnly = 1;
644   let hasCtrlDep = 1;
645   let hasExtraSrcRegAllocReq = 1;
646 }
647
648 // Jump and Link (Call)
649 let isCall=1, hasDelaySlot=1, Defs = [RA] in {
650   class JumpLink<bits<6> op, string instr_asm>:
651     FJ<op, (outs), (ins calltarget:$target),
652        !strconcat(instr_asm, "\t$target"), [(MipsJmpLink imm:$target)],
653        IIBranch> {
654        let DecoderMethod = "DecodeJumpTarget";
655        }
656
657   class JumpLinkReg<bits<6> op, bits<6> func, string instr_asm,
658                     RegisterClass RC>:
659     FR<op, func, (outs), (ins RC:$rs),
660        !strconcat(instr_asm, "\t$rs"), [(MipsJmpLink RC:$rs)], IIBranch> {
661     let rt = 0;
662     let rd = 31;
663     let shamt = 0;
664   }
665
666   class BranchLink<string instr_asm, bits<5> _rt, RegisterClass RC>:
667     FI<0x1, (outs), (ins RC:$rs, brtarget:$imm16),
668        !strconcat(instr_asm, "\t$rs, $imm16"), [], IIBranch> {
669     let rt = _rt;
670   }
671 }
672
673 // Mul, Div
674 class Mult<bits<6> func, string instr_asm, InstrItinClass itin,
675            RegisterClass RC, list<Register> DefRegs>:
676   FR<0x00, func, (outs), (ins RC:$rs, RC:$rt),
677      !strconcat(instr_asm, "\t$rs, $rt"), [], itin> {
678   let rd = 0;
679   let shamt = 0;
680   let isCommutable = 1;
681   let Defs = DefRegs;
682   let neverHasSideEffects = 1;
683 }
684
685 class Mult32<bits<6> func, string instr_asm, InstrItinClass itin>:
686   Mult<func, instr_asm, itin, CPURegs, [HI, LO]>;
687
688 class Div<SDNode op, bits<6> func, string instr_asm, InstrItinClass itin,
689           RegisterClass RC, list<Register> DefRegs>:
690   FR<0x00, func, (outs), (ins RC:$rs, RC:$rt),
691      !strconcat(instr_asm, "\t$$zero, $rs, $rt"),
692      [(op RC:$rs, RC:$rt)], itin> {
693   let rd = 0;
694   let shamt = 0;
695   let Defs = DefRegs;
696 }
697
698 class Div32<SDNode op, bits<6> func, string instr_asm, InstrItinClass itin>:
699   Div<op, func, instr_asm, itin, CPURegs, [HI, LO]>;
700
701 // Move from Hi/Lo
702 class MoveFromLOHI<bits<6> func, string instr_asm, RegisterClass RC,
703                    list<Register> UseRegs>:
704   FR<0x00, func, (outs RC:$rd), (ins),
705      !strconcat(instr_asm, "\t$rd"), [], IIHiLo> {
706   let rs = 0;
707   let rt = 0;
708   let shamt = 0;
709   let Uses = UseRegs;
710   let neverHasSideEffects = 1;
711 }
712
713 class MoveToLOHI<bits<6> func, string instr_asm, RegisterClass RC,
714                  list<Register> DefRegs>:
715   FR<0x00, func, (outs), (ins RC:$rs),
716      !strconcat(instr_asm, "\t$rs"), [], IIHiLo> {
717   let rt = 0;
718   let rd = 0;
719   let shamt = 0;
720   let Defs = DefRegs;
721   let neverHasSideEffects = 1;
722 }
723
724 class EffectiveAddress<bits<6> opc, string instr_asm, RegisterClass RC, Operand Mem> :
725   FMem<opc, (outs RC:$rt), (ins Mem:$addr),
726      instr_asm, [(set RC:$rt, addr:$addr)], IIAlu> {
727  let isCodeGenOnly = 1;
728 }
729
730 // Count Leading Ones/Zeros in Word
731 class CountLeading0<bits<6> func, string instr_asm, RegisterClass RC>:
732   FR<0x1c, func, (outs RC:$rd), (ins RC:$rs),
733      !strconcat(instr_asm, "\t$rd, $rs"),
734      [(set RC:$rd, (ctlz RC:$rs))], IIAlu>,
735      Requires<[HasBitCount, HasStandardEncoding]> {
736   let shamt = 0;
737   let rt = rd;
738 }
739
740 class CountLeading1<bits<6> func, string instr_asm, RegisterClass RC>:
741   FR<0x1c, func, (outs RC:$rd), (ins RC:$rs),
742      !strconcat(instr_asm, "\t$rd, $rs"),
743      [(set RC:$rd, (ctlz (not RC:$rs)))], IIAlu>,
744      Requires<[HasBitCount, HasStandardEncoding]> {
745   let shamt = 0;
746   let rt = rd;
747 }
748
749 // Sign Extend in Register.
750 class SignExtInReg<bits<5> sa, string instr_asm, ValueType vt,
751                    RegisterClass RC>:
752   FR<0x1f, 0x20, (outs RC:$rd), (ins RC:$rt),
753      !strconcat(instr_asm, "\t$rd, $rt"),
754      [(set RC:$rd, (sext_inreg RC:$rt, vt))], NoItinerary> {
755   let rs = 0;
756   let shamt = sa;
757   let Predicates = [HasSEInReg, HasStandardEncoding];
758 }
759
760 // Subword Swap
761 class SubwordSwap<bits<6> func, bits<5> sa, string instr_asm, RegisterClass RC>:
762   FR<0x1f, func, (outs RC:$rd), (ins RC:$rt),
763      !strconcat(instr_asm, "\t$rd, $rt"), [], NoItinerary> {
764   let rs = 0;
765   let shamt = sa;
766   let Predicates = [HasSwap, HasStandardEncoding];
767   let neverHasSideEffects = 1;
768 }
769
770 // Read Hardware
771 class ReadHardware<RegisterClass CPURegClass, RegisterClass HWRegClass>
772   : FR<0x1f, 0x3b, (outs CPURegClass:$rt), (ins HWRegClass:$rd),
773        "rdhwr\t$rt, $rd", [], IIAlu> {
774   let rs = 0;
775   let shamt = 0;
776 }
777
778 // Ext and Ins
779 class ExtBase<bits<6> _funct, string instr_asm, RegisterClass RC>:
780   FR<0x1f, _funct, (outs RC:$rt), (ins RC:$rs, uimm16:$pos, size_ext:$sz),
781      !strconcat(instr_asm, " $rt, $rs, $pos, $sz"),
782      [(set RC:$rt, (MipsExt RC:$rs, imm:$pos, imm:$sz))], NoItinerary> {
783   bits<5> pos;
784   bits<5> sz;
785   let rd = sz;
786   let shamt = pos;
787   let Predicates = [HasMips32r2, HasStandardEncoding];
788 }
789
790 class InsBase<bits<6> _funct, string instr_asm, RegisterClass RC>:
791   FR<0x1f, _funct, (outs RC:$rt),
792      (ins RC:$rs, uimm16:$pos, size_ins:$sz, RC:$src),
793      !strconcat(instr_asm, " $rt, $rs, $pos, $sz"),
794      [(set RC:$rt, (MipsIns RC:$rs, imm:$pos, imm:$sz, RC:$src))],
795      NoItinerary> {
796   bits<5> pos;
797   bits<5> sz;
798   let rd = sz;
799   let shamt = pos;
800   let Predicates = [HasMips32r2, HasStandardEncoding];
801   let Constraints = "$src = $rt";
802 }
803
804 // Atomic instructions with 2 source operands (ATOMIC_SWAP & ATOMIC_LOAD_*).
805 class Atomic2Ops<PatFrag Op, string Opstr, RegisterClass DRC,
806                  RegisterClass PRC> :
807   PseudoSE<(outs DRC:$dst), (ins PRC:$ptr, DRC:$incr),
808            !strconcat("atomic_", Opstr, "\t$dst, $ptr, $incr"),
809            [(set DRC:$dst, (Op PRC:$ptr, DRC:$incr))]>;
810
811 multiclass Atomic2Ops32<PatFrag Op, string Opstr> {
812   def #NAME# : Atomic2Ops<Op, Opstr, CPURegs, CPURegs>,
813                           Requires<[NotN64, HasStandardEncoding]>;
814   def _P8    : Atomic2Ops<Op, Opstr, CPURegs, CPU64Regs>,
815                           Requires<[IsN64, HasStandardEncoding]> {
816     let DecoderNamespace = "Mips64";
817   }
818 }
819
820 // Atomic Compare & Swap.
821 class AtomicCmpSwap<PatFrag Op, string Width, RegisterClass DRC,
822                     RegisterClass PRC> :
823   PseudoSE<(outs DRC:$dst), (ins PRC:$ptr, DRC:$cmp, DRC:$swap),
824            !strconcat("atomic_cmp_swap_", Width, "\t$dst, $ptr, $cmp, $swap"),
825            [(set DRC:$dst, (Op PRC:$ptr, DRC:$cmp, DRC:$swap))]>;
826
827 multiclass AtomicCmpSwap32<PatFrag Op, string Width>  {
828   def #NAME# : AtomicCmpSwap<Op, Width, CPURegs, CPURegs>,
829                              Requires<[NotN64, HasStandardEncoding]>;
830   def _P8    : AtomicCmpSwap<Op, Width, CPURegs, CPU64Regs>,
831                              Requires<[IsN64, HasStandardEncoding]> {
832     let DecoderNamespace = "Mips64";
833   }
834 }
835
836 class LLBase<bits<6> Opc, string opstring, RegisterClass RC, Operand Mem> :
837   FMem<Opc, (outs RC:$rt), (ins Mem:$addr),
838        !strconcat(opstring, "\t$rt, $addr"), [], IILoad> {
839   let mayLoad = 1;
840 }
841
842 class SCBase<bits<6> Opc, string opstring, RegisterClass RC, Operand Mem> :
843   FMem<Opc, (outs RC:$dst), (ins RC:$rt, Mem:$addr),
844        !strconcat(opstring, "\t$rt, $addr"), [], IIStore> {
845   let mayStore = 1;
846   let Constraints = "$rt = $dst";
847 }
848
849 //===----------------------------------------------------------------------===//
850 // Pseudo instructions
851 //===----------------------------------------------------------------------===//
852
853 // Return RA.
854 let isReturn=1, isTerminator=1, hasDelaySlot=1, isBarrier=1, hasCtrlDep=1 in
855 def RetRA : PseudoSE<(outs), (ins), "", [(MipsRet)]>;
856
857 let Defs = [SP], Uses = [SP], hasSideEffects = 1 in {
858 def ADJCALLSTACKDOWN : MipsPseudo<(outs), (ins i32imm:$amt),
859                                   "!ADJCALLSTACKDOWN $amt",
860                                   [(callseq_start timm:$amt)]>;
861 def ADJCALLSTACKUP   : MipsPseudo<(outs), (ins i32imm:$amt1, i32imm:$amt2),
862                                   "!ADJCALLSTACKUP $amt1",
863                                   [(callseq_end timm:$amt1, timm:$amt2)]>;
864 }
865
866 // When handling PIC code the assembler needs .cpload and .cprestore
867 // directives. If the real instructions corresponding these directives
868 // are used, we have the same behavior, but get also a bunch of warnings
869 // from the assembler.
870 let neverHasSideEffects = 1 in
871 def CPRESTORE : PseudoSE<(outs), (ins i32imm:$loc, CPURegs:$gp),
872                          ".cprestore\t$loc", []>;
873
874 let usesCustomInserter = 1 in {
875   defm ATOMIC_LOAD_ADD_I8   : Atomic2Ops32<atomic_load_add_8, "load_add_8">;
876   defm ATOMIC_LOAD_ADD_I16  : Atomic2Ops32<atomic_load_add_16, "load_add_16">;
877   defm ATOMIC_LOAD_ADD_I32  : Atomic2Ops32<atomic_load_add_32, "load_add_32">;
878   defm ATOMIC_LOAD_SUB_I8   : Atomic2Ops32<atomic_load_sub_8, "load_sub_8">;
879   defm ATOMIC_LOAD_SUB_I16  : Atomic2Ops32<atomic_load_sub_16, "load_sub_16">;
880   defm ATOMIC_LOAD_SUB_I32  : Atomic2Ops32<atomic_load_sub_32, "load_sub_32">;
881   defm ATOMIC_LOAD_AND_I8   : Atomic2Ops32<atomic_load_and_8, "load_and_8">;
882   defm ATOMIC_LOAD_AND_I16  : Atomic2Ops32<atomic_load_and_16, "load_and_16">;
883   defm ATOMIC_LOAD_AND_I32  : Atomic2Ops32<atomic_load_and_32, "load_and_32">;
884   defm ATOMIC_LOAD_OR_I8    : Atomic2Ops32<atomic_load_or_8, "load_or_8">;
885   defm ATOMIC_LOAD_OR_I16   : Atomic2Ops32<atomic_load_or_16, "load_or_16">;
886   defm ATOMIC_LOAD_OR_I32   : Atomic2Ops32<atomic_load_or_32, "load_or_32">;
887   defm ATOMIC_LOAD_XOR_I8   : Atomic2Ops32<atomic_load_xor_8, "load_xor_8">;
888   defm ATOMIC_LOAD_XOR_I16  : Atomic2Ops32<atomic_load_xor_16, "load_xor_16">;
889   defm ATOMIC_LOAD_XOR_I32  : Atomic2Ops32<atomic_load_xor_32, "load_xor_32">;
890   defm ATOMIC_LOAD_NAND_I8  : Atomic2Ops32<atomic_load_nand_8, "load_nand_8">;
891   defm ATOMIC_LOAD_NAND_I16 : Atomic2Ops32<atomic_load_nand_16, "load_nand_16">;
892   defm ATOMIC_LOAD_NAND_I32 : Atomic2Ops32<atomic_load_nand_32, "load_nand_32">;
893
894   defm ATOMIC_SWAP_I8       : Atomic2Ops32<atomic_swap_8, "swap_8">;
895   defm ATOMIC_SWAP_I16      : Atomic2Ops32<atomic_swap_16, "swap_16">;
896   defm ATOMIC_SWAP_I32      : Atomic2Ops32<atomic_swap_32, "swap_32">;
897
898   defm ATOMIC_CMP_SWAP_I8   : AtomicCmpSwap32<atomic_cmp_swap_8, "8">;
899   defm ATOMIC_CMP_SWAP_I16  : AtomicCmpSwap32<atomic_cmp_swap_16, "16">;
900   defm ATOMIC_CMP_SWAP_I32  : AtomicCmpSwap32<atomic_cmp_swap_32, "32">;
901 }
902
903 //===----------------------------------------------------------------------===//
904 // Instruction definition
905 //===----------------------------------------------------------------------===//
906
907 class LoadImm32< string instr_asm, Operand Od, RegisterClass RC> :
908   MipsAsmPseudoInst<(outs RC:$rt), (ins Od:$imm32),
909                      !strconcat(instr_asm, "\t$rt, $imm32")> ;
910 def LoadImm32Reg : LoadImm32<"li", shamt,CPURegs>;
911
912 class LoadAddress<string instr_asm, Operand MemOpnd, RegisterClass RC> :
913   MipsAsmPseudoInst<(outs RC:$rt), (ins MemOpnd:$addr),
914                      !strconcat(instr_asm, "\t$rt, $addr")> ;
915 def LoadAddr32Reg : LoadAddress<"la", mem, CPURegs>;
916
917 class LoadAddressImm<string instr_asm, Operand Od, RegisterClass RC> :
918   MipsAsmPseudoInst<(outs RC:$rt), (ins Od:$imm32),
919                      !strconcat(instr_asm, "\t$rt, $imm32")> ;
920 def LoadAddr32Imm : LoadAddressImm<"la", shamt,CPURegs>;
921
922 //===----------------------------------------------------------------------===//
923 // MipsI Instructions
924 //===----------------------------------------------------------------------===//
925
926 /// Arithmetic Instructions (ALU Immediate)
927 def ADDiu   : ArithLogicI<0x09, "addiu", add, simm16, immSExt16, CPURegs>;
928 def ADDi    : ArithOverflowI<0x08, "addi", add, simm16, immSExt16, CPURegs>;
929 def SLTi    : SetCC_I<0x0a, "slti", setlt, simm16, immSExt16, CPURegs>;
930 def SLTiu   : SetCC_I<0x0b, "sltiu", setult, simm16, immSExt16, CPURegs>;
931 def ANDi    : ArithLogicI<0x0c, "andi", and, uimm16, immZExt16, CPURegs>;
932 def ORi     : ArithLogicI<0x0d, "ori", or, uimm16, immZExt16, CPURegs>;
933 def XORi    : ArithLogicI<0x0e, "xori", xor, uimm16, immZExt16, CPURegs>;
934 def LUi     : LoadUpper<0x0f, "lui", CPURegs, uimm16>;
935
936 /// Arithmetic Instructions (3-Operand, R-Type)
937 def ADDu    : ArithLogicR<0x00, 0x21, "addu", add, IIAlu, CPURegs, 1>;
938 def SUBu    : ArithLogicR<0x00, 0x23, "subu", sub, IIAlu, CPURegs>;
939 def ADD     : ArithOverflowR<0x00, 0x20, "add", IIAlu, CPURegs, 1>;
940 def SUB     : ArithOverflowR<0x00, 0x22, "sub", IIAlu, CPURegs>;
941 def SLT     : SetCC_R<0x00, 0x2a, "slt", setlt, CPURegs>;
942 def SLTu    : SetCC_R<0x00, 0x2b, "sltu", setult, CPURegs>;
943 def AND     : ArithLogicR<0x00, 0x24, "and", and, IIAlu, CPURegs, 1>;
944 def OR      : ArithLogicR<0x00, 0x25, "or",  or, IIAlu, CPURegs, 1>;
945 def XOR     : ArithLogicR<0x00, 0x26, "xor", xor, IIAlu, CPURegs, 1>;
946 def NOR     : LogicNOR<0x00, 0x27, "nor", CPURegs>;
947
948 /// Shift Instructions
949 def SLL     : shift_rotate_imm32<0x00, 0x00, "sll", shl>;
950 def SRL     : shift_rotate_imm32<0x02, 0x00, "srl", srl>;
951 def SRA     : shift_rotate_imm32<0x03, 0x00, "sra", sra>;
952 def SLLV    : shift_rotate_reg<0x04, 0x00, "sllv", shl, CPURegs>;
953 def SRLV    : shift_rotate_reg<0x06, 0x00, "srlv", srl, CPURegs>;
954 def SRAV    : shift_rotate_reg<0x07, 0x00, "srav", sra, CPURegs>;
955
956 // Rotate Instructions
957 let Predicates = [HasMips32r2, HasStandardEncoding] in {
958     def ROTR    : shift_rotate_imm32<0x02, 0x01, "rotr", rotr>;
959     def ROTRV   : shift_rotate_reg<0x06, 0x01, "rotrv", rotr, CPURegs>;
960 }
961
962 /// Load and Store Instructions
963 ///  aligned
964 defm LB      : LoadM32<0x20, "lb",  sextloadi8>;
965 defm LBu     : LoadM32<0x24, "lbu", zextloadi8>;
966 defm LH      : LoadM32<0x21, "lh",  sextloadi16>;
967 defm LHu     : LoadM32<0x25, "lhu", zextloadi16>;
968 defm LW      : LoadM32<0x23, "lw",  load>;
969 defm SB      : StoreM32<0x28, "sb", truncstorei8>;
970 defm SH      : StoreM32<0x29, "sh", truncstorei16>;
971 defm SW      : StoreM32<0x2b, "sw", store>;
972
973 /// load/store left/right
974 defm LWL : LoadLeftRightM32<0x22, "lwl", MipsLWL>;
975 defm LWR : LoadLeftRightM32<0x26, "lwr", MipsLWR>;
976 defm SWL : StoreLeftRightM32<0x2a, "swl", MipsSWL>;
977 defm SWR : StoreLeftRightM32<0x2e, "swr", MipsSWR>;
978
979 let hasSideEffects = 1 in
980 def SYNC : InstSE<(outs), (ins i32imm:$stype), "sync $stype",
981                   [(MipsSync imm:$stype)], NoItinerary, FrmOther>
982 {
983   bits<5> stype;
984   let Opcode = 0;
985   let Inst{25-11} = 0;
986   let Inst{10-6} = stype;
987   let Inst{5-0} = 15;
988 }
989
990 /// Load-linked, Store-conditional
991 def LL    : LLBase<0x30, "ll", CPURegs, mem>,
992             Requires<[NotN64, HasStandardEncoding]>;
993 def LL_P8 : LLBase<0x30, "ll", CPURegs, mem64>,
994             Requires<[IsN64, HasStandardEncoding]> {
995   let DecoderNamespace = "Mips64";
996 }
997
998 def SC    : SCBase<0x38, "sc", CPURegs, mem>,
999             Requires<[NotN64, HasStandardEncoding]>;
1000 def SC_P8 : SCBase<0x38, "sc", CPURegs, mem64>,
1001             Requires<[IsN64, HasStandardEncoding]> {
1002   let DecoderNamespace = "Mips64";
1003 }
1004
1005 /// Jump and Branch Instructions
1006 def J       : JumpFJ<0x02, "j", br>,
1007               Requires<[RelocStatic, HasStandardEncoding]>, IsBranch;
1008 def JR      : IndirectBranch<CPURegs>;
1009 def B       : UncondBranch<0x04, "b">;
1010 def BEQ     : CBranch<0x04, "beq", seteq, CPURegs>;
1011 def BNE     : CBranch<0x05, "bne", setne, CPURegs>;
1012 def BGEZ    : CBranchZero<0x01, 1, "bgez", setge, CPURegs>;
1013 def BGTZ    : CBranchZero<0x07, 0, "bgtz", setgt, CPURegs>;
1014 def BLEZ    : CBranchZero<0x06, 0, "blez", setle, CPURegs>;
1015 def BLTZ    : CBranchZero<0x01, 0, "bltz", setlt, CPURegs>;
1016
1017 let rt = 0, rs = 0, isBranch = 1, isTerminator = 1, isBarrier = 1,
1018     hasDelaySlot = 1, Defs = [RA] in
1019 def BAL_BR: FI<0x1, (outs), (ins brtarget:$imm16), "bal\t$imm16", [], IIBranch>;
1020
1021 def JAL  : JumpLink<0x03, "jal">;
1022 def JALR : JumpLinkReg<0x00, 0x09, "jalr", CPURegs>;
1023 def BGEZAL  : BranchLink<"bgezal", 0x11, CPURegs>;
1024 def BLTZAL  : BranchLink<"bltzal", 0x10, CPURegs>;
1025 def TAILCALL : JumpFJ<0x02, "j", br>, IsTailCall;
1026 def TAILCALL_R : JumpFR<CPURegs, MipsTailCall>, IsTailCall;
1027
1028 def RET : RetBase<CPURegs>;
1029
1030 /// Multiply and Divide Instructions.
1031 def MULT    : Mult32<0x18, "mult", IIImul>;
1032 def MULTu   : Mult32<0x19, "multu", IIImul>;
1033 def SDIV    : Div32<MipsDivRem, 0x1a, "div", IIIdiv>;
1034 def UDIV    : Div32<MipsDivRemU, 0x1b, "divu", IIIdiv>;
1035
1036 def MTHI : MoveToLOHI<0x11, "mthi", CPURegs, [HI]>;
1037 def MTLO : MoveToLOHI<0x13, "mtlo", CPURegs, [LO]>;
1038 def MFHI : MoveFromLOHI<0x10, "mfhi", CPURegs, [HI]>;
1039 def MFLO : MoveFromLOHI<0x12, "mflo", CPURegs, [LO]>;
1040
1041 /// Sign Ext In Register Instructions.
1042 def SEB : SignExtInReg<0x10, "seb", i8, CPURegs>;
1043 def SEH : SignExtInReg<0x18, "seh", i16, CPURegs>;
1044
1045 /// Count Leading
1046 def CLZ : CountLeading0<0x20, "clz", CPURegs>;
1047 def CLO : CountLeading1<0x21, "clo", CPURegs>;
1048
1049 /// Word Swap Bytes Within Halfwords
1050 def WSBH : SubwordSwap<0x20, 0x2, "wsbh", CPURegs>;
1051
1052 /// No operation
1053 let addr=0 in
1054   def NOP   : FJ<0, (outs), (ins), "nop", [], IIAlu>;
1055
1056 // FrameIndexes are legalized when they are operands from load/store
1057 // instructions. The same not happens for stack address copies, so an
1058 // add op with mem ComplexPattern is used and the stack address copy
1059 // can be matched. It's similar to Sparc LEA_ADDRi
1060 def LEA_ADDiu : EffectiveAddress<0x09,"addiu\t$rt, $addr", CPURegs, mem_ea>;
1061
1062 // DynAlloc node points to dynamically allocated stack space.
1063 // $sp is added to the list of implicitly used registers to prevent dead code
1064 // elimination from removing instructions that modify $sp.
1065 let Uses = [SP] in
1066 def DynAlloc : EffectiveAddress<0x09,"addiu\t$rt, $addr", CPURegs, mem_ea>;
1067
1068 // MADD*/MSUB*
1069 def MADD  : MArithR<0, "madd", MipsMAdd, 1>;
1070 def MADDU : MArithR<1, "maddu", MipsMAddu, 1>;
1071 def MSUB  : MArithR<4, "msub", MipsMSub>;
1072 def MSUBU : MArithR<5, "msubu", MipsMSubu>;
1073
1074 // MUL is a assembly macro in the current used ISAs. In recent ISA's
1075 // it is a real instruction.
1076 def MUL   : ArithLogicR<0x1c, 0x02, "mul", mul, IIImul, CPURegs, 1>,
1077             Requires<[HasMips32, HasStandardEncoding]>;
1078
1079 def RDHWR : ReadHardware<CPURegs, HWRegs>;
1080
1081 def EXT : ExtBase<0, "ext", CPURegs>;
1082 def INS : InsBase<4, "ins", CPURegs>;
1083
1084 //===----------------------------------------------------------------------===//
1085 // Instruction aliases
1086 //===----------------------------------------------------------------------===//
1087 def : InstAlias<"move $dst,$src", (ADD CPURegs:$dst,CPURegs:$src,ZERO)>;
1088 def : InstAlias<"bal $offset", (BGEZAL RA,brtarget:$offset)>;
1089 def : InstAlias<"addu $rs,$rt,$imm",
1090                 (ADDiu CPURegs:$rs,CPURegs:$rt,simm16:$imm)>;
1091 def : InstAlias<"add $rs,$rt,$imm",
1092                 (ADDi CPURegs:$rs,CPURegs:$rt,simm16:$imm)>;
1093 def : InstAlias<"and $rs,$rt,$imm",
1094                 (ANDi CPURegs:$rs,CPURegs:$rt,simm16:$imm)>;
1095 def : InstAlias<"j $rs", (JR CPURegs:$rs)>;
1096 def : InstAlias<"not $rt,$rs", (NOR CPURegs:$rt,CPURegs:$rs,ZERO)>;
1097 def : InstAlias<"neg $rt,$rs", (SUB CPURegs:$rt,ZERO,CPURegs:$rs)>;
1098 def : InstAlias<"negu $rt,$rs", (SUBu CPURegs:$rt,ZERO,CPURegs:$rs)>;
1099 def : InstAlias<"slt $rs,$rt,$imm",
1100                 (SLTi CPURegs:$rs,CPURegs:$rt,simm16:$imm)>;
1101 def : InstAlias<"xor $rs,$rt,$imm",
1102                 (XORi CPURegs:$rs,CPURegs:$rt,simm16:$imm)>;
1103
1104 //===----------------------------------------------------------------------===//
1105 //  Arbitrary patterns that map to one or more instructions
1106 //===----------------------------------------------------------------------===//
1107
1108 // Small immediates
1109 def : MipsPat<(i32 immSExt16:$in),
1110               (ADDiu ZERO, imm:$in)>;
1111 def : MipsPat<(i32 immZExt16:$in),
1112               (ORi ZERO, imm:$in)>;
1113 def : MipsPat<(i32 immLow16Zero:$in),
1114               (LUi (HI16 imm:$in))>;
1115
1116 // Arbitrary immediates
1117 def : MipsPat<(i32 imm:$imm),
1118           (ORi (LUi (HI16 imm:$imm)), (LO16 imm:$imm))>;
1119
1120 // Carry MipsPatterns
1121 def : MipsPat<(subc CPURegs:$lhs, CPURegs:$rhs),
1122               (SUBu CPURegs:$lhs, CPURegs:$rhs)>;
1123 def : MipsPat<(addc CPURegs:$lhs, CPURegs:$rhs),
1124               (ADDu CPURegs:$lhs, CPURegs:$rhs)>;
1125 def : MipsPat<(addc  CPURegs:$src, immSExt16:$imm),
1126               (ADDiu CPURegs:$src, imm:$imm)>;
1127
1128 // Call
1129 def : MipsPat<(MipsJmpLink (i32 tglobaladdr:$dst)),
1130               (JAL tglobaladdr:$dst)>;
1131 def : MipsPat<(MipsJmpLink (i32 texternalsym:$dst)),
1132               (JAL texternalsym:$dst)>;
1133 //def : MipsPat<(MipsJmpLink CPURegs:$dst),
1134 //              (JALR CPURegs:$dst)>;
1135
1136 // hi/lo relocs
1137 def : MipsPat<(MipsHi tglobaladdr:$in), (LUi tglobaladdr:$in)>;
1138 def : MipsPat<(MipsHi tblockaddress:$in), (LUi tblockaddress:$in)>;
1139 def : MipsPat<(MipsHi tjumptable:$in), (LUi tjumptable:$in)>;
1140 def : MipsPat<(MipsHi tconstpool:$in), (LUi tconstpool:$in)>;
1141 def : MipsPat<(MipsHi tglobaltlsaddr:$in), (LUi tglobaltlsaddr:$in)>;
1142
1143 def : MipsPat<(MipsLo tglobaladdr:$in), (ADDiu ZERO, tglobaladdr:$in)>;
1144 def : MipsPat<(MipsLo tblockaddress:$in), (ADDiu ZERO, tblockaddress:$in)>;
1145 def : MipsPat<(MipsLo tjumptable:$in), (ADDiu ZERO, tjumptable:$in)>;
1146 def : MipsPat<(MipsLo tconstpool:$in), (ADDiu ZERO, tconstpool:$in)>;
1147 def : MipsPat<(MipsLo tglobaltlsaddr:$in), (ADDiu ZERO, tglobaltlsaddr:$in)>;
1148
1149 def : MipsPat<(add CPURegs:$hi, (MipsLo tglobaladdr:$lo)),
1150               (ADDiu CPURegs:$hi, tglobaladdr:$lo)>;
1151 def : MipsPat<(add CPURegs:$hi, (MipsLo tblockaddress:$lo)),
1152               (ADDiu CPURegs:$hi, tblockaddress:$lo)>;
1153 def : MipsPat<(add CPURegs:$hi, (MipsLo tjumptable:$lo)),
1154               (ADDiu CPURegs:$hi, tjumptable:$lo)>;
1155 def : MipsPat<(add CPURegs:$hi, (MipsLo tconstpool:$lo)),
1156               (ADDiu CPURegs:$hi, tconstpool:$lo)>;
1157 def : MipsPat<(add CPURegs:$hi, (MipsLo tglobaltlsaddr:$lo)),
1158               (ADDiu CPURegs:$hi, tglobaltlsaddr:$lo)>;
1159
1160 // gp_rel relocs
1161 def : MipsPat<(add CPURegs:$gp, (MipsGPRel tglobaladdr:$in)),
1162               (ADDiu CPURegs:$gp, tglobaladdr:$in)>;
1163 def : MipsPat<(add CPURegs:$gp, (MipsGPRel tconstpool:$in)),
1164               (ADDiu CPURegs:$gp, tconstpool:$in)>;
1165
1166 // wrapper_pic
1167 class WrapperPat<SDNode node, Instruction ADDiuOp, RegisterClass RC>:
1168       MipsPat<(MipsWrapper RC:$gp, node:$in),
1169               (ADDiuOp RC:$gp, node:$in)>;
1170
1171 def : WrapperPat<tglobaladdr, ADDiu, CPURegs>;
1172 def : WrapperPat<tconstpool, ADDiu, CPURegs>;
1173 def : WrapperPat<texternalsym, ADDiu, CPURegs>;
1174 def : WrapperPat<tblockaddress, ADDiu, CPURegs>;
1175 def : WrapperPat<tjumptable, ADDiu, CPURegs>;
1176 def : WrapperPat<tglobaltlsaddr, ADDiu, CPURegs>;
1177
1178 // Mips does not have "not", so we expand our way
1179 def : MipsPat<(not CPURegs:$in),
1180               (NOR CPURegs:$in, ZERO)>;
1181
1182 // extended loads
1183 let Predicates = [NotN64, HasStandardEncoding] in {
1184   def : MipsPat<(i32 (extloadi1  addr:$src)), (LBu addr:$src)>;
1185   def : MipsPat<(i32 (extloadi8  addr:$src)), (LBu addr:$src)>;
1186   def : MipsPat<(i32 (extloadi16 addr:$src)), (LHu addr:$src)>;
1187 }
1188 let Predicates = [IsN64, HasStandardEncoding] in {
1189   def : MipsPat<(i32 (extloadi1  addr:$src)), (LBu_P8 addr:$src)>;
1190   def : MipsPat<(i32 (extloadi8  addr:$src)), (LBu_P8 addr:$src)>;
1191   def : MipsPat<(i32 (extloadi16 addr:$src)), (LHu_P8 addr:$src)>;
1192 }
1193
1194 // peepholes
1195 let Predicates = [NotN64, HasStandardEncoding] in {
1196   def : MipsPat<(store (i32 0), addr:$dst), (SW ZERO, addr:$dst)>;
1197 }
1198 let Predicates = [IsN64, HasStandardEncoding] in {
1199   def : MipsPat<(store (i32 0), addr:$dst), (SW_P8 ZERO, addr:$dst)>;
1200 }
1201
1202 // brcond patterns
1203 multiclass BrcondPats<RegisterClass RC, Instruction BEQOp, Instruction BNEOp,
1204                       Instruction SLTOp, Instruction SLTuOp, Instruction SLTiOp,
1205                       Instruction SLTiuOp, Register ZEROReg> {
1206 def : MipsPat<(brcond (i32 (setne RC:$lhs, 0)), bb:$dst),
1207               (BNEOp RC:$lhs, ZEROReg, bb:$dst)>;
1208 def : MipsPat<(brcond (i32 (seteq RC:$lhs, 0)), bb:$dst),
1209               (BEQOp RC:$lhs, ZEROReg, bb:$dst)>;
1210
1211 def : MipsPat<(brcond (i32 (setge RC:$lhs, RC:$rhs)), bb:$dst),
1212               (BEQ (SLTOp RC:$lhs, RC:$rhs), ZERO, bb:$dst)>;
1213 def : MipsPat<(brcond (i32 (setuge RC:$lhs, RC:$rhs)), bb:$dst),
1214               (BEQ (SLTuOp RC:$lhs, RC:$rhs), ZERO, bb:$dst)>;
1215 def : MipsPat<(brcond (i32 (setge RC:$lhs, immSExt16:$rhs)), bb:$dst),
1216               (BEQ (SLTiOp RC:$lhs, immSExt16:$rhs), ZERO, bb:$dst)>;
1217 def : MipsPat<(brcond (i32 (setuge RC:$lhs, immSExt16:$rhs)), bb:$dst),
1218               (BEQ (SLTiuOp RC:$lhs, immSExt16:$rhs), ZERO, bb:$dst)>;
1219
1220 def : MipsPat<(brcond (i32 (setle RC:$lhs, RC:$rhs)), bb:$dst),
1221               (BEQ (SLTOp RC:$rhs, RC:$lhs), ZERO, bb:$dst)>;
1222 def : MipsPat<(brcond (i32 (setule RC:$lhs, RC:$rhs)), bb:$dst),
1223               (BEQ (SLTuOp RC:$rhs, RC:$lhs), ZERO, bb:$dst)>;
1224
1225 def : MipsPat<(brcond RC:$cond, bb:$dst),
1226               (BNEOp RC:$cond, ZEROReg, bb:$dst)>;
1227 }
1228
1229 defm : BrcondPats<CPURegs, BEQ, BNE, SLT, SLTu, SLTi, SLTiu, ZERO>;
1230
1231 // setcc patterns
1232 multiclass SeteqPats<RegisterClass RC, Instruction SLTiuOp, Instruction XOROp,
1233                      Instruction SLTuOp, Register ZEROReg> {
1234   def : MipsPat<(seteq RC:$lhs, RC:$rhs),
1235                 (SLTiuOp (XOROp RC:$lhs, RC:$rhs), 1)>;
1236   def : MipsPat<(setne RC:$lhs, RC:$rhs),
1237                 (SLTuOp ZEROReg, (XOROp RC:$lhs, RC:$rhs))>;
1238 }
1239
1240 multiclass SetlePats<RegisterClass RC, Instruction SLTOp, Instruction SLTuOp> {
1241   def : MipsPat<(setle RC:$lhs, RC:$rhs),
1242                 (XORi (SLTOp RC:$rhs, RC:$lhs), 1)>;
1243   def : MipsPat<(setule RC:$lhs, RC:$rhs),
1244                 (XORi (SLTuOp RC:$rhs, RC:$lhs), 1)>;
1245 }
1246
1247 multiclass SetgtPats<RegisterClass RC, Instruction SLTOp, Instruction SLTuOp> {
1248   def : MipsPat<(setgt RC:$lhs, RC:$rhs),
1249                 (SLTOp RC:$rhs, RC:$lhs)>;
1250   def : MipsPat<(setugt RC:$lhs, RC:$rhs),
1251                 (SLTuOp RC:$rhs, RC:$lhs)>;
1252 }
1253
1254 multiclass SetgePats<RegisterClass RC, Instruction SLTOp, Instruction SLTuOp> {
1255   def : MipsPat<(setge RC:$lhs, RC:$rhs),
1256                 (XORi (SLTOp RC:$lhs, RC:$rhs), 1)>;
1257   def : MipsPat<(setuge RC:$lhs, RC:$rhs),
1258                 (XORi (SLTuOp RC:$lhs, RC:$rhs), 1)>;
1259 }
1260
1261 multiclass SetgeImmPats<RegisterClass RC, Instruction SLTiOp,
1262                         Instruction SLTiuOp> {
1263   def : MipsPat<(setge RC:$lhs, immSExt16:$rhs),
1264                 (XORi (SLTiOp RC:$lhs, immSExt16:$rhs), 1)>;
1265   def : MipsPat<(setuge RC:$lhs, immSExt16:$rhs),
1266                 (XORi (SLTiuOp RC:$lhs, immSExt16:$rhs), 1)>;
1267 }
1268
1269 defm : SeteqPats<CPURegs, SLTiu, XOR, SLTu, ZERO>;
1270 defm : SetlePats<CPURegs, SLT, SLTu>;
1271 defm : SetgtPats<CPURegs, SLT, SLTu>;
1272 defm : SetgePats<CPURegs, SLT, SLTu>;
1273 defm : SetgeImmPats<CPURegs, SLTi, SLTiu>;
1274
1275 // select MipsDynAlloc
1276 def : MipsPat<(MipsDynAlloc addr:$f), (DynAlloc addr:$f)>;
1277
1278 // bswap pattern
1279 def : MipsPat<(bswap CPURegs:$rt), (ROTR (WSBH CPURegs:$rt), 16)>;
1280
1281 //===----------------------------------------------------------------------===//
1282 // Floating Point Support
1283 //===----------------------------------------------------------------------===//
1284
1285 include "MipsInstrFPU.td"
1286 include "Mips64InstrInfo.td"
1287 include "MipsCondMov.td"
1288
1289 //
1290 // Mips16
1291
1292 include "Mips16InstrFormats.td"
1293 include "Mips16InstrInfo.td"
1294
1295 // DSP
1296 include "MipsDSPInstrFormats.td"
1297 include "MipsDSPInstrInfo.td"
1298