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