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
19def SDT_MipsJmpLink      : SDTypeProfile<0, 1, [SDTCisVT<0, iPTR>]>;
20def SDT_MipsCMov         : SDTypeProfile<1, 4, [SDTCisSameAs<0, 1>,
21                                                SDTCisSameAs<1, 2>,
22                                                SDTCisSameAs<3, 4>,
23                                                SDTCisInt<4>]>;
24def SDT_MipsCallSeqStart : SDCallSeqStart<[SDTCisVT<0, i32>, SDTCisVT<1, i32>]>;
25def SDT_MipsCallSeqEnd   : SDCallSeqEnd<[SDTCisVT<0, i32>, SDTCisVT<1, i32>]>;
26def SDT_MFLOHI : SDTypeProfile<1, 1, [SDTCisInt<0>, SDTCisVT<1, untyped>]>;
27def SDT_MTLOHI : SDTypeProfile<1, 2, [SDTCisVT<0, untyped>,
28                                      SDTCisInt<1>, SDTCisSameAs<1, 2>]>;
29def SDT_MipsMultDiv : SDTypeProfile<1, 2, [SDTCisVT<0, untyped>, SDTCisInt<1>,
30                                    SDTCisSameAs<1, 2>]>;
31def SDT_MipsMAddMSub : SDTypeProfile<1, 3,
32                                     [SDTCisVT<0, untyped>, SDTCisSameAs<0, 3>,
33                                      SDTCisVT<1, i32>, SDTCisSameAs<1, 2>]>;
34def SDT_MipsDivRem16 : SDTypeProfile<0, 2, [SDTCisInt<0>, SDTCisSameAs<0, 1>]>;
35
36def SDT_MipsThreadPointer : SDTypeProfile<1, 0, [SDTCisPtrTy<0>]>;
37
38def SDT_Sync             : SDTypeProfile<0, 1, [SDTCisVT<0, i32>]>;
39
40def SDT_Ext : SDTypeProfile<1, 3, [SDTCisInt<0>, SDTCisSameAs<0, 1>,
41                                   SDTCisVT<2, i32>, SDTCisSameAs<2, 3>]>;
42def SDT_Ins : SDTypeProfile<1, 4, [SDTCisInt<0>, SDTCisSameAs<0, 1>,
43                                   SDTCisVT<2, i32>, SDTCisSameAs<2, 3>,
44                                   SDTCisSameAs<0, 4>]>;
45
46def SDTMipsLoadLR  : SDTypeProfile<1, 2,
47                                   [SDTCisInt<0>, SDTCisPtrTy<1>,
48                                    SDTCisSameAs<0, 2>]>;
49
50// Call
51def MipsJmpLink : SDNode<"MipsISD::JmpLink",SDT_MipsJmpLink,
52                         [SDNPHasChain, SDNPOutGlue, SDNPOptInGlue,
53                          SDNPVariadic]>;
54
55// Tail call
56def 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
63// Hi is the odd node out, on MIPS64 it can expand to either daddiu when
64// using static relocations with 64 bit symbols, or lui when using 32 bit
65// symbols.
66def MipsHigher : SDNode<"MipsISD::Higher", SDTIntUnaryOp>;
67def MipsHighest : SDNode<"MipsISD::Highest", SDTIntUnaryOp>;
68def MipsHi    : SDNode<"MipsISD::Hi", SDTIntUnaryOp>;
69def MipsLo    : SDNode<"MipsISD::Lo", SDTIntUnaryOp>;
70
71def MipsGPRel : SDNode<"MipsISD::GPRel", SDTIntUnaryOp>;
72
73// Hi node for accessing the GOT.
74def MipsGotHi : SDNode<"MipsISD::GotHi", SDTIntUnaryOp>;
75
76// Hi node for handling TLS offsets
77def MipsTlsHi   : SDNode<"MipsISD::TlsHi", SDTIntUnaryOp>;
78
79// Thread pointer
80def MipsThreadPointer: SDNode<"MipsISD::ThreadPointer", SDT_MipsThreadPointer>;
81
82// Return
83def MipsRet : SDNode<"MipsISD::Ret", SDTNone,
84                     [SDNPHasChain, SDNPOptInGlue, SDNPVariadic]>;
85
86def MipsERet : SDNode<"MipsISD::ERet", SDTNone,
87                      [SDNPHasChain, SDNPOptInGlue, SDNPSideEffect]>;
88
89// These are target-independent nodes, but have target-specific formats.
90def callseq_start : SDNode<"ISD::CALLSEQ_START", SDT_MipsCallSeqStart,
91                           [SDNPHasChain, SDNPSideEffect, SDNPOutGlue]>;
92def callseq_end   : SDNode<"ISD::CALLSEQ_END", SDT_MipsCallSeqEnd,
93                           [SDNPHasChain, SDNPSideEffect,
94                            SDNPOptInGlue, SDNPOutGlue]>;
95
96// Nodes used to extract LO/HI registers.
97def MipsMFHI : SDNode<"MipsISD::MFHI", SDT_MFLOHI>;
98def MipsMFLO : SDNode<"MipsISD::MFLO", SDT_MFLOHI>;
99
100// Node used to insert 32-bit integers to LOHI register pair.
101def MipsMTLOHI : SDNode<"MipsISD::MTLOHI", SDT_MTLOHI>;
102
103// Mult nodes.
104def MipsMult  : SDNode<"MipsISD::Mult", SDT_MipsMultDiv>;
105def MipsMultu : SDNode<"MipsISD::Multu", SDT_MipsMultDiv>;
106
107// MAdd*/MSub* nodes
108def MipsMAdd  : SDNode<"MipsISD::MAdd", SDT_MipsMAddMSub>;
109def MipsMAddu : SDNode<"MipsISD::MAddu", SDT_MipsMAddMSub>;
110def MipsMSub  : SDNode<"MipsISD::MSub", SDT_MipsMAddMSub>;
111def MipsMSubu : SDNode<"MipsISD::MSubu", SDT_MipsMAddMSub>;
112
113// DivRem(u) nodes
114def MipsDivRem    : SDNode<"MipsISD::DivRem", SDT_MipsMultDiv>;
115def MipsDivRemU   : SDNode<"MipsISD::DivRemU", SDT_MipsMultDiv>;
116def MipsDivRem16  : SDNode<"MipsISD::DivRem16", SDT_MipsDivRem16,
117                           [SDNPOutGlue]>;
118def MipsDivRemU16 : SDNode<"MipsISD::DivRemU16", SDT_MipsDivRem16,
119                           [SDNPOutGlue]>;
120
121// Target constant nodes that are not part of any isel patterns and remain
122// unchanged can cause instructions with illegal operands to be emitted.
123// Wrapper node patterns give the instruction selector a chance to replace
124// target constant nodes that would otherwise remain unchanged with ADDiu
125// nodes. Without these wrapper node patterns, the following conditional move
126// instruction is emitted when function cmov2 in test/CodeGen/Mips/cmov.ll is
127// compiled:
128//  movn  %got(d)($gp), %got(c)($gp), $4
129// This instruction is illegal since movn can take only register operands.
130
131def MipsWrapper    : SDNode<"MipsISD::Wrapper", SDTIntBinOp>;
132
133def MipsSync : SDNode<"MipsISD::Sync", SDT_Sync, [SDNPHasChain,SDNPSideEffect]>;
134
135def MipsExt :  SDNode<"MipsISD::Ext", SDT_Ext>;
136def MipsIns :  SDNode<"MipsISD::Ins", SDT_Ins>;
137def MipsCIns : SDNode<"MipsISD::CIns", SDT_Ext>;
138
139def MipsLWL : SDNode<"MipsISD::LWL", SDTMipsLoadLR,
140                     [SDNPHasChain, SDNPMayLoad, SDNPMemOperand]>;
141def MipsLWR : SDNode<"MipsISD::LWR", SDTMipsLoadLR,
142                     [SDNPHasChain, SDNPMayLoad, SDNPMemOperand]>;
143def MipsSWL : SDNode<"MipsISD::SWL", SDTStore,
144                     [SDNPHasChain, SDNPMayStore, SDNPMemOperand]>;
145def MipsSWR : SDNode<"MipsISD::SWR", SDTStore,
146                     [SDNPHasChain, SDNPMayStore, SDNPMemOperand]>;
147def MipsLDL : SDNode<"MipsISD::LDL", SDTMipsLoadLR,
148                     [SDNPHasChain, SDNPMayLoad, SDNPMemOperand]>;
149def MipsLDR : SDNode<"MipsISD::LDR", SDTMipsLoadLR,
150                     [SDNPHasChain, SDNPMayLoad, SDNPMemOperand]>;
151def MipsSDL : SDNode<"MipsISD::SDL", SDTStore,
152                     [SDNPHasChain, SDNPMayStore, SDNPMemOperand]>;
153def MipsSDR : SDNode<"MipsISD::SDR", SDTStore,
154                     [SDNPHasChain, SDNPMayStore, SDNPMemOperand]>;
155
156//===----------------------------------------------------------------------===//
157// Mips Instruction Predicate Definitions.
158//===----------------------------------------------------------------------===//
159def HasMips2     :    Predicate<"Subtarget->hasMips2()">,
160                      AssemblerPredicate<"FeatureMips2">;
161def HasMips3_32  :    Predicate<"Subtarget->hasMips3_32()">,
162                      AssemblerPredicate<"FeatureMips3_32">;
163def HasMips3_32r2 :   Predicate<"Subtarget->hasMips3_32r2()">,
164                      AssemblerPredicate<"FeatureMips3_32r2">;
165def HasMips3     :    Predicate<"Subtarget->hasMips3()">,
166                      AssemblerPredicate<"FeatureMips3">;
167def NotMips3     :    Predicate<"!Subtarget->hasMips3()">,
168                      AssemblerPredicate<"!FeatureMips3">;
169def HasMips4_32  :    Predicate<"Subtarget->hasMips4_32()">,
170                      AssemblerPredicate<"FeatureMips4_32">;
171def NotMips4_32  :    Predicate<"!Subtarget->hasMips4_32()">,
172                      AssemblerPredicate<"!FeatureMips4_32">;
173def HasMips4_32r2 :   Predicate<"Subtarget->hasMips4_32r2()">,
174                      AssemblerPredicate<"FeatureMips4_32r2">;
175def HasMips5_32r2 :   Predicate<"Subtarget->hasMips5_32r2()">,
176                      AssemblerPredicate<"FeatureMips5_32r2">;
177def HasMips32    :    Predicate<"Subtarget->hasMips32()">,
178                      AssemblerPredicate<"FeatureMips32">;
179def HasMips32r2  :    Predicate<"Subtarget->hasMips32r2()">,
180                      AssemblerPredicate<"FeatureMips32r2">;
181def HasMips32r5  :    Predicate<"Subtarget->hasMips32r5()">,
182                      AssemblerPredicate<"FeatureMips32r5">;
183def HasMips32r6  :    Predicate<"Subtarget->hasMips32r6()">,
184                      AssemblerPredicate<"FeatureMips32r6">;
185def NotMips32r6  :    Predicate<"!Subtarget->hasMips32r6()">,
186                      AssemblerPredicate<"!FeatureMips32r6">;
187def IsGP64bit    :    Predicate<"Subtarget->isGP64bit()">,
188                      AssemblerPredicate<"FeatureGP64Bit">;
189def IsGP32bit    :    Predicate<"!Subtarget->isGP64bit()">,
190                      AssemblerPredicate<"!FeatureGP64Bit">;
191def IsPTR64bit    :   Predicate<"Subtarget->isABI_N64()">,
192                      AssemblerPredicate<"FeaturePTR64Bit">;
193def IsPTR32bit    :   Predicate<"!Subtarget->isABI_N64()">,
194                      AssemblerPredicate<"!FeaturePTR64Bit">;
195def HasMips64    :    Predicate<"Subtarget->hasMips64()">,
196                      AssemblerPredicate<"FeatureMips64">;
197def NotMips64    :    Predicate<"!Subtarget->hasMips64()">,
198                      AssemblerPredicate<"!FeatureMips64">;
199def HasMips64r2  :    Predicate<"Subtarget->hasMips64r2()">,
200                      AssemblerPredicate<"FeatureMips64r2">;
201def HasMips64r5  :    Predicate<"Subtarget->hasMips64r5()">,
202                      AssemblerPredicate<"FeatureMips64r5">;
203def HasMips64r6  :    Predicate<"Subtarget->hasMips64r6()">,
204                      AssemblerPredicate<"FeatureMips64r6">;
205def NotMips64r6  :    Predicate<"!Subtarget->hasMips64r6()">,
206                      AssemblerPredicate<"!FeatureMips64r6">;
207def InMips16Mode :    Predicate<"Subtarget->inMips16Mode()">,
208                      AssemblerPredicate<"FeatureMips16">;
209def NotInMips16Mode : Predicate<"!Subtarget->inMips16Mode()">,
210                      AssemblerPredicate<"!FeatureMips16">;
211def HasCnMips    :    Predicate<"Subtarget->hasCnMips()">,
212                      AssemblerPredicate<"FeatureCnMips">;
213def NotCnMips    :    Predicate<"!Subtarget->hasCnMips()">,
214                      AssemblerPredicate<"!FeatureCnMips">;
215def IsSym32     :     Predicate<"Subtarget->HasSym32()">,
216                      AssemblerPredicate<"FeatureSym32">;
217def IsSym64     :     Predicate<"!Subtarget->HasSym32()">,
218                      AssemblerPredicate<"!FeatureSym32">;
219def IsN64       :     Predicate<"Subtarget->isABI_N64()">;
220def IsNotN64    :     Predicate<"!Subtarget->isABI_N64()">;
221def RelocNotPIC :     Predicate<"!TM.isPositionIndependent()">;
222def RelocPIC    :     Predicate<"TM.isPositionIndependent()">;
223def NoNaNsFPMath :    Predicate<"TM.Options.NoNaNsFPMath">;
224def HasStdEnc :       Predicate<"Subtarget->hasStandardEncoding()">,
225                      AssemblerPredicate<"!FeatureMips16">;
226def NotDSP :          Predicate<"!Subtarget->hasDSP()">;
227def InMicroMips    :  Predicate<"Subtarget->inMicroMipsMode()">,
228                      AssemblerPredicate<"FeatureMicroMips">;
229def NotInMicroMips :  Predicate<"!Subtarget->inMicroMipsMode()">,
230                      AssemblerPredicate<"!FeatureMicroMips">;
231def IsLE           :  Predicate<"Subtarget->isLittle()">;
232def IsBE           :  Predicate<"!Subtarget->isLittle()">;
233def IsNotNaCl    :    Predicate<"!Subtarget->isTargetNaCl()">;
234def UseTCCInDIV    :  AssemblerPredicate<"FeatureUseTCCInDIV">;
235def HasEVA       :    Predicate<"Subtarget->hasEVA()">,
236                      AssemblerPredicate<"FeatureEVA">;
237def HasMSA : Predicate<"Subtarget->hasMSA()">,
238             AssemblerPredicate<"FeatureMSA">;
239def HasMadd4 : Predicate<"!Subtarget->disableMadd4()">,
240               AssemblerPredicate<"!FeatureMadd4">;
241def HasMT  : Predicate<"Subtarget->hasMT()">,
242             AssemblerPredicate<"FeatureMT">;
243def UseIndirectJumpsHazard : Predicate<"Subtarget->useIndirectJumpsHazard()">,
244                            AssemblerPredicate<"FeatureUseIndirectJumpsHazard">;
245def NoIndirectJumpGuards : Predicate<"!Subtarget->useIndirectJumpsHazard()">,
246                           AssemblerPredicate<"!FeatureUseIndirectJumpsHazard">;
247def HasCRC   : Predicate<"Subtarget->hasCRC()">,
248               AssemblerPredicate<"FeatureCRC">;
249def HasVirt  : Predicate<"Subtarget->hasVirt()">,
250               AssemblerPredicate<"FeatureVirt">;
251def HasGINV  : Predicate<"Subtarget->hasGINV()">,
252               AssemblerPredicate<"FeatureGINV">;
253// TODO: Add support for FPOpFusion::Standard
254def AllowFPOpFusion : Predicate<"TM.Options.AllowFPOpFusion =="
255                                " FPOpFusion::Fast">;
256//===----------------------------------------------------------------------===//
257// Mips GPR size adjectives.
258// They are mutually exclusive.
259//===----------------------------------------------------------------------===//
260
261class GPR_32 { list<Predicate> GPRPredicates = [IsGP32bit]; }
262class GPR_64 { list<Predicate> GPRPredicates = [IsGP64bit]; }
263
264class PTR_32 { list<Predicate> PTRPredicates = [IsPTR32bit]; }
265class PTR_64 { list<Predicate> PTRPredicates = [IsPTR64bit]; }
266
267//===----------------------------------------------------------------------===//
268// Mips Symbol size adjectives.
269// They are mutally exculsive.
270//===----------------------------------------------------------------------===//
271
272class SYM_32 { list<Predicate> SYMPredicates = [IsSym32]; }
273class SYM_64 { list<Predicate> SYMPredicates = [IsSym64]; }
274
275//===----------------------------------------------------------------------===//
276// Mips ISA/ASE membership and instruction group membership adjectives.
277// They are mutually exclusive.
278//===----------------------------------------------------------------------===//
279
280// FIXME: I'd prefer to use additive predicates to build the instruction sets
281//        but we are short on assembler feature bits at the moment. Using a
282//        subtractive predicate will hopefully keep us under the 32 predicate
283//        limit long enough to develop an alternative way to handle P1||P2
284//        predicates.
285class ISA_MIPS1 {
286  list<Predicate> EncodingPredicates = [HasStdEnc];
287}
288class ISA_MIPS1_NOT_MIPS3 {
289  list<Predicate> InsnPredicates = [NotMips3];
290  list<Predicate> EncodingPredicates = [HasStdEnc];
291}
292class ISA_MIPS1_NOT_4_32 {
293  list<Predicate> InsnPredicates = [NotMips4_32];
294  list<Predicate> EncodingPredicates = [HasStdEnc];
295}
296class ISA_MIPS1_NOT_32R6_64R6 {
297  list<Predicate> InsnPredicates = [NotMips32r6, NotMips64r6];
298  list<Predicate> EncodingPredicates = [HasStdEnc];
299}
300class ISA_MIPS2 {
301  list<Predicate> InsnPredicates = [HasMips2];
302  list<Predicate> EncodingPredicates = [HasStdEnc];
303}
304class ISA_MIPS2_NOT_32R6_64R6 {
305  list<Predicate> InsnPredicates = [HasMips2, NotMips32r6, NotMips64r6];
306  list<Predicate> EncodingPredicates = [HasStdEnc];
307}
308class ISA_MIPS3 {
309  list<Predicate> InsnPredicates = [HasMips3];
310  list<Predicate> EncodingPredicates = [HasStdEnc];
311}
312class ISA_MIPS3_NOT_32R6_64R6 {
313  list<Predicate> InsnPredicates = [HasMips3, NotMips32r6, NotMips64r6];
314  list<Predicate> EncodingPredicates = [HasStdEnc];
315}
316class ISA_MIPS32 {
317  list<Predicate> InsnPredicates = [HasMips32];
318  list<Predicate> EncodingPredicates = [HasStdEnc];
319}
320class ISA_MIPS32_NOT_32R6_64R6 {
321  list<Predicate> InsnPredicates = [HasMips32, NotMips32r6, NotMips64r6];
322  list<Predicate> EncodingPredicates = [HasStdEnc];
323}
324class ISA_MIPS32R2 {
325  list<Predicate> InsnPredicates = [HasMips32r2];
326  list<Predicate> EncodingPredicates = [HasStdEnc];
327}
328class ISA_MIPS32R2_NOT_32R6_64R6 {
329  list<Predicate> InsnPredicates = [HasMips32r2, NotMips32r6, NotMips64r6];
330  list<Predicate> EncodingPredicates = [HasStdEnc];
331}
332class ISA_MIPS32R5 {
333  list<Predicate> InsnPredicates = [HasMips32r5];
334  list<Predicate> EncodingPredicates = [HasStdEnc];
335}
336class ISA_MIPS64 {
337  list<Predicate> InsnPredicates = [HasMips64];
338  list<Predicate> EncodingPredicates = [HasStdEnc];
339}
340class ISA_MIPS64_NOT_64R6 {
341  list<Predicate> InsnPredicates = [HasMips64, NotMips64r6];
342  list<Predicate> EncodingPredicates = [HasStdEnc];
343}
344class ISA_MIPS64R2 {
345  list<Predicate> InsnPredicates = [HasMips64r2];
346  list<Predicate> EncodingPredicates = [HasStdEnc];
347}
348class ISA_MIPS64R5 {
349  list<Predicate> InsnPredicates = [HasMips64r5];
350  list<Predicate> EncodingPredicates = [HasStdEnc];
351}
352class ISA_MIPS32R6 {
353  list<Predicate> InsnPredicates = [HasMips32r6];
354  list<Predicate> EncodingPredicates = [HasStdEnc];
355}
356class ISA_MIPS64R6 {
357  list<Predicate> InsnPredicates = [HasMips64r6];
358  list<Predicate> EncodingPredicates = [HasStdEnc];
359}
360class ISA_MICROMIPS {
361  list<Predicate> EncodingPredicates = [InMicroMips];
362}
363class ISA_MICROMIPS32R5 {
364  list<Predicate> InsnPredicates = [HasMips32r5];
365  list<Predicate> EncodingPredicates = [InMicroMips];
366}
367class ISA_MICROMIPS32R6 {
368  list<Predicate> InsnPredicates = [HasMips32r6];
369  list<Predicate> EncodingPredicates = [InMicroMips];
370}
371class ISA_MICROMIPS64R6 {
372  list<Predicate> InsnPredicates = [HasMips64r6];
373  list<Predicate> EncodingPredicates = [InMicroMips];
374}
375class ISA_MICROMIPS32_NOT_MIPS32R6 {
376  list<Predicate> InsnPredicates = [NotMips32r6];
377  list<Predicate> EncodingPredicates = [InMicroMips];
378}
379class ASE_EVA { list<Predicate> ASEPredicate = [HasEVA]; }
380
381// The portions of MIPS-III that were also added to MIPS32
382class INSN_MIPS3_32 {
383  list<Predicate> InsnPredicates = [HasMips3_32];
384  list<Predicate> EncodingPredicates = [HasStdEnc];
385}
386
387// The portions of MIPS-III that were also added to MIPS32 but were removed in
388// MIPS32r6 and MIPS64r6.
389class INSN_MIPS3_32_NOT_32R6_64R6 {
390  list<Predicate> InsnPredicates = [HasMips3_32, NotMips32r6, NotMips64r6];
391  list<Predicate> EncodingPredicates = [HasStdEnc];
392}
393
394// The portions of MIPS-III that were also added to MIPS32
395class INSN_MIPS3_32R2 {
396  list<Predicate> InsnPredicates = [HasMips3_32r2];
397  list<Predicate> EncodingPredicates = [HasStdEnc];
398}
399
400// The portions of MIPS-IV that were also added to MIPS32.
401class INSN_MIPS4_32 {
402  list <Predicate> InsnPredicates = [HasMips4_32];
403  list<Predicate> EncodingPredicates = [HasStdEnc];
404}
405
406// The portions of MIPS-IV that were also added to MIPS32 but were removed in
407// MIPS32r6 and MIPS64r6.
408class INSN_MIPS4_32_NOT_32R6_64R6 {
409  list<Predicate> InsnPredicates = [HasMips4_32, NotMips32r6, NotMips64r6];
410  list<Predicate> EncodingPredicates = [HasStdEnc];
411}
412
413// The portions of MIPS-IV that were also added to MIPS32r2 but were removed in
414// MIPS32r6 and MIPS64r6.
415class INSN_MIPS4_32R2_NOT_32R6_64R6 {
416  list<Predicate> InsnPredicates = [HasMips4_32r2, NotMips32r6, NotMips64r6];
417  list<Predicate> EncodingPredicates = [HasStdEnc];
418}
419
420// The portions of MIPS-IV that were also added to MIPS32r2.
421class INSN_MIPS4_32R2 {
422  list<Predicate> InsnPredicates = [HasMips4_32r2];
423  list<Predicate> EncodingPredicates = [HasStdEnc];
424}
425
426// The portions of MIPS-V that were also added to MIPS32r2 but were removed in
427// MIPS32r6 and MIPS64r6.
428class INSN_MIPS5_32R2_NOT_32R6_64R6 {
429  list<Predicate> InsnPredicates = [HasMips5_32r2, NotMips32r6, NotMips64r6];
430  list<Predicate> EncodingPredicates = [HasStdEnc];
431}
432
433class ASE_CNMIPS {
434  list<Predicate> ASEPredicate = [HasCnMips];
435}
436
437class NOT_ASE_CNMIPS {
438  list<Predicate> ASEPredicate = [NotCnMips];
439}
440
441class ASE_MIPS64_CNMIPS {
442  list<Predicate> ASEPredicate = [HasMips64, HasCnMips];
443}
444
445class ASE_MSA {
446  list<Predicate> ASEPredicate = [HasMSA];
447}
448
449class ASE_MSA_NOT_MSA64 {
450  list<Predicate> ASEPredicate = [HasMSA, NotMips64];
451}
452
453class ASE_MSA64 {
454  list<Predicate> ASEPredicate = [HasMSA, HasMips64];
455}
456
457class ASE_MT {
458  list <Predicate> ASEPredicate = [HasMT];
459}
460
461class ASE_CRC {
462  list <Predicate> ASEPredicate = [HasCRC];
463}
464
465class ASE_VIRT {
466  list <Predicate> ASEPredicate = [HasVirt];
467}
468
469class ASE_GINV {
470  list <Predicate> ASEPredicate = [HasGINV];
471}
472
473// Class used for separating microMIPSr6 and microMIPS (r3) instruction.
474// It can be used only on instructions that doesn't inherit PredicateControl.
475class ISA_MICROMIPS_NOT_32R6 : PredicateControl {
476  let InsnPredicates = [NotMips32r6];
477  let EncodingPredicates = [InMicroMips];
478}
479
480class ASE_NOT_DSP {
481  list<Predicate> ASEPredicate = [NotDSP];
482}
483
484class MADD4 {
485  list<Predicate> AdditionalPredicates = [HasMadd4];
486}
487
488// Classses used for separating expansions that differ based on the ABI in
489// use.
490class ABI_N64 {
491  list<Predicate> AdditionalPredicates = [IsN64];
492}
493
494class ABI_NOT_N64 {
495  list<Predicate> AdditionalPredicates = [IsNotN64];
496}
497
498class FPOP_FUSION_FAST {
499  list <Predicate> AdditionalPredicates = [AllowFPOpFusion];
500}
501
502//===----------------------------------------------------------------------===//
503
504class MipsPat<dag pattern, dag result> : Pat<pattern, result>, PredicateControl;
505
506class MipsInstAlias<string Asm, dag Result, bit Emit = 0b1> :
507  InstAlias<Asm, Result, Emit>, PredicateControl;
508
509class IsCommutable {
510  bit isCommutable = 1;
511}
512
513class IsBranch {
514  bit isBranch = 1;
515  bit isCTI = 1;
516}
517
518class IsReturn {
519  bit isReturn = 1;
520  bit isCTI = 1;
521}
522
523class IsCall {
524  bit isCall = 1;
525  bit isCTI = 1;
526}
527
528class IsTailCall {
529  bit isCall = 1;
530  bit isTerminator = 1;
531  bit isReturn = 1;
532  bit isBarrier = 1;
533  bit hasExtraSrcRegAllocReq = 1;
534  bit isCodeGenOnly = 1;
535  bit isCTI = 1;
536}
537
538class IsAsCheapAsAMove {
539  bit isAsCheapAsAMove = 1;
540}
541
542class NeverHasSideEffects {
543  bit hasSideEffects = 0;
544}
545
546//===----------------------------------------------------------------------===//
547// Instruction format superclass
548//===----------------------------------------------------------------------===//
549
550include "MipsInstrFormats.td"
551
552//===----------------------------------------------------------------------===//
553// Mips Operand, Complex Patterns and Transformations Definitions.
554//===----------------------------------------------------------------------===//
555
556class ConstantSImmAsmOperandClass<int Bits, list<AsmOperandClass> Supers = [],
557                                  int Offset = 0> : AsmOperandClass {
558  let Name = "ConstantSImm" # Bits # "_" # Offset;
559  let RenderMethod = "addConstantSImmOperands<" # Bits # ", " # Offset # ">";
560  let PredicateMethod = "isConstantSImm<" # Bits # ", " # Offset # ">";
561  let SuperClasses = Supers;
562  let DiagnosticType = "SImm" # Bits # "_" # Offset;
563}
564
565class SimmLslAsmOperandClass<int Bits, list<AsmOperandClass> Supers = [],
566                                  int Shift = 0> : AsmOperandClass {
567  let Name = "Simm" # Bits # "_Lsl" # Shift;
568  let RenderMethod = "addImmOperands";
569  let PredicateMethod = "isScaledSImm<" # Bits # ", " # Shift # ">";
570  let SuperClasses = Supers;
571  let DiagnosticType = "SImm" # Bits # "_Lsl" # Shift;
572}
573
574class ConstantUImmAsmOperandClass<int Bits, list<AsmOperandClass> Supers = [],
575                                  int Offset = 0> : AsmOperandClass {
576  let Name = "ConstantUImm" # Bits # "_" # Offset;
577  let RenderMethod = "addConstantUImmOperands<" # Bits # ", " # Offset # ">";
578  let PredicateMethod = "isConstantUImm<" # Bits # ", " # Offset # ">";
579  let SuperClasses = Supers;
580  let DiagnosticType = "UImm" # Bits # "_" # Offset;
581}
582
583class ConstantUImmRangeAsmOperandClass<int Bottom, int Top,
584                                       list<AsmOperandClass> Supers = []>
585    : AsmOperandClass {
586  let Name = "ConstantUImmRange" # Bottom # "_" # Top;
587  let RenderMethod = "addImmOperands";
588  let PredicateMethod = "isConstantUImmRange<" # Bottom # ", " # Top # ">";
589  let SuperClasses = Supers;
590  let DiagnosticType = "UImmRange" # Bottom # "_" # Top;
591}
592
593class SImmAsmOperandClass<int Bits, list<AsmOperandClass> Supers = []>
594    : AsmOperandClass {
595  let Name = "SImm" # Bits;
596  let RenderMethod = "addSImmOperands<" # Bits # ">";
597  let PredicateMethod = "isSImm<" # Bits # ">";
598  let SuperClasses = Supers;
599  let DiagnosticType = "SImm" # Bits;
600}
601
602class UImmAsmOperandClass<int Bits, list<AsmOperandClass> Supers = []>
603    : AsmOperandClass {
604  let Name = "UImm" # Bits;
605  let RenderMethod = "addUImmOperands<" # Bits # ">";
606  let PredicateMethod = "isUImm<" # Bits # ">";
607  let SuperClasses = Supers;
608  let DiagnosticType = "UImm" # Bits;
609}
610
611// Generic case - only to support certain assembly pseudo instructions.
612class UImmAnyAsmOperandClass<int Bits, list<AsmOperandClass> Supers = []>
613    : AsmOperandClass {
614  let Name = "ImmAny";
615  let RenderMethod = "addConstantUImmOperands<32>";
616  let PredicateMethod = "isSImm<" # Bits # ">";
617  let SuperClasses = Supers;
618  let DiagnosticType = "ImmAny";
619}
620
621// AsmOperandClasses require a strict ordering which is difficult to manage
622// as a hierarchy. Instead, we use a linear ordering and impose an order that
623// is in some places arbitrary.
624//
625// Here the rules that are in use:
626// * Wider immediates are a superset of narrower immediates:
627//     uimm4 < uimm5 < uimm6
628// * For the same bit-width, unsigned immediates are a superset of signed
629//   immediates::
630//     simm4 < uimm4 < simm5 < uimm5
631// * For the same upper-bound, signed immediates are a superset of unsigned
632//   immediates:
633//     uimm3 < simm4 < uimm4 < simm4
634// * Modified immediates are a superset of ordinary immediates:
635//     uimm5 < uimm5_plus1 (1..32) < uimm5_plus32 (32..63) < uimm6
636//   The term 'superset' starts to break down here since the uimm5_plus* classes
637//   are not true supersets of uimm5 (but they are still subsets of uimm6).
638// * 'Relaxed' immediates are supersets of the corresponding unsigned immediate.
639//     uimm16 < uimm16_relaxed
640// * The codeGen pattern type is arbitrarily ordered.
641//     uimm5 < uimm5_64, and uimm5 < vsplat_uimm5
642//   This is entirely arbitrary. We need an ordering and what we pick is
643//   unimportant since only one is possible for a given mnemonic.
644
645def UImm32CoercedAsmOperandClass : UImmAnyAsmOperandClass<33, []> {
646  let Name = "UImm32_Coerced";
647  let DiagnosticType = "UImm32_Coerced";
648}
649def SImm32RelaxedAsmOperandClass
650    : SImmAsmOperandClass<32, [UImm32CoercedAsmOperandClass]> {
651  let Name = "SImm32_Relaxed";
652  let PredicateMethod = "isAnyImm<33>";
653  let DiagnosticType = "SImm32_Relaxed";
654}
655def SImm32AsmOperandClass
656    : SImmAsmOperandClass<32, [SImm32RelaxedAsmOperandClass]>;
657def ConstantUImm26AsmOperandClass
658    : ConstantUImmAsmOperandClass<26, [SImm32AsmOperandClass]>;
659def ConstantUImm20AsmOperandClass
660    : ConstantUImmAsmOperandClass<20, [ConstantUImm26AsmOperandClass]>;
661def ConstantSImm19Lsl2AsmOperandClass : AsmOperandClass {
662  let Name = "SImm19Lsl2";
663  let RenderMethod = "addImmOperands";
664  let PredicateMethod = "isScaledSImm<19, 2>";
665  let SuperClasses = [ConstantUImm20AsmOperandClass];
666  let DiagnosticType = "SImm19_Lsl2";
667}
668def UImm16RelaxedAsmOperandClass
669    : UImmAsmOperandClass<16, [ConstantUImm20AsmOperandClass]> {
670  let Name = "UImm16_Relaxed";
671  let PredicateMethod = "isAnyImm<16>";
672  let DiagnosticType = "UImm16_Relaxed";
673}
674// Similar to the relaxed classes which take an SImm and render it as
675// an UImm, this takes a UImm and renders it as an SImm.
676def UImm16AltRelaxedAsmOperandClass
677    : SImmAsmOperandClass<16, [UImm16RelaxedAsmOperandClass]> {
678  let Name = "UImm16_AltRelaxed";
679  let PredicateMethod = "isUImm<16>";
680  let DiagnosticType = "UImm16_AltRelaxed";
681}
682// FIXME: One of these should probably have UImm16AsmOperandClass as the
683//        superclass instead of UImm16RelaxedasmOPerandClass.
684def UImm16AsmOperandClass
685    : UImmAsmOperandClass<16, [UImm16RelaxedAsmOperandClass]>;
686def SImm16RelaxedAsmOperandClass
687    : SImmAsmOperandClass<16, [UImm16RelaxedAsmOperandClass]> {
688  let Name = "SImm16_Relaxed";
689  let PredicateMethod = "isAnyImm<16>";
690  let DiagnosticType = "SImm16_Relaxed";
691}
692def SImm16AsmOperandClass
693    : SImmAsmOperandClass<16, [SImm16RelaxedAsmOperandClass]>;
694def ConstantSImm10Lsl3AsmOperandClass : AsmOperandClass {
695  let Name = "SImm10Lsl3";
696  let RenderMethod = "addImmOperands";
697  let PredicateMethod = "isScaledSImm<10, 3>";
698  let SuperClasses = [SImm16AsmOperandClass];
699  let DiagnosticType = "SImm10_Lsl3";
700}
701def ConstantSImm10Lsl2AsmOperandClass : AsmOperandClass {
702  let Name = "SImm10Lsl2";
703  let RenderMethod = "addImmOperands";
704  let PredicateMethod = "isScaledSImm<10, 2>";
705  let SuperClasses = [ConstantSImm10Lsl3AsmOperandClass];
706  let DiagnosticType = "SImm10_Lsl2";
707}
708def ConstantSImm11AsmOperandClass
709    : ConstantSImmAsmOperandClass<11, [ConstantSImm10Lsl2AsmOperandClass]>;
710def ConstantSImm10Lsl1AsmOperandClass : AsmOperandClass {
711  let Name = "SImm10Lsl1";
712  let RenderMethod = "addImmOperands";
713  let PredicateMethod = "isScaledSImm<10, 1>";
714  let SuperClasses = [ConstantSImm11AsmOperandClass];
715  let DiagnosticType = "SImm10_Lsl1";
716}
717def ConstantUImm10AsmOperandClass
718    : ConstantUImmAsmOperandClass<10, [ConstantSImm10Lsl1AsmOperandClass]>;
719def ConstantSImm10AsmOperandClass
720    : ConstantSImmAsmOperandClass<10, [ConstantUImm10AsmOperandClass]>;
721def ConstantSImm9AsmOperandClass
722    : ConstantSImmAsmOperandClass<9, [ConstantSImm10AsmOperandClass]>;
723def ConstantSImm7Lsl2AsmOperandClass : AsmOperandClass {
724  let Name = "SImm7Lsl2";
725  let RenderMethod = "addImmOperands";
726  let PredicateMethod = "isScaledSImm<7, 2>";
727  let SuperClasses = [ConstantSImm9AsmOperandClass];
728  let DiagnosticType = "SImm7_Lsl2";
729}
730def ConstantUImm8AsmOperandClass
731    : ConstantUImmAsmOperandClass<8, [ConstantSImm7Lsl2AsmOperandClass]>;
732def ConstantUImm7Sub1AsmOperandClass
733    : ConstantUImmAsmOperandClass<7, [ConstantUImm8AsmOperandClass], -1> {
734  // Specify the names since the -1 offset causes invalid identifiers otherwise.
735  let Name = "UImm7_N1";
736  let DiagnosticType = "UImm7_N1";
737}
738def ConstantUImm7AsmOperandClass
739    : ConstantUImmAsmOperandClass<7, [ConstantUImm7Sub1AsmOperandClass]>;
740def ConstantUImm6Lsl2AsmOperandClass : AsmOperandClass {
741  let Name = "UImm6Lsl2";
742  let RenderMethod = "addImmOperands";
743  let PredicateMethod = "isScaledUImm<6, 2>";
744  let SuperClasses = [ConstantUImm7AsmOperandClass];
745  let DiagnosticType = "UImm6_Lsl2";
746}
747def ConstantUImm6AsmOperandClass
748    : ConstantUImmAsmOperandClass<6, [ConstantUImm6Lsl2AsmOperandClass]>;
749def ConstantSImm6AsmOperandClass
750    : ConstantSImmAsmOperandClass<6, [ConstantUImm6AsmOperandClass]>;
751def ConstantUImm5Lsl2AsmOperandClass : AsmOperandClass {
752  let Name = "UImm5Lsl2";
753  let RenderMethod = "addImmOperands";
754  let PredicateMethod = "isScaledUImm<5, 2>";
755  let SuperClasses = [ConstantSImm6AsmOperandClass];
756  let DiagnosticType = "UImm5_Lsl2";
757}
758def ConstantUImm5_Range2_64AsmOperandClass
759    : ConstantUImmRangeAsmOperandClass<2, 64, [ConstantUImm5Lsl2AsmOperandClass]>;
760def ConstantUImm5Plus33AsmOperandClass
761    : ConstantUImmAsmOperandClass<5, [ConstantUImm5_Range2_64AsmOperandClass],
762                                  33>;
763def ConstantUImm5ReportUImm6AsmOperandClass
764    : ConstantUImmAsmOperandClass<5, [ConstantUImm5Plus33AsmOperandClass]> {
765  let Name = "ConstantUImm5_0_Report_UImm6";
766  let DiagnosticType = "UImm5_0_Report_UImm6";
767}
768def ConstantUImm5Plus32AsmOperandClass
769    : ConstantUImmAsmOperandClass<
770          5, [ConstantUImm5ReportUImm6AsmOperandClass], 32>;
771def ConstantUImm5Plus32NormalizeAsmOperandClass
772    : ConstantUImmAsmOperandClass<5, [ConstantUImm5Plus32AsmOperandClass], 32> {
773  let Name = "ConstantUImm5_32_Norm";
774  // We must also subtract 32 when we render the operand.
775  let RenderMethod = "addConstantUImmOperands<5, 32, -32>";
776}
777def ConstantUImm5Plus1ReportUImm6AsmOperandClass
778    : ConstantUImmAsmOperandClass<
779          5, [ConstantUImm5Plus32NormalizeAsmOperandClass], 1>{
780  let Name = "ConstantUImm5_Plus1_Report_UImm6";
781}
782def ConstantUImm5Plus1AsmOperandClass
783    : ConstantUImmAsmOperandClass<
784          5, [ConstantUImm5Plus1ReportUImm6AsmOperandClass], 1>;
785def ConstantUImm5AsmOperandClass
786    : ConstantUImmAsmOperandClass<5, [ConstantUImm5Plus1AsmOperandClass]>;
787def ConstantSImm5AsmOperandClass
788    : ConstantSImmAsmOperandClass<5, [ConstantUImm5AsmOperandClass]>;
789def ConstantUImm4AsmOperandClass
790    : ConstantUImmAsmOperandClass<4, [ConstantSImm5AsmOperandClass]>;
791def ConstantSImm4AsmOperandClass
792    : ConstantSImmAsmOperandClass<4, [ConstantUImm4AsmOperandClass]>;
793def ConstantUImm3AsmOperandClass
794    : ConstantUImmAsmOperandClass<3, [ConstantSImm4AsmOperandClass]>;
795def ConstantUImm2Plus1AsmOperandClass
796    : ConstantUImmAsmOperandClass<2, [ConstantUImm3AsmOperandClass], 1>;
797def ConstantUImm2AsmOperandClass
798    : ConstantUImmAsmOperandClass<2, [ConstantUImm3AsmOperandClass]>;
799def ConstantUImm1AsmOperandClass
800    : ConstantUImmAsmOperandClass<1, [ConstantUImm2AsmOperandClass]>;
801def ConstantImmzAsmOperandClass : AsmOperandClass {
802  let Name = "ConstantImmz";
803  let RenderMethod = "addConstantUImmOperands<1>";
804  let PredicateMethod = "isConstantImmz";
805  let SuperClasses = [ConstantUImm1AsmOperandClass];
806  let DiagnosticType = "Immz";
807}
808
809def Simm19Lsl2AsmOperand
810    : SimmLslAsmOperandClass<19, [], 2>;
811
812def MipsJumpTargetAsmOperand : AsmOperandClass {
813  let Name = "JumpTarget";
814  let ParserMethod = "parseJumpTarget";
815  let PredicateMethod = "isImm";
816  let RenderMethod = "addImmOperands";
817}
818
819// Instruction operand types
820def jmptarget   : Operand<OtherVT> {
821  let EncoderMethod = "getJumpTargetOpValue";
822  let ParserMatchClass = MipsJumpTargetAsmOperand;
823}
824def brtarget    : Operand<OtherVT> {
825  let EncoderMethod = "getBranchTargetOpValue";
826  let OperandType = "OPERAND_PCREL";
827  let DecoderMethod = "DecodeBranchTarget";
828  let ParserMatchClass = MipsJumpTargetAsmOperand;
829}
830def brtarget1SImm16 : Operand<OtherVT> {
831  let EncoderMethod = "getBranchTargetOpValue1SImm16";
832  let OperandType = "OPERAND_PCREL";
833  let DecoderMethod = "DecodeBranchTarget1SImm16";
834  let ParserMatchClass = MipsJumpTargetAsmOperand;
835}
836def calltarget  : Operand<iPTR> {
837  let EncoderMethod = "getJumpTargetOpValue";
838  let ParserMatchClass = MipsJumpTargetAsmOperand;
839}
840
841def imm64: Operand<i64>;
842
843def simm19_lsl2 : Operand<i32> {
844  let EncoderMethod = "getSimm19Lsl2Encoding";
845  let DecoderMethod = "DecodeSimm19Lsl2";
846  let ParserMatchClass = Simm19Lsl2AsmOperand;
847}
848
849def simm18_lsl3 : Operand<i32> {
850  let EncoderMethod = "getSimm18Lsl3Encoding";
851  let DecoderMethod = "DecodeSimm18Lsl3";
852  let ParserMatchClass = MipsJumpTargetAsmOperand;
853}
854
855// Zero
856def uimmz       : Operand<i32> {
857  let PrintMethod = "printUImm<0>";
858  let ParserMatchClass = ConstantImmzAsmOperandClass;
859}
860
861// size operand of ins instruction
862def uimm_range_2_64 : Operand<i32> {
863  let PrintMethod = "printUImm<6, 2>";
864  let EncoderMethod = "getSizeInsEncoding";
865  let DecoderMethod = "DecodeInsSize";
866  let ParserMatchClass = ConstantUImm5_Range2_64AsmOperandClass;
867}
868
869// Unsigned Operands
870foreach I = {1, 2, 3, 4, 5, 6, 7, 8, 10, 20, 26} in
871  def uimm # I : Operand<i32> {
872    let PrintMethod = "printUImm<" # I # ">";
873    let ParserMatchClass =
874        !cast<AsmOperandClass>("ConstantUImm" # I # "AsmOperandClass");
875  }
876
877def uimm2_plus1 : Operand<i32> {
878  let PrintMethod = "printUImm<2, 1>";
879  let EncoderMethod = "getUImmWithOffsetEncoding<2, 1>";
880  let DecoderMethod = "DecodeUImmWithOffset<2, 1>";
881  let ParserMatchClass = ConstantUImm2Plus1AsmOperandClass;
882}
883
884def uimm5_plus1 : Operand<i32> {
885  let PrintMethod = "printUImm<5, 1>";
886  let EncoderMethod = "getUImmWithOffsetEncoding<5, 1>";
887  let DecoderMethod = "DecodeUImmWithOffset<5, 1>";
888  let ParserMatchClass = ConstantUImm5Plus1AsmOperandClass;
889}
890
891def uimm5_plus1_report_uimm6 : Operand<i32> {
892  let PrintMethod = "printUImm<6, 1>";
893  let EncoderMethod = "getUImmWithOffsetEncoding<5, 1>";
894  let DecoderMethod = "DecodeUImmWithOffset<5, 1>";
895  let ParserMatchClass = ConstantUImm5Plus1ReportUImm6AsmOperandClass;
896}
897
898def uimm5_plus32 : Operand<i32> {
899  let PrintMethod = "printUImm<5, 32>";
900  let ParserMatchClass = ConstantUImm5Plus32AsmOperandClass;
901}
902
903def uimm5_plus33 : Operand<i32> {
904  let PrintMethod = "printUImm<5, 33>";
905  let EncoderMethod = "getUImmWithOffsetEncoding<5, 1>";
906  let DecoderMethod = "DecodeUImmWithOffset<5, 1>";
907  let ParserMatchClass = ConstantUImm5Plus33AsmOperandClass;
908}
909
910def uimm5_inssize_plus1 : Operand<i32> {
911  let PrintMethod = "printUImm<6>";
912  let ParserMatchClass = ConstantUImm5Plus1AsmOperandClass;
913  let EncoderMethod = "getSizeInsEncoding";
914  let DecoderMethod = "DecodeInsSize";
915}
916
917def uimm5_plus32_normalize : Operand<i32> {
918  let PrintMethod = "printUImm<5>";
919  let ParserMatchClass = ConstantUImm5Plus32NormalizeAsmOperandClass;
920}
921
922def uimm5_lsl2 : Operand<OtherVT> {
923  let EncoderMethod = "getUImm5Lsl2Encoding";
924  let DecoderMethod = "DecodeUImmWithOffsetAndScale<5, 0, 4>";
925  let ParserMatchClass = ConstantUImm5Lsl2AsmOperandClass;
926}
927
928def uimm5_plus32_normalize_64 : Operand<i64> {
929  let PrintMethod = "printUImm<5>";
930  let ParserMatchClass = ConstantUImm5Plus32NormalizeAsmOperandClass;
931}
932
933def uimm6_lsl2 : Operand<OtherVT> {
934  let EncoderMethod = "getUImm6Lsl2Encoding";
935  let DecoderMethod = "DecodeUImmWithOffsetAndScale<6, 0, 4>";
936  let ParserMatchClass = ConstantUImm6Lsl2AsmOperandClass;
937}
938
939foreach I = {16} in
940  def uimm # I : Operand<i32> {
941    let PrintMethod = "printUImm<" # I # ">";
942    let ParserMatchClass =
943        !cast<AsmOperandClass>("UImm" # I # "AsmOperandClass");
944  }
945
946// Like uimm16_64 but coerces simm16 to uimm16.
947def uimm16_relaxed : Operand<i32> {
948  let PrintMethod = "printUImm<16>";
949  let ParserMatchClass =
950      !cast<AsmOperandClass>("UImm16RelaxedAsmOperandClass");
951}
952
953foreach I = {5} in
954  def uimm # I # _64 : Operand<i64> {
955    let PrintMethod = "printUImm<" # I # ">";
956    let ParserMatchClass =
957        !cast<AsmOperandClass>("ConstantUImm" # I # "AsmOperandClass");
958  }
959
960foreach I = {16} in
961  def uimm # I # _64 : Operand<i64> {
962    let PrintMethod = "printUImm<" # I # ">";
963    let ParserMatchClass =
964        !cast<AsmOperandClass>("UImm" # I # "AsmOperandClass");
965  }
966
967// Like uimm16_64 but coerces simm16 to uimm16.
968def uimm16_64_relaxed : Operand<i64> {
969  let PrintMethod = "printUImm<16>";
970  let ParserMatchClass =
971      !cast<AsmOperandClass>("UImm16RelaxedAsmOperandClass");
972}
973
974def uimm16_altrelaxed : Operand<i32> {
975  let PrintMethod = "printUImm<16>";
976  let ParserMatchClass =
977      !cast<AsmOperandClass>("UImm16AltRelaxedAsmOperandClass");
978}
979// Like uimm5 but reports a less confusing error for 32-63 when
980// an instruction alias permits that.
981def uimm5_report_uimm6 : Operand<i32> {
982  let PrintMethod = "printUImm<6>";
983  let ParserMatchClass = ConstantUImm5ReportUImm6AsmOperandClass;
984}
985
986// Like uimm5_64 but reports a less confusing error for 32-63 when
987// an instruction alias permits that.
988def uimm5_64_report_uimm6 : Operand<i64> {
989  let PrintMethod = "printUImm<5>";
990  let ParserMatchClass = ConstantUImm5ReportUImm6AsmOperandClass;
991}
992
993foreach I = {1, 2, 3, 4} in
994  def uimm # I # _ptr : Operand<iPTR> {
995    let PrintMethod = "printUImm<" # I # ">";
996    let ParserMatchClass =
997        !cast<AsmOperandClass>("ConstantUImm" # I # "AsmOperandClass");
998  }
999
1000foreach I = {1, 2, 3, 4, 5, 6, 8} in
1001  def vsplat_uimm # I : Operand<vAny> {
1002    let PrintMethod = "printUImm<" # I # ">";
1003    let ParserMatchClass =
1004        !cast<AsmOperandClass>("ConstantUImm" # I # "AsmOperandClass");
1005  }
1006
1007// Signed operands
1008foreach I = {4, 5, 6, 9, 10, 11} in
1009  def simm # I : Operand<i32> {
1010    let DecoderMethod = "DecodeSImmWithOffsetAndScale<" # I # ">";
1011    let ParserMatchClass =
1012        !cast<AsmOperandClass>("ConstantSImm" # I # "AsmOperandClass");
1013  }
1014
1015foreach I = {1, 2, 3} in
1016  def simm10_lsl # I : Operand<i32> {
1017    let DecoderMethod = "DecodeSImmWithOffsetAndScale<10, " # I # ">";
1018    let ParserMatchClass =
1019        !cast<AsmOperandClass>("ConstantSImm10Lsl" # I # "AsmOperandClass");
1020  }
1021
1022foreach I = {10} in
1023  def simm # I # _64 : Operand<i64> {
1024    let DecoderMethod = "DecodeSImmWithOffsetAndScale<" # I # ">";
1025    let ParserMatchClass =
1026        !cast<AsmOperandClass>("ConstantSImm" # I # "AsmOperandClass");
1027  }
1028
1029foreach I = {5, 10} in
1030  def vsplat_simm # I : Operand<vAny> {
1031    let ParserMatchClass =
1032        !cast<AsmOperandClass>("ConstantSImm" # I # "AsmOperandClass");
1033  }
1034
1035def simm7_lsl2 : Operand<OtherVT> {
1036  let EncoderMethod = "getSImm7Lsl2Encoding";
1037  let DecoderMethod = "DecodeSImmWithOffsetAndScale<" # I # ", 0, 4>";
1038  let ParserMatchClass = ConstantSImm7Lsl2AsmOperandClass;
1039}
1040
1041foreach I = {16, 32} in
1042  def simm # I : Operand<i32> {
1043    let DecoderMethod = "DecodeSImmWithOffsetAndScale<" # I # ">";
1044    let ParserMatchClass = !cast<AsmOperandClass>("SImm" # I # "AsmOperandClass");
1045  }
1046
1047// Like simm16 but coerces uimm16 to simm16.
1048def simm16_relaxed : Operand<i32> {
1049  let DecoderMethod = "DecodeSImmWithOffsetAndScale<16>";
1050  let ParserMatchClass = !cast<AsmOperandClass>("SImm16RelaxedAsmOperandClass");
1051}
1052
1053def simm16_64 : Operand<i64> {
1054  let DecoderMethod = "DecodeSImmWithOffsetAndScale<16>";
1055  let ParserMatchClass = !cast<AsmOperandClass>("SImm16AsmOperandClass");
1056}
1057
1058// like simm32 but coerces simm32 to uimm32.
1059def uimm32_coerced : Operand<i32> {
1060  let ParserMatchClass = !cast<AsmOperandClass>("UImm32CoercedAsmOperandClass");
1061}
1062// Like simm32 but coerces uimm32 to simm32.
1063def simm32_relaxed : Operand<i32> {
1064  let DecoderMethod = "DecodeSImmWithOffsetAndScale<32>";
1065  let ParserMatchClass = !cast<AsmOperandClass>("SImm32RelaxedAsmOperandClass");
1066}
1067
1068// This is almost the same as a uimm7 but 0x7f is interpreted as -1.
1069def li16_imm : Operand<i32> {
1070  let DecoderMethod = "DecodeLi16Imm";
1071  let ParserMatchClass = ConstantUImm7Sub1AsmOperandClass;
1072}
1073
1074def MipsMemAsmOperand : AsmOperandClass {
1075  let Name = "Mem";
1076  let ParserMethod = "parseMemOperand";
1077}
1078
1079def MipsMemSimm9AsmOperand : AsmOperandClass {
1080  let Name = "MemOffsetSimm9";
1081  let SuperClasses = [MipsMemAsmOperand];
1082  let RenderMethod = "addMemOperands";
1083  let ParserMethod = "parseMemOperand";
1084  let PredicateMethod = "isMemWithSimmOffset<9>";
1085  let DiagnosticType = "MemSImm9";
1086}
1087
1088def MipsMemSimm10AsmOperand : AsmOperandClass {
1089  let Name = "MemOffsetSimm10";
1090  let SuperClasses = [MipsMemAsmOperand];
1091  let RenderMethod = "addMemOperands";
1092  let ParserMethod = "parseMemOperand";
1093  let PredicateMethod = "isMemWithSimmOffset<10>";
1094  let DiagnosticType = "MemSImm10";
1095}
1096
1097def MipsMemSimm12AsmOperand : AsmOperandClass {
1098  let Name = "MemOffsetSimm12";
1099  let SuperClasses = [MipsMemAsmOperand];
1100  let RenderMethod = "addMemOperands";
1101  let ParserMethod = "parseMemOperand";
1102  let PredicateMethod = "isMemWithSimmOffset<12>";
1103  let DiagnosticType = "MemSImm12";
1104}
1105
1106foreach I = {1, 2, 3} in
1107  def MipsMemSimm10Lsl # I # AsmOperand : AsmOperandClass {
1108    let Name = "MemOffsetSimm10_" # I;
1109    let SuperClasses = [MipsMemAsmOperand];
1110    let RenderMethod = "addMemOperands";
1111    let ParserMethod = "parseMemOperand";
1112    let PredicateMethod = "isMemWithSimmOffset<10, " # I # ">";
1113    let DiagnosticType = "MemSImm10Lsl" # I;
1114  }
1115
1116def MipsMemSimm11AsmOperand : AsmOperandClass {
1117  let Name = "MemOffsetSimm11";
1118  let SuperClasses = [MipsMemAsmOperand];
1119  let RenderMethod = "addMemOperands";
1120  let ParserMethod = "parseMemOperand";
1121  let PredicateMethod = "isMemWithSimmOffset<11>";
1122  let DiagnosticType = "MemSImm11";
1123}
1124
1125def MipsMemSimm16AsmOperand : AsmOperandClass {
1126  let Name = "MemOffsetSimm16";
1127  let SuperClasses = [MipsMemAsmOperand];
1128  let RenderMethod = "addMemOperands";
1129  let ParserMethod = "parseMemOperand";
1130  let PredicateMethod = "isMemWithSimmOffset<16>";
1131  let DiagnosticType = "MemSImm16";
1132}
1133
1134def MipsMemSimmPtrAsmOperand : AsmOperandClass {
1135  let Name = "MemOffsetSimmPtr";
1136  let SuperClasses = [MipsMemAsmOperand];
1137  let RenderMethod = "addMemOperands";
1138  let ParserMethod = "parseMemOperand";
1139  let PredicateMethod = "isMemWithPtrSizeOffset";
1140  let DiagnosticType = "MemSImmPtr";
1141}
1142
1143def MipsInvertedImmoperand : AsmOperandClass {
1144  let Name = "InvNum";
1145  let RenderMethod = "addImmOperands";
1146  let ParserMethod = "parseInvNum";
1147}
1148
1149def InvertedImOperand : Operand<i32> {
1150  let ParserMatchClass = MipsInvertedImmoperand;
1151}
1152
1153def InvertedImOperand64 : Operand<i64> {
1154  let ParserMatchClass = MipsInvertedImmoperand;
1155}
1156
1157class mem_generic : Operand<iPTR> {
1158  let PrintMethod = "printMemOperand";
1159  let MIOperandInfo = (ops ptr_rc, simm16);
1160  let EncoderMethod = "getMemEncoding";
1161  let ParserMatchClass = MipsMemAsmOperand;
1162  let OperandType = "OPERAND_MEMORY";
1163}
1164
1165// Address operand
1166def mem : mem_generic;
1167
1168// MSA specific address operand
1169def mem_msa : mem_generic {
1170  let MIOperandInfo = (ops ptr_rc, simm10);
1171  let EncoderMethod = "getMSAMemEncoding";
1172}
1173
1174def simm12 : Operand<i32> {
1175  let DecoderMethod = "DecodeSimm12";
1176}
1177
1178def mem_simm9 : mem_generic {
1179  let MIOperandInfo = (ops ptr_rc, simm9);
1180  let EncoderMethod = "getMemEncoding";
1181  let ParserMatchClass = MipsMemSimm9AsmOperand;
1182}
1183
1184def mem_simm10 : mem_generic {
1185  let MIOperandInfo = (ops ptr_rc, simm10);
1186  let EncoderMethod = "getMemEncoding";
1187  let ParserMatchClass = MipsMemSimm10AsmOperand;
1188}
1189
1190foreach I = {1, 2, 3} in
1191  def mem_simm10_lsl # I : mem_generic {
1192    let MIOperandInfo = (ops ptr_rc, !cast<Operand>("simm10_lsl" # I));
1193    let EncoderMethod = "getMemEncoding<" # I  # ">";
1194    let ParserMatchClass =
1195            !cast<AsmOperandClass>("MipsMemSimm10Lsl" # I # "AsmOperand");
1196  }
1197
1198def mem_simm11 : mem_generic {
1199  let MIOperandInfo = (ops ptr_rc, simm11);
1200  let EncoderMethod = "getMemEncoding";
1201  let ParserMatchClass = MipsMemSimm11AsmOperand;
1202}
1203
1204def mem_simm12 : mem_generic {
1205  let MIOperandInfo = (ops ptr_rc, simm12);
1206  let EncoderMethod = "getMemEncoding";
1207  let ParserMatchClass = MipsMemSimm12AsmOperand;
1208}
1209
1210def mem_simm16 : mem_generic {
1211  let MIOperandInfo = (ops ptr_rc, simm16);
1212  let EncoderMethod = "getMemEncoding";
1213  let ParserMatchClass = MipsMemSimm16AsmOperand;
1214}
1215
1216def mem_simmptr : mem_generic {
1217  let ParserMatchClass = MipsMemSimmPtrAsmOperand;
1218}
1219
1220def mem_ea : Operand<iPTR> {
1221  let PrintMethod = "printMemOperandEA";
1222  let MIOperandInfo = (ops ptr_rc, simm16);
1223  let EncoderMethod = "getMemEncoding";
1224  let OperandType = "OPERAND_MEMORY";
1225}
1226
1227def PtrRC : Operand<iPTR> {
1228  let MIOperandInfo = (ops ptr_rc);
1229  let DecoderMethod = "DecodePtrRegisterClass";
1230  let ParserMatchClass = GPR32AsmOperand;
1231}
1232
1233// size operand of ins instruction
1234def size_ins : Operand<i32> {
1235  let EncoderMethod = "getSizeInsEncoding";
1236  let DecoderMethod = "DecodeInsSize";
1237}
1238
1239// Transformation Function - get the lower 16 bits.
1240def LO16 : SDNodeXForm<imm, [{
1241  return getImm(N, N->getZExtValue() & 0xFFFF);
1242}]>;
1243
1244// Transformation Function - get the higher 16 bits.
1245def HI16 : SDNodeXForm<imm, [{
1246  return getImm(N, (N->getZExtValue() >> 16) & 0xFFFF);
1247}]>;
1248
1249// Plus 1.
1250def Plus1 : SDNodeXForm<imm, [{ return getImm(N, N->getSExtValue() + 1); }]>;
1251
1252// Node immediate is zero (e.g. insve.d)
1253def immz : PatLeaf<(imm), [{ return N->getSExtValue() == 0; }]>;
1254
1255// Node immediate fits as 16-bit sign extended on target immediate.
1256// e.g. addi, andi
1257def immSExt8  : PatLeaf<(imm), [{ return isInt<8>(N->getSExtValue()); }]>;
1258
1259// Node immediate fits as 16-bit sign extended on target immediate.
1260// e.g. addi, andi
1261def immSExt16  : PatLeaf<(imm), [{ return isInt<16>(N->getSExtValue()); }]>;
1262
1263// Node immediate fits as 7-bit zero extended on target immediate.
1264def immZExt7 : PatLeaf<(imm), [{ return isUInt<7>(N->getZExtValue()); }]>;
1265
1266// Node immediate fits as 16-bit zero extended on target immediate.
1267// The LO16 param means that only the lower 16 bits of the node
1268// immediate are caught.
1269// e.g. addiu, sltiu
1270def immZExt16  : PatLeaf<(imm), [{
1271  if (N->getValueType(0) == MVT::i32)
1272    return (uint32_t)N->getZExtValue() == (unsigned short)N->getZExtValue();
1273  else
1274    return (uint64_t)N->getZExtValue() == (unsigned short)N->getZExtValue();
1275}], LO16>;
1276
1277// Immediate can be loaded with LUi (32-bit int with lower 16-bit cleared).
1278def immSExt32Low16Zero : PatLeaf<(imm), [{
1279  int64_t Val = N->getSExtValue();
1280  return isInt<32>(Val) && !(Val & 0xffff);
1281}]>;
1282
1283// Zero-extended 32-bit unsigned int with lower 16-bit cleared.
1284def immZExt32Low16Zero : PatLeaf<(imm), [{
1285  uint64_t Val = N->getZExtValue();
1286  return isUInt<32>(Val) && !(Val & 0xffff);
1287}]>;
1288
1289// Note immediate fits as a 32 bit signed extended on target immediate.
1290def immSExt32  : PatLeaf<(imm), [{ return isInt<32>(N->getSExtValue()); }]>;
1291
1292// Note immediate fits as a 32 bit zero extended on target immediate.
1293def immZExt32  : PatLeaf<(imm), [{ return isUInt<32>(N->getZExtValue()); }]>;
1294
1295// shamt field must fit in 5 bits.
1296def immZExt5 : ImmLeaf<i32, [{return Imm == (Imm & 0x1f);}]>;
1297
1298def immZExt5Plus1 : PatLeaf<(imm), [{
1299  return isUInt<5>(N->getZExtValue() - 1);
1300}]>;
1301def immZExt5Plus32 : PatLeaf<(imm), [{
1302  return isUInt<5>(N->getZExtValue() - 32);
1303}]>;
1304def immZExt5Plus33 : PatLeaf<(imm), [{
1305  return isUInt<5>(N->getZExtValue() - 33);
1306}]>;
1307
1308def immZExt5To31 : SDNodeXForm<imm, [{
1309  return getImm(N, 31 - N->getZExtValue());
1310}]>;
1311
1312// True if (N + 1) fits in 16-bit field.
1313def immSExt16Plus1 : PatLeaf<(imm), [{
1314  return isInt<17>(N->getSExtValue()) && isInt<16>(N->getSExtValue() + 1);
1315}]>;
1316
1317def immZExtRange2To64 : PatLeaf<(imm), [{
1318  return isUInt<7>(N->getZExtValue()) && (N->getZExtValue() >= 2) &&
1319         (N->getZExtValue() <= 64);
1320}]>;
1321
1322def ORiPred  : PatLeaf<(imm), [{
1323  return isUInt<16>(N->getZExtValue()) && !isInt<16>(N->getSExtValue());
1324}], LO16>;
1325
1326def LUiPred : PatLeaf<(imm), [{
1327  int64_t Val = N->getSExtValue();
1328  return !isInt<16>(Val) && isInt<32>(Val) && !(Val & 0xffff);
1329}]>;
1330
1331def LUiORiPred  : PatLeaf<(imm), [{
1332  int64_t SVal = N->getSExtValue();
1333  return isInt<32>(SVal) && (SVal & 0xffff);
1334}]>;
1335
1336// Mips Address Mode! SDNode frameindex could possibily be a match
1337// since load and store instructions from stack used it.
1338def addr :
1339  ComplexPattern<iPTR, 2, "selectIntAddr", [frameindex]>;
1340
1341def addrRegImm :
1342  ComplexPattern<iPTR, 2, "selectAddrRegImm", [frameindex]>;
1343
1344def addrDefault :
1345  ComplexPattern<iPTR, 2, "selectAddrDefault", [frameindex]>;
1346
1347def addrimm10 : ComplexPattern<iPTR, 2, "selectIntAddrSImm10", [frameindex]>;
1348def addrimm10lsl1 : ComplexPattern<iPTR, 2, "selectIntAddrSImm10Lsl1",
1349                                   [frameindex]>;
1350def addrimm10lsl2 : ComplexPattern<iPTR, 2, "selectIntAddrSImm10Lsl2",
1351                                   [frameindex]>;
1352def addrimm10lsl3 : ComplexPattern<iPTR, 2, "selectIntAddrSImm10Lsl3",
1353                                   [frameindex]>;
1354
1355//===----------------------------------------------------------------------===//
1356// Instructions specific format
1357//===----------------------------------------------------------------------===//
1358
1359// Arithmetic and logical instructions with 3 register operands.
1360class ArithLogicR<string opstr, RegisterOperand RO, bit isComm = 0,
1361                  InstrItinClass Itin = NoItinerary,
1362                  SDPatternOperator OpNode = null_frag>:
1363  InstSE<(outs RO:$rd), (ins RO:$rs, RO:$rt),
1364         !strconcat(opstr, "\t$rd, $rs, $rt"),
1365         [(set RO:$rd, (OpNode RO:$rs, RO:$rt))], Itin, FrmR, opstr> {
1366  let isCommutable = isComm;
1367  let isReMaterializable = 1;
1368  let TwoOperandAliasConstraint = "$rd = $rs";
1369}
1370
1371// Arithmetic and logical instructions with 2 register operands.
1372class ArithLogicI<string opstr, Operand Od, RegisterOperand RO,
1373                  InstrItinClass Itin = NoItinerary,
1374                  SDPatternOperator imm_type = null_frag,
1375                  SDPatternOperator OpNode = null_frag> :
1376  InstSE<(outs RO:$rt), (ins RO:$rs, Od:$imm16),
1377         !strconcat(opstr, "\t$rt, $rs, $imm16"),
1378         [(set RO:$rt, (OpNode RO:$rs, imm_type:$imm16))],
1379         Itin, FrmI, opstr> {
1380  let isReMaterializable = 1;
1381  let TwoOperandAliasConstraint = "$rs = $rt";
1382}
1383
1384// Arithmetic Multiply ADD/SUB
1385class MArithR<string opstr, InstrItinClass itin, bit isComm = 0> :
1386  InstSE<(outs), (ins GPR32Opnd:$rs, GPR32Opnd:$rt),
1387         !strconcat(opstr, "\t$rs, $rt"), [], itin, FrmR, opstr> {
1388  let Defs = [HI0, LO0];
1389  let Uses = [HI0, LO0];
1390  let isCommutable = isComm;
1391}
1392
1393//  Logical
1394class LogicNOR<string opstr, RegisterOperand RO>:
1395  InstSE<(outs RO:$rd), (ins RO:$rs, RO:$rt),
1396         !strconcat(opstr, "\t$rd, $rs, $rt"),
1397         [(set RO:$rd, (not (or RO:$rs, RO:$rt)))], II_NOR, FrmR, opstr> {
1398  let isCommutable = 1;
1399}
1400
1401// Shifts
1402class shift_rotate_imm<string opstr, Operand ImmOpnd,
1403                       RegisterOperand RO, InstrItinClass itin,
1404                       SDPatternOperator OpNode = null_frag,
1405                       SDPatternOperator PF = null_frag> :
1406  InstSE<(outs RO:$rd), (ins RO:$rt, ImmOpnd:$shamt),
1407         !strconcat(opstr, "\t$rd, $rt, $shamt"),
1408         [(set RO:$rd, (OpNode RO:$rt, PF:$shamt))], itin, FrmR, opstr> {
1409  let TwoOperandAliasConstraint = "$rt = $rd";
1410}
1411
1412class shift_rotate_reg<string opstr, RegisterOperand RO, InstrItinClass itin,
1413                       SDPatternOperator OpNode = null_frag>:
1414  InstSE<(outs RO:$rd), (ins RO:$rt, GPR32Opnd:$rs),
1415         !strconcat(opstr, "\t$rd, $rt, $rs"),
1416         [(set RO:$rd, (OpNode RO:$rt, GPR32Opnd:$rs))], itin, FrmR,
1417         opstr>;
1418
1419// Load Upper Immediate
1420class LoadUpper<string opstr, RegisterOperand RO, Operand Imm>:
1421  InstSE<(outs RO:$rt), (ins Imm:$imm16), !strconcat(opstr, "\t$rt, $imm16"),
1422         [], II_LUI, FrmI, opstr>, IsAsCheapAsAMove {
1423  let hasSideEffects = 0;
1424  let isReMaterializable = 1;
1425}
1426
1427// Memory Load/Store
1428class LoadMemory<string opstr, DAGOperand RO, DAGOperand MO,
1429                 SDPatternOperator OpNode = null_frag,
1430                 InstrItinClass Itin = NoItinerary,
1431                 ComplexPattern Addr = addr> :
1432  InstSE<(outs RO:$rt), (ins MO:$addr), !strconcat(opstr, "\t$rt, $addr"),
1433         [(set RO:$rt, (OpNode Addr:$addr))], Itin, FrmI, opstr> {
1434  let DecoderMethod = "DecodeMem";
1435  let canFoldAsLoad = 1;
1436  string BaseOpcode = opstr;
1437  let mayLoad = 1;
1438}
1439
1440class Load<string opstr, DAGOperand RO, SDPatternOperator OpNode = null_frag,
1441           InstrItinClass Itin = NoItinerary, ComplexPattern Addr = addr> :
1442  LoadMemory<opstr, RO, mem, OpNode, Itin, Addr>;
1443
1444class StoreMemory<string opstr, DAGOperand RO, DAGOperand MO,
1445            SDPatternOperator OpNode = null_frag,
1446            InstrItinClass Itin = NoItinerary, ComplexPattern Addr = addr> :
1447  InstSE<(outs), (ins RO:$rt, MO:$addr), !strconcat(opstr, "\t$rt, $addr"),
1448         [(OpNode RO:$rt, Addr:$addr)], Itin, FrmI, opstr> {
1449  let DecoderMethod = "DecodeMem";
1450  string BaseOpcode = opstr;
1451  let mayStore = 1;
1452}
1453
1454class Store<string opstr, DAGOperand RO, SDPatternOperator OpNode = null_frag,
1455            InstrItinClass Itin = NoItinerary, ComplexPattern Addr = addr,
1456            DAGOperand MO = mem> :
1457  StoreMemory<opstr, RO, MO, OpNode, Itin, Addr>;
1458
1459// Load/Store Left/Right
1460let canFoldAsLoad = 1 in
1461class LoadLeftRight<string opstr, SDNode OpNode, RegisterOperand RO,
1462                    InstrItinClass Itin> :
1463  InstSE<(outs RO:$rt), (ins mem:$addr, RO:$src),
1464         !strconcat(opstr, "\t$rt, $addr"),
1465         [(set RO:$rt, (OpNode addr:$addr, RO:$src))], Itin, FrmI> {
1466  let DecoderMethod = "DecodeMem";
1467  string Constraints = "$src = $rt";
1468  let BaseOpcode = opstr;
1469}
1470
1471class StoreLeftRight<string opstr, SDNode OpNode, RegisterOperand RO,
1472                     InstrItinClass Itin> :
1473  InstSE<(outs), (ins RO:$rt, mem:$addr), !strconcat(opstr, "\t$rt, $addr"),
1474         [(OpNode RO:$rt, addr:$addr)], Itin, FrmI> {
1475  let DecoderMethod = "DecodeMem";
1476  let BaseOpcode = opstr;
1477}
1478
1479// COP2 Load/Store
1480class LW_FT2<string opstr, RegisterOperand RC, InstrItinClass Itin,
1481             SDPatternOperator OpNode= null_frag> :
1482  InstSE<(outs RC:$rt), (ins mem_simm16:$addr),
1483         !strconcat(opstr, "\t$rt, $addr"),
1484         [(set RC:$rt, (OpNode addrDefault:$addr))], Itin, FrmFI, opstr> {
1485  let DecoderMethod = "DecodeFMem2";
1486  let mayLoad = 1;
1487}
1488
1489class SW_FT2<string opstr, RegisterOperand RC, InstrItinClass Itin,
1490             SDPatternOperator OpNode= null_frag> :
1491  InstSE<(outs), (ins RC:$rt, mem_simm16:$addr),
1492         !strconcat(opstr, "\t$rt, $addr"),
1493         [(OpNode RC:$rt, addrDefault:$addr)], Itin, FrmFI, opstr> {
1494  let DecoderMethod = "DecodeFMem2";
1495  let mayStore = 1;
1496}
1497
1498// COP3 Load/Store
1499class LW_FT3<string opstr, RegisterOperand RC, InstrItinClass Itin,
1500             SDPatternOperator OpNode= null_frag> :
1501  InstSE<(outs RC:$rt), (ins mem:$addr), !strconcat(opstr, "\t$rt, $addr"),
1502         [(set RC:$rt, (OpNode addrDefault:$addr))], Itin, FrmFI, opstr> {
1503  let DecoderMethod = "DecodeFMem3";
1504  let mayLoad = 1;
1505}
1506
1507class SW_FT3<string opstr, RegisterOperand RC, InstrItinClass Itin,
1508             SDPatternOperator OpNode= null_frag> :
1509  InstSE<(outs), (ins RC:$rt, mem:$addr), !strconcat(opstr, "\t$rt, $addr"),
1510         [(OpNode RC:$rt, addrDefault:$addr)], Itin, FrmFI, opstr> {
1511  let DecoderMethod = "DecodeFMem3";
1512  let mayStore = 1;
1513}
1514
1515// Conditional Branch
1516class CBranch<string opstr, DAGOperand opnd, PatFrag cond_op,
1517              RegisterOperand RO> :
1518  InstSE<(outs), (ins RO:$rs, RO:$rt, opnd:$offset),
1519         !strconcat(opstr, "\t$rs, $rt, $offset"),
1520         [(brcond (i32 (cond_op RO:$rs, RO:$rt)), bb:$offset)], II_BCC,
1521         FrmI, opstr> {
1522  let isBranch = 1;
1523  let isTerminator = 1;
1524  let hasDelaySlot = 1;
1525  let Defs = [AT];
1526  bit isCTI = 1;
1527}
1528
1529class CBranchLikely<string opstr, DAGOperand opnd, RegisterOperand RO> :
1530  InstSE<(outs), (ins RO:$rs, RO:$rt, opnd:$offset),
1531         !strconcat(opstr, "\t$rs, $rt, $offset"), [], II_BCC, FrmI, opstr> {
1532  let isBranch = 1;
1533  let isTerminator = 1;
1534  let hasDelaySlot = 1;
1535  let Defs = [AT];
1536  bit isCTI = 1;
1537}
1538
1539class CBranchZero<string opstr, DAGOperand opnd, PatFrag cond_op,
1540                  RegisterOperand RO> :
1541  InstSE<(outs), (ins RO:$rs, opnd:$offset),
1542         !strconcat(opstr, "\t$rs, $offset"),
1543         [(brcond (i32 (cond_op RO:$rs, 0)), bb:$offset)], II_BCCZ,
1544         FrmI, opstr> {
1545  let isBranch = 1;
1546  let isTerminator = 1;
1547  let hasDelaySlot = 1;
1548  let Defs = [AT];
1549  bit isCTI = 1;
1550}
1551
1552class CBranchZeroLikely<string opstr, DAGOperand opnd, RegisterOperand RO> :
1553  InstSE<(outs), (ins RO:$rs, opnd:$offset),
1554         !strconcat(opstr, "\t$rs, $offset"), [], II_BCCZ, FrmI, opstr> {
1555  let isBranch = 1;
1556  let isTerminator = 1;
1557  let hasDelaySlot = 1;
1558  let Defs = [AT];
1559  bit isCTI = 1;
1560}
1561
1562// SetCC
1563class SetCC_R<string opstr, PatFrag cond_op, RegisterOperand RO> :
1564  InstSE<(outs GPR32Opnd:$rd), (ins RO:$rs, RO:$rt),
1565         !strconcat(opstr, "\t$rd, $rs, $rt"),
1566         [(set GPR32Opnd:$rd, (cond_op RO:$rs, RO:$rt))],
1567         II_SLT_SLTU, FrmR, opstr>;
1568
1569class SetCC_I<string opstr, PatFrag cond_op, Operand Od, PatLeaf imm_type,
1570              RegisterOperand RO>:
1571  InstSE<(outs GPR32Opnd:$rt), (ins RO:$rs, Od:$imm16),
1572         !strconcat(opstr, "\t$rt, $rs, $imm16"),
1573         [(set GPR32Opnd:$rt, (cond_op RO:$rs, imm_type:$imm16))],
1574         II_SLTI_SLTIU, FrmI, opstr>;
1575
1576// Jump
1577class JumpFJ<DAGOperand opnd, string opstr, SDPatternOperator operator,
1578             SDPatternOperator targetoperator, string bopstr> :
1579  InstSE<(outs), (ins opnd:$target), !strconcat(opstr, "\t$target"),
1580         [(operator targetoperator:$target)], II_J, FrmJ, bopstr> {
1581  let isTerminator=1;
1582  let isBarrier=1;
1583  let hasDelaySlot = 1;
1584  let DecoderMethod = "DecodeJumpTarget";
1585  let Defs = [AT];
1586  bit isCTI = 1;
1587}
1588
1589// Unconditional branch
1590class UncondBranch<Instruction BEQInst, DAGOperand opnd> :
1591  PseudoSE<(outs), (ins brtarget:$offset), [(br bb:$offset)], II_B>,
1592  PseudoInstExpansion<(BEQInst ZERO, ZERO, opnd:$offset)> {
1593  let isBranch = 1;
1594  let isTerminator = 1;
1595  let isBarrier = 1;
1596  let hasDelaySlot = 1;
1597  let AdditionalPredicates = [RelocPIC];
1598  let Defs = [AT];
1599  bit isCTI = 1;
1600}
1601
1602// Base class for indirect branch and return instruction classes.
1603let isTerminator=1, isBarrier=1, hasDelaySlot = 1, isCTI = 1 in
1604class JumpFR<string opstr, RegisterOperand RO,
1605             SDPatternOperator operator = null_frag>:
1606  InstSE<(outs), (ins RO:$rs), "jr\t$rs", [(operator RO:$rs)], II_JR,
1607         FrmR, opstr>;
1608
1609// Indirect branch
1610class IndirectBranch<string opstr, RegisterOperand RO> : JumpFR<opstr, RO> {
1611  let isBranch = 1;
1612  let isIndirectBranch = 1;
1613}
1614
1615// Jump and Link (Call)
1616let isCall=1, hasDelaySlot=1, isCTI=1, Defs = [RA] in {
1617  class JumpLink<string opstr, DAGOperand opnd> :
1618    InstSE<(outs), (ins opnd:$target), !strconcat(opstr, "\t$target"),
1619           [(MipsJmpLink tglobaladdr:$target)], II_JAL, FrmJ, opstr> {
1620    let DecoderMethod = "DecodeJumpTarget";
1621  }
1622
1623  class JumpLinkRegPseudo<RegisterOperand RO, Instruction JALRInst,
1624                          Register RetReg, RegisterOperand ResRO = RO>:
1625    PseudoSE<(outs), (ins RO:$rs), [(MipsJmpLink RO:$rs)], II_JALR>,
1626    PseudoInstExpansion<(JALRInst RetReg, ResRO:$rs)>;
1627
1628  class JumpLinkReg<string opstr, RegisterOperand RO>:
1629    InstSE<(outs RO:$rd), (ins RO:$rs), !strconcat(opstr, "\t$rd, $rs"),
1630           [], II_JALR, FrmR, opstr>;
1631
1632  class BGEZAL_FT<string opstr, DAGOperand opnd,
1633                  RegisterOperand RO> :
1634    InstSE<(outs), (ins RO:$rs, opnd:$offset),
1635           !strconcat(opstr, "\t$rs, $offset"), [], II_BCCZAL, FrmI, opstr> {
1636    let hasDelaySlot = 1;
1637  }
1638
1639}
1640
1641let isCall = 1, isTerminator = 1, isReturn = 1, isBarrier = 1, hasDelaySlot = 1,
1642    hasExtraSrcRegAllocReq = 1, isCTI = 1, Defs = [AT] in {
1643  class TailCall<Instruction JumpInst, DAGOperand Opnd> :
1644    PseudoSE<(outs), (ins calltarget:$target), [], II_J>,
1645    PseudoInstExpansion<(JumpInst Opnd:$target)>;
1646
1647  class TailCallReg<Instruction JumpInst, RegisterOperand RO> :
1648    PseudoSE<(outs), (ins RO:$rs), [(MipsTailCall RO:$rs)], II_JR>,
1649    PseudoInstExpansion<(JumpInst RO:$rs)>;
1650}
1651
1652class BAL_BR_Pseudo<Instruction RealInst, DAGOperand opnd> :
1653  PseudoSE<(outs), (ins opnd:$offset), [], II_BCCZAL>,
1654  PseudoInstExpansion<(RealInst ZERO, opnd:$offset)> {
1655  let isBranch = 1;
1656  let isTerminator = 1;
1657  let isBarrier = 1;
1658  let hasDelaySlot = 1;
1659  let Defs = [RA];
1660  bit isCTI = 1;
1661}
1662
1663let isCTI = 1 in {
1664// Syscall
1665class SYS_FT<string opstr, Operand ImmOp, InstrItinClass itin = NoItinerary> :
1666  InstSE<(outs), (ins ImmOp:$code_),
1667         !strconcat(opstr, "\t$code_"), [], itin, FrmI, opstr>;
1668// Break
1669class BRK_FT<string opstr> :
1670  InstSE<(outs), (ins uimm10:$code_1, uimm10:$code_2),
1671         !strconcat(opstr, "\t$code_1, $code_2"), [], II_BREAK,
1672         FrmOther, opstr>;
1673
1674// (D)Eret
1675class ER_FT<string opstr, InstrItinClass itin = NoItinerary> :
1676  InstSE<(outs), (ins),
1677         opstr, [], itin, FrmOther, opstr>;
1678
1679// Wait
1680class WAIT_FT<string opstr> :
1681  InstSE<(outs), (ins), opstr, [], II_WAIT, FrmOther, opstr>;
1682}
1683
1684// Interrupts
1685class DEI_FT<string opstr, RegisterOperand RO,
1686             InstrItinClass itin = NoItinerary> :
1687  InstSE<(outs RO:$rt), (ins),
1688         !strconcat(opstr, "\t$rt"), [], itin, FrmOther, opstr>;
1689
1690// Sync
1691let hasSideEffects = 1 in
1692class SYNC_FT<string opstr> :
1693  InstSE<(outs), (ins uimm5:$stype), "sync $stype",
1694         [(MipsSync immZExt5:$stype)], II_SYNC, FrmOther, opstr>;
1695
1696class SYNCI_FT<string opstr, DAGOperand MO> :
1697  InstSE<(outs), (ins MO:$addr), !strconcat(opstr, "\t$addr"), [],
1698         II_SYNCI, FrmOther, opstr> {
1699  let hasSideEffects = 1;
1700  let DecoderMethod = "DecodeSyncI";
1701}
1702
1703let hasSideEffects = 1, isCTI = 1 in {
1704class TEQ_FT<string opstr, RegisterOperand RO, Operand ImmOp,
1705             InstrItinClass itin = NoItinerary> :
1706  InstSE<(outs), (ins RO:$rs, RO:$rt, ImmOp:$code_),
1707         !strconcat(opstr, "\t$rs, $rt, $code_"), [], itin, FrmI, opstr>;
1708
1709class TEQI_FT<string opstr, RegisterOperand RO,
1710              InstrItinClass itin = NoItinerary> :
1711  InstSE<(outs), (ins RO:$rs, simm16:$imm16),
1712         !strconcat(opstr, "\t$rs, $imm16"), [], itin, FrmOther, opstr>;
1713}
1714
1715// Mul, Div
1716class Mult<string opstr, InstrItinClass itin, RegisterOperand RO,
1717           list<Register> DefRegs> :
1718  InstSE<(outs), (ins RO:$rs, RO:$rt), !strconcat(opstr, "\t$rs, $rt"), [],
1719         itin, FrmR, opstr> {
1720  let isCommutable = 1;
1721  let Defs = DefRegs;
1722  let hasSideEffects = 0;
1723}
1724
1725// Pseudo multiply/divide instruction with explicit accumulator register
1726// operands.
1727class MultDivPseudo<Instruction RealInst, RegisterClass R0, RegisterOperand R1,
1728                    SDPatternOperator OpNode, InstrItinClass Itin,
1729                    bit IsComm = 1, bit HasSideEffects = 0,
1730                    bit UsesCustomInserter = 0> :
1731  PseudoSE<(outs R0:$ac), (ins R1:$rs, R1:$rt),
1732           [(set R0:$ac, (OpNode R1:$rs, R1:$rt))], Itin>,
1733  PseudoInstExpansion<(RealInst R1:$rs, R1:$rt)> {
1734  let isCommutable = IsComm;
1735  let hasSideEffects = HasSideEffects;
1736  let usesCustomInserter = UsesCustomInserter;
1737}
1738
1739// Pseudo multiply add/sub instruction with explicit accumulator register
1740// operands.
1741class MAddSubPseudo<Instruction RealInst, SDPatternOperator OpNode,
1742                    InstrItinClass itin>
1743  : PseudoSE<(outs ACC64:$ac),
1744             (ins GPR32Opnd:$rs, GPR32Opnd:$rt, ACC64:$acin),
1745             [(set ACC64:$ac,
1746              (OpNode GPR32Opnd:$rs, GPR32Opnd:$rt, ACC64:$acin))],
1747             itin>,
1748    PseudoInstExpansion<(RealInst GPR32Opnd:$rs, GPR32Opnd:$rt)> {
1749  string Constraints = "$acin = $ac";
1750}
1751
1752class Div<string opstr, InstrItinClass itin, RegisterOperand RO,
1753          list<Register> DefRegs> :
1754  InstSE<(outs), (ins RO:$rs, RO:$rt), !strconcat(opstr, "\t$$zero, $rs, $rt"),
1755         [], itin, FrmR, opstr> {
1756  let Defs = DefRegs;
1757}
1758
1759// Move from Hi/Lo
1760class PseudoMFLOHI<RegisterClass DstRC, RegisterClass SrcRC, SDNode OpNode>
1761  : PseudoSE<(outs DstRC:$rd), (ins SrcRC:$hilo),
1762             [(set DstRC:$rd, (OpNode SrcRC:$hilo))], II_MFHI_MFLO>;
1763
1764class MoveFromLOHI<string opstr, RegisterOperand RO, Register UseReg>:
1765  InstSE<(outs RO:$rd), (ins), !strconcat(opstr, "\t$rd"), [], II_MFHI_MFLO,
1766         FrmR, opstr> {
1767  let Uses = [UseReg];
1768  let hasSideEffects = 0;
1769  let isMoveReg = 1;
1770}
1771
1772class PseudoMTLOHI<RegisterClass DstRC, RegisterClass SrcRC>
1773  : PseudoSE<(outs DstRC:$lohi), (ins SrcRC:$lo, SrcRC:$hi),
1774             [(set DstRC:$lohi, (MipsMTLOHI SrcRC:$lo, SrcRC:$hi))],
1775             II_MTHI_MTLO>;
1776
1777class MoveToLOHI<string opstr, RegisterOperand RO, list<Register> DefRegs>:
1778  InstSE<(outs), (ins RO:$rs), !strconcat(opstr, "\t$rs"), [], II_MTHI_MTLO,
1779  FrmR, opstr> {
1780  let Defs = DefRegs;
1781  let hasSideEffects = 0;
1782  let isMoveReg = 1;
1783}
1784
1785class EffectiveAddress<string opstr, RegisterOperand RO> :
1786  InstSE<(outs RO:$rt), (ins mem_ea:$addr), !strconcat(opstr, "\t$rt, $addr"),
1787         [(set RO:$rt, addr:$addr)], II_ADDIU, FrmI,
1788         !strconcat(opstr, "_lea")> {
1789  let isCodeGenOnly = 1;
1790  let hasNoSchedulingInfo = 1;
1791  let DecoderMethod = "DecodeMem";
1792}
1793
1794// Count Leading Ones/Zeros in Word
1795class CountLeading0<string opstr, RegisterOperand RO,
1796                  InstrItinClass itin = NoItinerary>:
1797  InstSE<(outs RO:$rd), (ins RO:$rs), !strconcat(opstr, "\t$rd, $rs"),
1798         [(set RO:$rd, (ctlz RO:$rs))], itin, FrmR, opstr>;
1799
1800class CountLeading1<string opstr, RegisterOperand RO,
1801                  InstrItinClass itin = NoItinerary>:
1802  InstSE<(outs RO:$rd), (ins RO:$rs), !strconcat(opstr, "\t$rd, $rs"),
1803         [(set RO:$rd, (ctlz (not RO:$rs)))], itin, FrmR, opstr>;
1804
1805// Sign Extend in Register.
1806class SignExtInReg<string opstr, ValueType vt, RegisterOperand RO,
1807                   InstrItinClass itin> :
1808  InstSE<(outs RO:$rd), (ins RO:$rt), !strconcat(opstr, "\t$rd, $rt"),
1809         [(set RO:$rd, (sext_inreg RO:$rt, vt))], itin, FrmR, opstr>;
1810
1811// Subword Swap
1812class SubwordSwap<string opstr, RegisterOperand RO,
1813                  InstrItinClass itin = NoItinerary>:
1814  InstSE<(outs RO:$rd), (ins RO:$rt), !strconcat(opstr, "\t$rd, $rt"), [], itin,
1815         FrmR, opstr> {
1816  let hasSideEffects = 0;
1817}
1818
1819// Read Hardware
1820class ReadHardware<RegisterOperand CPURegOperand, RegisterOperand RO> :
1821  InstSE<(outs CPURegOperand:$rt), (ins RO:$rd, uimm8:$sel),
1822         "rdhwr\t$rt, $rd, $sel", [], II_RDHWR, FrmR, "rdhwr">;
1823
1824// Ext and Ins
1825class ExtBase<string opstr, RegisterOperand RO, Operand PosOpnd,
1826              Operand SizeOpnd, PatFrag PosImm, PatFrag SizeImm,
1827              SDPatternOperator Op = null_frag> :
1828  InstSE<(outs RO:$rt), (ins RO:$rs, PosOpnd:$pos, SizeOpnd:$size),
1829         !strconcat(opstr, "\t$rt, $rs, $pos, $size"),
1830         [(set RO:$rt, (Op RO:$rs, PosImm:$pos, SizeImm:$size))], II_EXT,
1831         FrmR, opstr>;
1832
1833// 'ins' and its' 64 bit variants are matched by C++ code.
1834class InsBase<string opstr, RegisterOperand RO, Operand PosOpnd,
1835              Operand SizeOpnd, PatFrag PosImm, PatFrag SizeImm>:
1836  InstSE<(outs RO:$rt), (ins RO:$rs, PosOpnd:$pos, SizeOpnd:$size, RO:$src),
1837         !strconcat(opstr, "\t$rt, $rs, $pos, $size"),
1838         [(set RO:$rt, (null_frag RO:$rs, PosImm:$pos, SizeImm:$size,
1839                                  RO:$src))],
1840         II_INS, FrmR, opstr> {
1841  let Constraints = "$src = $rt";
1842}
1843
1844// Atomic instructions with 2 source operands (ATOMIC_SWAP & ATOMIC_LOAD_*).
1845class Atomic2Ops<PatFrag Op, RegisterClass DRC> :
1846  PseudoSE<(outs DRC:$dst), (ins PtrRC:$ptr, DRC:$incr),
1847           [(set DRC:$dst, (Op iPTR:$ptr, DRC:$incr))]>;
1848
1849class Atomic2OpsPostRA<RegisterClass RC> :
1850  PseudoSE<(outs RC:$dst), (ins PtrRC:$ptr, RC:$incr), []> {
1851  let mayLoad = 1;
1852  let mayStore = 1;
1853}
1854
1855class Atomic2OpsSubwordPostRA<RegisterClass RC> :
1856  PseudoSE<(outs RC:$dst), (ins PtrRC:$ptr, RC:$incr, RC:$mask, RC:$mask2,
1857                                RC:$shiftamnt), []>;
1858
1859// Atomic Compare & Swap.
1860// Atomic compare and swap is lowered into two stages. The first stage happens
1861// during ISelLowering, which produces the PostRA version of this instruction.
1862class AtomicCmpSwap<PatFrag Op, RegisterClass DRC> :
1863  PseudoSE<(outs DRC:$dst), (ins PtrRC:$ptr, DRC:$cmp, DRC:$swap),
1864           [(set DRC:$dst, (Op iPTR:$ptr, DRC:$cmp, DRC:$swap))]>;
1865
1866class AtomicCmpSwapPostRA<RegisterClass RC> :
1867  PseudoSE<(outs RC:$dst), (ins PtrRC:$ptr, RC:$cmp, RC:$swap), []> {
1868  let mayLoad = 1;
1869  let mayStore = 1;
1870}
1871
1872class AtomicCmpSwapSubwordPostRA<RegisterClass RC> :
1873  PseudoSE<(outs RC:$dst), (ins PtrRC:$ptr, RC:$mask, RC:$ShiftCmpVal,
1874                                RC:$mask2, RC:$ShiftNewVal, RC:$ShiftAmt), []> {
1875  let mayLoad = 1;
1876  let mayStore = 1;
1877}
1878
1879
1880class LLBase<string opstr, RegisterOperand RO, DAGOperand MO = mem> :
1881  InstSE<(outs RO:$rt), (ins MO:$addr), !strconcat(opstr, "\t$rt, $addr"),
1882         [], II_LL, FrmI, opstr> {
1883  let DecoderMethod = "DecodeMem";
1884  let mayLoad = 1;
1885}
1886
1887class SCBase<string opstr, RegisterOperand RO> :
1888  InstSE<(outs RO:$dst), (ins RO:$rt, mem:$addr),
1889         !strconcat(opstr, "\t$rt, $addr"), [], II_SC, FrmI> {
1890  let DecoderMethod = "DecodeMem";
1891  let mayStore = 1;
1892  let Constraints = "$rt = $dst";
1893}
1894
1895class MFC3OP<string asmstr, RegisterOperand RO, RegisterOperand RD,
1896             InstrItinClass itin> :
1897  InstSE<(outs RO:$rt), (ins RD:$rd, uimm3:$sel),
1898         !strconcat(asmstr, "\t$rt, $rd, $sel"), [], itin, FrmFR> {
1899  let BaseOpcode = asmstr;
1900}
1901
1902class MTC3OP<string asmstr, RegisterOperand RO, RegisterOperand RD,
1903             InstrItinClass itin> :
1904  InstSE<(outs RO:$rd), (ins RD:$rt, uimm3:$sel),
1905         !strconcat(asmstr, "\t$rt, $rd, $sel"), [], itin, FrmFR> {
1906  let BaseOpcode = asmstr;
1907}
1908
1909class TrapBase<Instruction RealInst>
1910  : PseudoSE<(outs), (ins), [(trap)], II_TRAP>,
1911    PseudoInstExpansion<(RealInst 0, 0)> {
1912  let isBarrier = 1;
1913  let isTerminator = 1;
1914  let isCodeGenOnly = 1;
1915  let isCTI = 1;
1916}
1917
1918//===----------------------------------------------------------------------===//
1919// Pseudo instructions
1920//===----------------------------------------------------------------------===//
1921
1922// Return RA.
1923let isReturn=1, isTerminator=1, isBarrier=1, hasCtrlDep=1, isCTI=1 in {
1924  let hasDelaySlot=1 in
1925  def RetRA : PseudoSE<(outs), (ins), [(MipsRet)]>;
1926
1927  let hasSideEffects=1 in
1928  def ERet : PseudoSE<(outs), (ins), [(MipsERet)]>;
1929}
1930
1931let Defs = [SP], Uses = [SP], hasSideEffects = 1 in {
1932def ADJCALLSTACKDOWN : MipsPseudo<(outs), (ins i32imm:$amt1, i32imm:$amt2),
1933                                  [(callseq_start timm:$amt1, timm:$amt2)]>;
1934def ADJCALLSTACKUP   : MipsPseudo<(outs), (ins i32imm:$amt1, i32imm:$amt2),
1935                                  [(callseq_end timm:$amt1, timm:$amt2)]>;
1936}
1937
1938let usesCustomInserter = 1 in {
1939  def ATOMIC_LOAD_ADD_I8   : Atomic2Ops<atomic_load_add_8, GPR32>;
1940  def ATOMIC_LOAD_ADD_I16  : Atomic2Ops<atomic_load_add_16, GPR32>;
1941  def ATOMIC_LOAD_ADD_I32  : Atomic2Ops<atomic_load_add_32, GPR32>;
1942  def ATOMIC_LOAD_SUB_I8   : Atomic2Ops<atomic_load_sub_8, GPR32>;
1943  def ATOMIC_LOAD_SUB_I16  : Atomic2Ops<atomic_load_sub_16, GPR32>;
1944  def ATOMIC_LOAD_SUB_I32  : Atomic2Ops<atomic_load_sub_32, GPR32>;
1945  def ATOMIC_LOAD_AND_I8   : Atomic2Ops<atomic_load_and_8, GPR32>;
1946  def ATOMIC_LOAD_AND_I16  : Atomic2Ops<atomic_load_and_16, GPR32>;
1947  def ATOMIC_LOAD_AND_I32  : Atomic2Ops<atomic_load_and_32, GPR32>;
1948  def ATOMIC_LOAD_OR_I8    : Atomic2Ops<atomic_load_or_8, GPR32>;
1949  def ATOMIC_LOAD_OR_I16   : Atomic2Ops<atomic_load_or_16, GPR32>;
1950  def ATOMIC_LOAD_OR_I32   : Atomic2Ops<atomic_load_or_32, GPR32>;
1951  def ATOMIC_LOAD_XOR_I8   : Atomic2Ops<atomic_load_xor_8, GPR32>;
1952  def ATOMIC_LOAD_XOR_I16  : Atomic2Ops<atomic_load_xor_16, GPR32>;
1953  def ATOMIC_LOAD_XOR_I32  : Atomic2Ops<atomic_load_xor_32, GPR32>;
1954  def ATOMIC_LOAD_NAND_I8  : Atomic2Ops<atomic_load_nand_8, GPR32>;
1955  def ATOMIC_LOAD_NAND_I16 : Atomic2Ops<atomic_load_nand_16, GPR32>;
1956  def ATOMIC_LOAD_NAND_I32 : Atomic2Ops<atomic_load_nand_32, GPR32>;
1957
1958  def ATOMIC_SWAP_I8       : Atomic2Ops<atomic_swap_8, GPR32>;
1959  def ATOMIC_SWAP_I16      : Atomic2Ops<atomic_swap_16, GPR32>;
1960  def ATOMIC_SWAP_I32      : Atomic2Ops<atomic_swap_32, GPR32>;
1961
1962  def ATOMIC_CMP_SWAP_I8   : AtomicCmpSwap<atomic_cmp_swap_8, GPR32>;
1963  def ATOMIC_CMP_SWAP_I16  : AtomicCmpSwap<atomic_cmp_swap_16, GPR32>;
1964  def ATOMIC_CMP_SWAP_I32  : AtomicCmpSwap<atomic_cmp_swap_32, GPR32>;
1965
1966}
1967
1968def ATOMIC_LOAD_ADD_I8_POSTRA   : Atomic2OpsSubwordPostRA<GPR32>;
1969def ATOMIC_LOAD_ADD_I16_POSTRA  : Atomic2OpsSubwordPostRA<GPR32>;
1970def ATOMIC_LOAD_ADD_I32_POSTRA  : Atomic2OpsPostRA<GPR32>;
1971def ATOMIC_LOAD_SUB_I8_POSTRA   : Atomic2OpsSubwordPostRA<GPR32>;
1972def ATOMIC_LOAD_SUB_I16_POSTRA  : Atomic2OpsSubwordPostRA<GPR32>;
1973def ATOMIC_LOAD_SUB_I32_POSTRA  : Atomic2OpsPostRA<GPR32>;
1974def ATOMIC_LOAD_AND_I8_POSTRA   : Atomic2OpsSubwordPostRA<GPR32>;
1975def ATOMIC_LOAD_AND_I16_POSTRA  : Atomic2OpsSubwordPostRA<GPR32>;
1976def ATOMIC_LOAD_AND_I32_POSTRA  : Atomic2OpsPostRA<GPR32>;
1977def ATOMIC_LOAD_OR_I8_POSTRA    : Atomic2OpsSubwordPostRA<GPR32>;
1978def ATOMIC_LOAD_OR_I16_POSTRA   : Atomic2OpsSubwordPostRA<GPR32>;
1979def ATOMIC_LOAD_OR_I32_POSTRA   : Atomic2OpsPostRA<GPR32>;
1980def ATOMIC_LOAD_XOR_I8_POSTRA   : Atomic2OpsSubwordPostRA<GPR32>;
1981def ATOMIC_LOAD_XOR_I16_POSTRA  : Atomic2OpsSubwordPostRA<GPR32>;
1982def ATOMIC_LOAD_XOR_I32_POSTRA  : Atomic2OpsPostRA<GPR32>;
1983def ATOMIC_LOAD_NAND_I8_POSTRA  : Atomic2OpsSubwordPostRA<GPR32>;
1984def ATOMIC_LOAD_NAND_I16_POSTRA : Atomic2OpsSubwordPostRA<GPR32>;
1985def ATOMIC_LOAD_NAND_I32_POSTRA : Atomic2OpsPostRA<GPR32>;
1986
1987def ATOMIC_SWAP_I8_POSTRA  : Atomic2OpsSubwordPostRA<GPR32>;
1988def ATOMIC_SWAP_I16_POSTRA : Atomic2OpsSubwordPostRA<GPR32>;
1989def ATOMIC_SWAP_I32_POSTRA : Atomic2OpsPostRA<GPR32>;
1990
1991def ATOMIC_CMP_SWAP_I8_POSTRA : AtomicCmpSwapSubwordPostRA<GPR32>;
1992def ATOMIC_CMP_SWAP_I16_POSTRA : AtomicCmpSwapSubwordPostRA<GPR32>;
1993def ATOMIC_CMP_SWAP_I32_POSTRA : AtomicCmpSwapPostRA<GPR32>;
1994
1995/// Pseudo instructions for loading and storing accumulator registers.
1996let isPseudo = 1, isCodeGenOnly = 1, hasNoSchedulingInfo = 1 in {
1997  def LOAD_ACC64  : Load<"", ACC64>;
1998  def STORE_ACC64 : Store<"", ACC64>;
1999}
2000
2001// We need these two pseudo instructions to avoid offset calculation for long
2002// branches.  See the comment in file MipsLongBranch.cpp for detailed
2003// explanation.
2004
2005// Expands to: lui $dst, %hi($tgt - $baltgt)
2006def LONG_BRANCH_LUi : PseudoSE<(outs GPR32Opnd:$dst),
2007  (ins brtarget:$tgt, brtarget:$baltgt), []>;
2008
2009// Expands to: addiu $dst, $src, %lo($tgt - $baltgt)
2010def LONG_BRANCH_ADDiu : PseudoSE<(outs GPR32Opnd:$dst),
2011  (ins GPR32Opnd:$src, brtarget:$tgt, brtarget:$baltgt), []>;
2012
2013//===----------------------------------------------------------------------===//
2014// Instruction definition
2015//===----------------------------------------------------------------------===//
2016//===----------------------------------------------------------------------===//
2017// MipsI Instructions
2018//===----------------------------------------------------------------------===//
2019
2020/// Arithmetic Instructions (ALU Immediate)
2021let AdditionalPredicates = [NotInMicroMips] in {
2022  def ADDiu : MMRel, StdMMR6Rel, ArithLogicI<"addiu", simm16_relaxed, GPR32Opnd,
2023                                             II_ADDIU, immSExt16, add>,
2024              ADDI_FM<0x9>, IsAsCheapAsAMove, ISA_MIPS1;
2025
2026  def ANDi : MMRel, StdMMR6Rel,
2027             ArithLogicI<"andi", uimm16, GPR32Opnd, II_ANDI, immZExt16, and>,
2028             ADDI_FM<0xc>, ISA_MIPS1;
2029  def ORi  : MMRel, StdMMR6Rel,
2030             ArithLogicI<"ori", uimm16, GPR32Opnd, II_ORI, immZExt16, or>,
2031             ADDI_FM<0xd>, ISA_MIPS1;
2032  def XORi : MMRel, StdMMR6Rel,
2033             ArithLogicI<"xori", uimm16, GPR32Opnd, II_XORI, immZExt16, xor>,
2034             ADDI_FM<0xe>, ISA_MIPS1;
2035  def ADDi  : MMRel, ArithLogicI<"addi", simm16_relaxed, GPR32Opnd, II_ADDI>,
2036              ADDI_FM<0x8>, ISA_MIPS1_NOT_32R6_64R6;
2037  def SLTi  : MMRel, SetCC_I<"slti", setlt, simm16, immSExt16, GPR32Opnd>,
2038              SLTI_FM<0xa>, ISA_MIPS1;
2039  def SLTiu : MMRel, SetCC_I<"sltiu", setult, simm16, immSExt16, GPR32Opnd>,
2040              SLTI_FM<0xb>, ISA_MIPS1;
2041
2042  def LUi   : MMRel, LoadUpper<"lui", GPR32Opnd, uimm16_relaxed>, LUI_FM,
2043              ISA_MIPS1;
2044
2045  /// Arithmetic Instructions (3-Operand, R-Type)
2046  def ADDu  : MMRel, StdMMR6Rel, ArithLogicR<"addu", GPR32Opnd, 1, II_ADDU, add>,
2047              ADD_FM<0, 0x21>, ISA_MIPS1;
2048  def SUBu  : MMRel, StdMMR6Rel, ArithLogicR<"subu", GPR32Opnd, 0, II_SUBU, sub>,
2049              ADD_FM<0, 0x23>, ISA_MIPS1;
2050
2051  let Defs = [HI0, LO0] in
2052    def MUL   : MMRel, ArithLogicR<"mul", GPR32Opnd, 1, II_MUL, mul>,
2053                ADD_FM<0x1c, 2>, ISA_MIPS32_NOT_32R6_64R6;
2054
2055  def ADD   : MMRel, StdMMR6Rel, ArithLogicR<"add", GPR32Opnd, 1, II_ADD>,
2056              ADD_FM<0, 0x20>, ISA_MIPS1;
2057  def SUB   : MMRel, StdMMR6Rel, ArithLogicR<"sub", GPR32Opnd, 0, II_SUB>,
2058              ADD_FM<0, 0x22>, ISA_MIPS1;
2059
2060  def SLT   : MMRel, SetCC_R<"slt", setlt, GPR32Opnd>, ADD_FM<0, 0x2a>,
2061              ISA_MIPS1;
2062  def SLTu  : MMRel, SetCC_R<"sltu", setult, GPR32Opnd>, ADD_FM<0, 0x2b>,
2063              ISA_MIPS1;
2064  def AND   : MMRel, StdMMR6Rel, ArithLogicR<"and", GPR32Opnd, 1, II_AND, and>,
2065              ADD_FM<0, 0x24>, ISA_MIPS1;
2066  def OR    : MMRel, StdMMR6Rel, ArithLogicR<"or", GPR32Opnd, 1, II_OR, or>,
2067              ADD_FM<0, 0x25>, ISA_MIPS1;
2068  def XOR   : MMRel, StdMMR6Rel, ArithLogicR<"xor", GPR32Opnd, 1, II_XOR, xor>,
2069              ADD_FM<0, 0x26>, ISA_MIPS1;
2070  def NOR   : MMRel, StdMMR6Rel, LogicNOR<"nor", GPR32Opnd>, ADD_FM<0, 0x27>,
2071              ISA_MIPS1;
2072}
2073
2074let AdditionalPredicates = [NotInMicroMips] in {
2075  /// Shift Instructions
2076  def SLL  : MMRel, shift_rotate_imm<"sll", uimm5, GPR32Opnd, II_SLL, shl,
2077                                     immZExt5>, SRA_FM<0, 0>, ISA_MIPS1;
2078  def SRL  : MMRel, shift_rotate_imm<"srl", uimm5, GPR32Opnd, II_SRL, srl,
2079                                     immZExt5>, SRA_FM<2, 0>, ISA_MIPS1;
2080  def SRA  : MMRel, shift_rotate_imm<"sra", uimm5, GPR32Opnd, II_SRA, sra,
2081                                     immZExt5>, SRA_FM<3, 0>, ISA_MIPS1;
2082  def SLLV : MMRel, shift_rotate_reg<"sllv", GPR32Opnd, II_SLLV, shl>,
2083             SRLV_FM<4, 0>, ISA_MIPS1;
2084  def SRLV : MMRel, shift_rotate_reg<"srlv", GPR32Opnd, II_SRLV, srl>,
2085             SRLV_FM<6, 0>, ISA_MIPS1;
2086  def SRAV : MMRel, shift_rotate_reg<"srav", GPR32Opnd, II_SRAV, sra>,
2087             SRLV_FM<7, 0>, ISA_MIPS1;
2088
2089  // Rotate Instructions
2090  def ROTR  : MMRel, shift_rotate_imm<"rotr", uimm5, GPR32Opnd, II_ROTR, rotr,
2091                                      immZExt5>,
2092              SRA_FM<2, 1>, ISA_MIPS32R2;
2093  def ROTRV : MMRel, shift_rotate_reg<"rotrv", GPR32Opnd, II_ROTRV, rotr>,
2094              SRLV_FM<6, 1>, ISA_MIPS32R2;
2095}
2096
2097/// Load and Store Instructions
2098///  aligned
2099let AdditionalPredicates = [NotInMicroMips] in {
2100  def LB  : LoadMemory<"lb", GPR32Opnd, mem_simmptr, sextloadi8, II_LB>, MMRel,
2101            LW_FM<0x20>, ISA_MIPS1;
2102  def LBu : LoadMemory<"lbu", GPR32Opnd, mem_simmptr, zextloadi8, II_LBU,
2103                       addrDefault>, MMRel, LW_FM<0x24>, ISA_MIPS1;
2104  def LH  : LoadMemory<"lh", GPR32Opnd, mem_simmptr, sextloadi16, II_LH,
2105                       addrDefault>, MMRel, LW_FM<0x21>, ISA_MIPS1;
2106  def LHu : LoadMemory<"lhu", GPR32Opnd, mem_simmptr, zextloadi16, II_LHU>,
2107            MMRel, LW_FM<0x25>, ISA_MIPS1;
2108  def LW  : StdMMR6Rel, Load<"lw", GPR32Opnd, load, II_LW, addrDefault>, MMRel,
2109            LW_FM<0x23>, ISA_MIPS1;
2110  def SB  : StdMMR6Rel, Store<"sb", GPR32Opnd, truncstorei8, II_SB>, MMRel,
2111            LW_FM<0x28>, ISA_MIPS1;
2112  def SH  : Store<"sh", GPR32Opnd, truncstorei16, II_SH>, MMRel, LW_FM<0x29>,
2113            ISA_MIPS1;
2114  def SW  : Store<"sw", GPR32Opnd, store, II_SW>, MMRel, LW_FM<0x2b>, ISA_MIPS1;
2115}
2116
2117/// load/store left/right
2118let AdditionalPredicates = [NotInMicroMips] in {
2119def LWL : MMRel, LoadLeftRight<"lwl", MipsLWL, GPR32Opnd, II_LWL>, LW_FM<0x22>,
2120          ISA_MIPS1_NOT_32R6_64R6;
2121def LWR : MMRel, LoadLeftRight<"lwr", MipsLWR, GPR32Opnd, II_LWR>, LW_FM<0x26>,
2122          ISA_MIPS1_NOT_32R6_64R6;
2123def SWL : MMRel, StoreLeftRight<"swl", MipsSWL, GPR32Opnd, II_SWL>, LW_FM<0x2a>,
2124          ISA_MIPS1_NOT_32R6_64R6;
2125def SWR : MMRel, StoreLeftRight<"swr", MipsSWR, GPR32Opnd, II_SWR>, LW_FM<0x2e>,
2126          ISA_MIPS1_NOT_32R6_64R6;
2127
2128// COP2 Memory Instructions
2129def LWC2 : StdMMR6Rel, LW_FT2<"lwc2", COP2Opnd, II_LWC2, load>, LW_FM<0x32>,
2130           ISA_MIPS1_NOT_32R6_64R6;
2131def SWC2 : StdMMR6Rel, SW_FT2<"swc2", COP2Opnd, II_SWC2, store>,
2132           LW_FM<0x3a>, ISA_MIPS1_NOT_32R6_64R6;
2133def LDC2 : StdMMR6Rel, LW_FT2<"ldc2", COP2Opnd, II_LDC2, load>, LW_FM<0x36>,
2134           ISA_MIPS2_NOT_32R6_64R6;
2135def SDC2 : StdMMR6Rel, SW_FT2<"sdc2", COP2Opnd, II_SDC2, store>,
2136           LW_FM<0x3e>, ISA_MIPS2_NOT_32R6_64R6;
2137
2138// COP3 Memory Instructions
2139let DecoderNamespace = "COP3_" in {
2140  def LWC3 : LW_FT3<"lwc3", COP3Opnd, II_LWC3, load>, LW_FM<0x33>,
2141             ISA_MIPS1_NOT_32R6_64R6, NOT_ASE_CNMIPS;
2142  def SWC3 : SW_FT3<"swc3", COP3Opnd, II_SWC3, store>, LW_FM<0x3b>,
2143             ISA_MIPS1_NOT_32R6_64R6, NOT_ASE_CNMIPS;
2144  def LDC3 : LW_FT3<"ldc3", COP3Opnd, II_LDC3, load>, LW_FM<0x37>,
2145             ISA_MIPS2, NOT_ASE_CNMIPS;
2146  def SDC3 : SW_FT3<"sdc3", COP3Opnd, II_SDC3, store>, LW_FM<0x3f>,
2147             ISA_MIPS2, NOT_ASE_CNMIPS;
2148}
2149
2150  def SYNC : MMRel, StdMMR6Rel, SYNC_FT<"sync">, SYNC_FM, ISA_MIPS2;
2151  def SYNCI : MMRel, StdMMR6Rel, SYNCI_FT<"synci", mem_simm16>, SYNCI_FM,
2152              ISA_MIPS32R2;
2153}
2154
2155let AdditionalPredicates = [NotInMicroMips] in {
2156  def TEQ : MMRel, TEQ_FT<"teq", GPR32Opnd, uimm10, II_TEQ>, TEQ_FM<0x34>,
2157            ISA_MIPS2;
2158  def TGE : MMRel, TEQ_FT<"tge", GPR32Opnd, uimm10, II_TGE>, TEQ_FM<0x30>,
2159            ISA_MIPS2;
2160  def TGEU : MMRel, TEQ_FT<"tgeu", GPR32Opnd, uimm10, II_TGEU>, TEQ_FM<0x31>,
2161             ISA_MIPS2;
2162  def TLT : MMRel, TEQ_FT<"tlt", GPR32Opnd, uimm10, II_TLT>, TEQ_FM<0x32>,
2163            ISA_MIPS2;
2164  def TLTU : MMRel, TEQ_FT<"tltu", GPR32Opnd, uimm10, II_TLTU>, TEQ_FM<0x33>,
2165            ISA_MIPS2;
2166  def TNE : MMRel, TEQ_FT<"tne", GPR32Opnd, uimm10, II_TNE>, TEQ_FM<0x36>,
2167            ISA_MIPS2;
2168
2169  def TEQI : MMRel, TEQI_FT<"teqi", GPR32Opnd, II_TEQI>, TEQI_FM<0xc>,
2170             ISA_MIPS2_NOT_32R6_64R6;
2171  def TGEI : MMRel, TEQI_FT<"tgei", GPR32Opnd, II_TGEI>, TEQI_FM<0x8>,
2172             ISA_MIPS2_NOT_32R6_64R6;
2173  def TGEIU : MMRel, TEQI_FT<"tgeiu", GPR32Opnd, II_TGEIU>, TEQI_FM<0x9>,
2174              ISA_MIPS2_NOT_32R6_64R6;
2175  def TLTI : MMRel, TEQI_FT<"tlti", GPR32Opnd, II_TLTI>, TEQI_FM<0xa>,
2176             ISA_MIPS2_NOT_32R6_64R6;
2177  def TTLTIU : MMRel, TEQI_FT<"tltiu", GPR32Opnd, II_TTLTIU>, TEQI_FM<0xb>,
2178               ISA_MIPS2_NOT_32R6_64R6;
2179  def TNEI : MMRel, TEQI_FT<"tnei", GPR32Opnd, II_TNEI>, TEQI_FM<0xe>,
2180             ISA_MIPS2_NOT_32R6_64R6;
2181}
2182
2183let AdditionalPredicates = [NotInMicroMips] in {
2184  def BREAK : MMRel, StdMMR6Rel, BRK_FT<"break">, BRK_FM<0xd>, ISA_MIPS1;
2185  def SYSCALL : MMRel, SYS_FT<"syscall", uimm20, II_SYSCALL>, SYS_FM<0xc>,
2186                ISA_MIPS1;
2187  def TRAP : TrapBase<BREAK>, ISA_MIPS1;
2188  def SDBBP : MMRel, SYS_FT<"sdbbp", uimm20, II_SDBBP>, SDBBP_FM,
2189              ISA_MIPS32_NOT_32R6_64R6;
2190
2191  def ERET : MMRel, ER_FT<"eret", II_ERET>, ER_FM<0x18, 0x0>, INSN_MIPS3_32;
2192  def ERETNC : MMRel, ER_FT<"eretnc", II_ERETNC>, ER_FM<0x18, 0x1>,
2193               ISA_MIPS32R5;
2194  def DERET : MMRel, ER_FT<"deret", II_DERET>, ER_FM<0x1f, 0x0>, ISA_MIPS32;
2195
2196  def EI : MMRel, StdMMR6Rel, DEI_FT<"ei", GPR32Opnd, II_EI>, EI_FM<1>,
2197           ISA_MIPS32R2;
2198  def DI : MMRel, StdMMR6Rel, DEI_FT<"di", GPR32Opnd, II_DI>, EI_FM<0>,
2199           ISA_MIPS32R2;
2200
2201  def WAIT : MMRel, StdMMR6Rel, WAIT_FT<"wait">, WAIT_FM, INSN_MIPS3_32;
2202}
2203
2204let AdditionalPredicates = [NotInMicroMips] in {
2205/// Load-linked, Store-conditional
2206def LL : LLBase<"ll", GPR32Opnd>, LW_FM<0x30>, PTR_32, ISA_MIPS2_NOT_32R6_64R6;
2207def SC : SCBase<"sc", GPR32Opnd>, LW_FM<0x38>, PTR_32, ISA_MIPS2_NOT_32R6_64R6;
2208}
2209/// Jump and Branch Instructions
2210let AdditionalPredicates = [NotInMicroMips, RelocNotPIC] in
2211def J       : MMRel, JumpFJ<jmptarget, "j", br, bb, "j">, FJ<2>,
2212              IsBranch, ISA_MIPS1;
2213
2214let AdditionalPredicates = [NotInMicroMips] in {
2215def JR      : MMRel, IndirectBranch<"jr", GPR32Opnd>, MTLO_FM<8>, ISA_MIPS1_NOT_32R6_64R6;
2216def BEQ     : MMRel, CBranch<"beq", brtarget, seteq, GPR32Opnd>, BEQ_FM<4>,
2217              ISA_MIPS1;
2218def BEQL    : MMRel, CBranchLikely<"beql", brtarget, GPR32Opnd>,
2219              BEQ_FM<20>, ISA_MIPS2_NOT_32R6_64R6;
2220def BNE     : MMRel, CBranch<"bne", brtarget, setne, GPR32Opnd>, BEQ_FM<5>,
2221              ISA_MIPS1;
2222def BNEL    : MMRel, CBranchLikely<"bnel", brtarget, GPR32Opnd>,
2223              BEQ_FM<21>, ISA_MIPS2_NOT_32R6_64R6;
2224def BGEZ    : MMRel, CBranchZero<"bgez", brtarget, setge, GPR32Opnd>,
2225              BGEZ_FM<1, 1>, ISA_MIPS1;
2226def BGEZL   : MMRel, CBranchZeroLikely<"bgezl", brtarget, GPR32Opnd>,
2227              BGEZ_FM<1, 3>, ISA_MIPS2_NOT_32R6_64R6;
2228def BGTZ    : MMRel, CBranchZero<"bgtz", brtarget, setgt, GPR32Opnd>,
2229              BGEZ_FM<7, 0>, ISA_MIPS1;
2230def BGTZL   : MMRel, CBranchZeroLikely<"bgtzl", brtarget, GPR32Opnd>,
2231              BGEZ_FM<23, 0>, ISA_MIPS2_NOT_32R6_64R6;
2232def BLEZ    : MMRel, CBranchZero<"blez", brtarget, setle, GPR32Opnd>,
2233              BGEZ_FM<6, 0>, ISA_MIPS1;
2234def BLEZL   : MMRel, CBranchZeroLikely<"blezl", brtarget, GPR32Opnd>,
2235              BGEZ_FM<22, 0>, ISA_MIPS2_NOT_32R6_64R6;
2236def BLTZ    : MMRel, CBranchZero<"bltz", brtarget, setlt, GPR32Opnd>,
2237              BGEZ_FM<1, 0>, ISA_MIPS1;
2238def BLTZL   : MMRel, CBranchZeroLikely<"bltzl", brtarget, GPR32Opnd>,
2239              BGEZ_FM<1, 2>, ISA_MIPS2_NOT_32R6_64R6;
2240def B       : UncondBranch<BEQ, brtarget>, ISA_MIPS1;
2241
2242def JAL  : MMRel, JumpLink<"jal", calltarget>, FJ<3>, ISA_MIPS1;
2243
2244}
2245
2246let AdditionalPredicates = [NotInMicroMips, NoIndirectJumpGuards] in {
2247  def JALR : JumpLinkReg<"jalr", GPR32Opnd>, JALR_FM, ISA_MIPS1;
2248  def JALRPseudo : JumpLinkRegPseudo<GPR32Opnd, JALR, RA>, ISA_MIPS1;
2249}
2250
2251let AdditionalPredicates = [NotInMicroMips] in {
2252  def JALX : MMRel, JumpLink<"jalx", calltarget>, FJ<0x1D>,
2253             ISA_MIPS32_NOT_32R6_64R6;
2254  def BGEZAL : MMRel, BGEZAL_FT<"bgezal", brtarget, GPR32Opnd>, BGEZAL_FM<0x11>,
2255               ISA_MIPS1_NOT_32R6_64R6;
2256  def BGEZALL : MMRel, BGEZAL_FT<"bgezall", brtarget, GPR32Opnd>,
2257                BGEZAL_FM<0x13>, ISA_MIPS2_NOT_32R6_64R6;
2258  def BLTZAL : MMRel, BGEZAL_FT<"bltzal", brtarget, GPR32Opnd>, BGEZAL_FM<0x10>,
2259               ISA_MIPS1_NOT_32R6_64R6;
2260  def BLTZALL : MMRel, BGEZAL_FT<"bltzall", brtarget, GPR32Opnd>,
2261                BGEZAL_FM<0x12>, ISA_MIPS2_NOT_32R6_64R6;
2262  def BAL_BR : BAL_BR_Pseudo<BGEZAL, brtarget>, ISA_MIPS1;
2263}
2264let AdditionalPredicates = [NotInMips16Mode, NotInMicroMips] in {
2265  def TAILCALL : TailCall<J, jmptarget>, ISA_MIPS1;
2266}
2267let AdditionalPredicates = [NotInMips16Mode, NotInMicroMips,
2268                            NoIndirectJumpGuards] in
2269  def TAILCALLREG : TailCallReg<JR, GPR32Opnd>, ISA_MIPS1_NOT_32R6_64R6;
2270
2271// Indirect branches are matched as PseudoIndirectBranch/PseudoIndirectBranch64
2272// then are expanded to JR, JR64, JALR, or JALR64 depending on the ISA.
2273class PseudoIndirectBranchBase<Instruction JumpInst, RegisterOperand RO> :
2274    MipsPseudo<(outs), (ins RO:$rs), [(brind RO:$rs)],
2275               II_IndirectBranchPseudo>,
2276    PseudoInstExpansion<(JumpInst RO:$rs)> {
2277  let isTerminator=1;
2278  let isBarrier=1;
2279  let hasDelaySlot = 1;
2280  let isBranch = 1;
2281  let isIndirectBranch = 1;
2282  bit isCTI = 1;
2283}
2284
2285let AdditionalPredicates = [NotInMips16Mode, NotInMicroMips,
2286                            NoIndirectJumpGuards] in
2287  def PseudoIndirectBranch : PseudoIndirectBranchBase<JR, GPR32Opnd>,
2288                             ISA_MIPS1_NOT_32R6_64R6;
2289
2290// Return instructions are matched as a RetRA instruction, then are expanded
2291// into PseudoReturn/PseudoReturn64 after register allocation. Finally,
2292// MipsAsmPrinter expands this into JR, JR64, JALR, or JALR64 depending on the
2293// ISA.
2294class PseudoReturnBase<RegisterOperand RO> : MipsPseudo<(outs), (ins RO:$rs),
2295                                                        [], II_ReturnPseudo> {
2296  let isTerminator = 1;
2297  let isBarrier = 1;
2298  let hasDelaySlot = 1;
2299  let isReturn = 1;
2300  let isCodeGenOnly = 1;
2301  let hasCtrlDep = 1;
2302  let hasExtraSrcRegAllocReq = 1;
2303  bit isCTI = 1;
2304}
2305
2306def PseudoReturn : PseudoReturnBase<GPR32Opnd>;
2307
2308// Exception handling related node and instructions.
2309// The conversion sequence is:
2310// ISD::EH_RETURN -> MipsISD::EH_RETURN ->
2311// MIPSeh_return -> (stack change + indirect branch)
2312//
2313// MIPSeh_return takes the place of regular return instruction
2314// but takes two arguments (V1, V0) which are used for storing
2315// the offset and return address respectively.
2316def SDT_MipsEHRET : SDTypeProfile<0, 2, [SDTCisInt<0>, SDTCisPtrTy<1>]>;
2317
2318def MIPSehret : SDNode<"MipsISD::EH_RETURN", SDT_MipsEHRET,
2319                      [SDNPHasChain, SDNPOptInGlue, SDNPVariadic]>;
2320
2321let Uses = [V0, V1], isTerminator = 1, isReturn = 1, isBarrier = 1, isCTI = 1 in {
2322  def MIPSeh_return32 : MipsPseudo<(outs), (ins GPR32:$spoff, GPR32:$dst),
2323                                [(MIPSehret GPR32:$spoff, GPR32:$dst)]>;
2324  def MIPSeh_return64 : MipsPseudo<(outs), (ins GPR64:$spoff,
2325                                                GPR64:$dst),
2326                                [(MIPSehret GPR64:$spoff, GPR64:$dst)]>;
2327}
2328
2329/// Multiply and Divide Instructions.
2330let AdditionalPredicates = [NotInMicroMips] in {
2331  def MULT  : MMRel, Mult<"mult", II_MULT, GPR32Opnd, [HI0, LO0]>,
2332              MULT_FM<0, 0x18>, ISA_MIPS1_NOT_32R6_64R6;
2333  def MULTu : MMRel, Mult<"multu", II_MULTU, GPR32Opnd, [HI0, LO0]>,
2334              MULT_FM<0, 0x19>, ISA_MIPS1_NOT_32R6_64R6;
2335  def SDIV  : MMRel, Div<"div", II_DIV, GPR32Opnd, [HI0, LO0]>,
2336              MULT_FM<0, 0x1a>, ISA_MIPS1_NOT_32R6_64R6;
2337  def UDIV  : MMRel, Div<"divu", II_DIVU, GPR32Opnd, [HI0, LO0]>,
2338              MULT_FM<0, 0x1b>, ISA_MIPS1_NOT_32R6_64R6;
2339  def MTHI : MMRel, MoveToLOHI<"mthi", GPR32Opnd, [HI0]>, MTLO_FM<0x11>,
2340             ISA_MIPS1_NOT_32R6_64R6;
2341  def MTLO : MMRel, MoveToLOHI<"mtlo", GPR32Opnd, [LO0]>, MTLO_FM<0x13>,
2342             ISA_MIPS1_NOT_32R6_64R6;
2343  def MFHI : MMRel, MoveFromLOHI<"mfhi", GPR32Opnd, AC0>, MFLO_FM<0x10>,
2344             ISA_MIPS1_NOT_32R6_64R6;
2345  def MFLO : MMRel, MoveFromLOHI<"mflo", GPR32Opnd, AC0>, MFLO_FM<0x12>,
2346             ISA_MIPS1_NOT_32R6_64R6;
2347
2348  /// Sign Ext In Register Instructions.
2349  def SEB : MMRel, StdMMR6Rel, SignExtInReg<"seb", i8, GPR32Opnd, II_SEB>,
2350            SEB_FM<0x10, 0x20>, ISA_MIPS32R2;
2351  def SEH : MMRel, StdMMR6Rel, SignExtInReg<"seh", i16, GPR32Opnd, II_SEH>,
2352            SEB_FM<0x18, 0x20>, ISA_MIPS32R2;
2353
2354  /// Count Leading
2355  def CLZ : MMRel, CountLeading0<"clz", GPR32Opnd, II_CLZ>, CLO_FM<0x20>,
2356            ISA_MIPS32_NOT_32R6_64R6;
2357  def CLO : MMRel, CountLeading1<"clo", GPR32Opnd, II_CLO>, CLO_FM<0x21>,
2358            ISA_MIPS32_NOT_32R6_64R6;
2359
2360  /// Word Swap Bytes Within Halfwords
2361  def WSBH : MMRel, SubwordSwap<"wsbh", GPR32Opnd, II_WSBH>, SEB_FM<2, 0x20>,
2362             ISA_MIPS32R2;
2363
2364  /// No operation.
2365  def NOP : PseudoSE<(outs), (ins), []>,
2366                     PseudoInstExpansion<(SLL ZERO, ZERO, 0)>, ISA_MIPS1;
2367
2368  // FrameIndexes are legalized when they are operands from load/store
2369  // instructions. The same not happens for stack address copies, so an
2370  // add op with mem ComplexPattern is used and the stack address copy
2371  // can be matched. It's similar to Sparc LEA_ADDRi
2372  let AdditionalPredicates = [NotInMicroMips] in
2373    def LEA_ADDiu : MMRel, EffectiveAddress<"addiu", GPR32Opnd>, LW_FM<9>, ISA_MIPS1;
2374
2375  // MADD*/MSUB*
2376  def MADD  : MMRel, MArithR<"madd", II_MADD, 1>, MULT_FM<0x1c, 0>,
2377              ISA_MIPS32_NOT_32R6_64R6;
2378  def MADDU : MMRel, MArithR<"maddu", II_MADDU, 1>, MULT_FM<0x1c, 1>,
2379              ISA_MIPS32_NOT_32R6_64R6;
2380  def MSUB  : MMRel, MArithR<"msub", II_MSUB>, MULT_FM<0x1c, 4>,
2381              ISA_MIPS32_NOT_32R6_64R6;
2382  def MSUBU : MMRel, MArithR<"msubu", II_MSUBU>, MULT_FM<0x1c, 5>,
2383              ISA_MIPS32_NOT_32R6_64R6;
2384}
2385
2386let AdditionalPredicates = [NotDSP] in {
2387def PseudoMULT  : MultDivPseudo<MULT, ACC64, GPR32Opnd, MipsMult, II_MULT>,
2388                  ISA_MIPS1_NOT_32R6_64R6;
2389def PseudoMULTu : MultDivPseudo<MULTu, ACC64, GPR32Opnd, MipsMultu, II_MULTU>,
2390                  ISA_MIPS1_NOT_32R6_64R6;
2391def PseudoMFHI : PseudoMFLOHI<GPR32, ACC64, MipsMFHI>, ISA_MIPS1_NOT_32R6_64R6;
2392def PseudoMFLO : PseudoMFLOHI<GPR32, ACC64, MipsMFLO>, ISA_MIPS1_NOT_32R6_64R6;
2393def PseudoMTLOHI : PseudoMTLOHI<ACC64, GPR32>, ISA_MIPS1_NOT_32R6_64R6;
2394def PseudoMADD  : MAddSubPseudo<MADD, MipsMAdd, II_MADD>,
2395                  ISA_MIPS32_NOT_32R6_64R6;
2396def PseudoMADDU : MAddSubPseudo<MADDU, MipsMAddu, II_MADDU>,
2397                  ISA_MIPS32_NOT_32R6_64R6;
2398def PseudoMSUB  : MAddSubPseudo<MSUB, MipsMSub, II_MSUB>,
2399                  ISA_MIPS32_NOT_32R6_64R6;
2400def PseudoMSUBU : MAddSubPseudo<MSUBU, MipsMSubu, II_MSUBU>,
2401                  ISA_MIPS32_NOT_32R6_64R6;
2402}
2403
2404let AdditionalPredicates = [NotInMicroMips] in {
2405  def PseudoSDIV : MultDivPseudo<SDIV, ACC64, GPR32Opnd, MipsDivRem, II_DIV,
2406                                 0, 1, 1>, ISA_MIPS1_NOT_32R6_64R6;
2407  def PseudoUDIV : MultDivPseudo<UDIV, ACC64, GPR32Opnd, MipsDivRemU, II_DIVU,
2408                                 0, 1, 1>, ISA_MIPS1_NOT_32R6_64R6;
2409  def RDHWR : MMRel, ReadHardware<GPR32Opnd, HWRegsOpnd>, RDHWR_FM, ISA_MIPS1;
2410  // TODO: Add '0 < pos+size <= 32' constraint check to ext instruction
2411  def EXT : MMRel, StdMMR6Rel, ExtBase<"ext", GPR32Opnd, uimm5, uimm5_plus1,
2412                                       immZExt5, immZExt5Plus1, MipsExt>,
2413            EXT_FM<0>, ISA_MIPS32R2;
2414  def INS : MMRel, StdMMR6Rel, InsBase<"ins", GPR32Opnd, uimm5,
2415                                       uimm5_inssize_plus1, immZExt5,
2416                                       immZExt5Plus1>,
2417            EXT_FM<4>, ISA_MIPS32R2;
2418}
2419/// Move Control Registers From/To CPU Registers
2420let AdditionalPredicates = [NotInMicroMips] in {
2421  def MTC0 : MTC3OP<"mtc0", COP0Opnd, GPR32Opnd, II_MTC0>,
2422             MFC3OP_FM<0x10, 4, 0>, ISA_MIPS1;
2423  def MFC0 : MFC3OP<"mfc0", GPR32Opnd, COP0Opnd, II_MFC0>,
2424             MFC3OP_FM<0x10, 0, 0>, ISA_MIPS1;
2425  def MFC2 : MFC3OP<"mfc2", GPR32Opnd, COP2Opnd, II_MFC2>,
2426             MFC3OP_FM<0x12, 0, 0>, ISA_MIPS1;
2427  def MTC2 : MTC3OP<"mtc2", COP2Opnd, GPR32Opnd, II_MTC2>,
2428             MFC3OP_FM<0x12, 4, 0>, ISA_MIPS1;
2429}
2430
2431class Barrier<string asmstr, InstrItinClass itin = NoItinerary> :
2432  InstSE<(outs), (ins), asmstr, [], itin, FrmOther, asmstr>;
2433let AdditionalPredicates = [NotInMicroMips] in {
2434  def SSNOP : MMRel, StdMMR6Rel, Barrier<"ssnop", II_SSNOP>, BARRIER_FM<1>,
2435              ISA_MIPS1;
2436  def EHB : MMRel, Barrier<"ehb", II_EHB>, BARRIER_FM<3>, ISA_MIPS1;
2437
2438  let isCTI = 1 in
2439  def PAUSE : MMRel, StdMMR6Rel, Barrier<"pause", II_PAUSE>, BARRIER_FM<5>,
2440              ISA_MIPS32R2;
2441}
2442
2443// JR_HB and JALR_HB are defined here using the new style naming
2444// scheme because some of this code is shared with Mips32r6InstrInfo.td
2445// and because of that it doesn't follow the naming convention of the
2446// rest of the file. To avoid a mixture of old vs new style, the new
2447// style was chosen.
2448class JR_HB_DESC_BASE<string instr_asm, RegisterOperand GPROpnd> {
2449  dag OutOperandList = (outs);
2450  dag InOperandList = (ins GPROpnd:$rs);
2451  string AsmString = !strconcat(instr_asm, "\t$rs");
2452  list<dag> Pattern = [];
2453}
2454
2455class JALR_HB_DESC_BASE<string instr_asm, RegisterOperand GPROpnd> {
2456  dag OutOperandList = (outs GPROpnd:$rd);
2457  dag InOperandList = (ins GPROpnd:$rs);
2458  string AsmString = !strconcat(instr_asm, "\t$rd, $rs");
2459  list<dag> Pattern = [];
2460}
2461
2462class JR_HB_DESC<RegisterOperand RO> :
2463  InstSE<(outs), (ins), "", [], II_JR_HB, FrmJ>, JR_HB_DESC_BASE<"jr.hb", RO> {
2464  let isBranch=1;
2465  let isIndirectBranch=1;
2466  let hasDelaySlot=1;
2467  let isTerminator=1;
2468  let isBarrier=1;
2469  bit isCTI = 1;
2470}
2471
2472class JALR_HB_DESC<RegisterOperand RO> :
2473  InstSE<(outs), (ins), "", [], II_JALR_HB, FrmJ>, JALR_HB_DESC_BASE<"jalr.hb",
2474                                                                     RO> {
2475  let isIndirectBranch=1;
2476  let hasDelaySlot=1;
2477  bit isCTI = 1;
2478}
2479
2480class JR_HB_ENC : JR_HB_FM<8>;
2481class JALR_HB_ENC : JALR_HB_FM<9>;
2482
2483def JR_HB : JR_HB_DESC<GPR32Opnd>, JR_HB_ENC, ISA_MIPS32R2_NOT_32R6_64R6;
2484def JALR_HB : JALR_HB_DESC<GPR32Opnd>, JALR_HB_ENC, ISA_MIPS32;
2485
2486let AdditionalPredicates = [NotInMicroMips, UseIndirectJumpsHazard] in
2487  def JALRHBPseudo : JumpLinkRegPseudo<GPR32Opnd, JALR_HB, RA>;
2488
2489
2490let AdditionalPredicates = [NotInMips16Mode, NotInMicroMips,
2491                            UseIndirectJumpsHazard] in {
2492  def TAILCALLREGHB : TailCallReg<JR_HB, GPR32Opnd>, ISA_MIPS32_NOT_32R6_64R6;
2493  def PseudoIndirectHazardBranch : PseudoIndirectBranchBase<JR_HB, GPR32Opnd>,
2494                                   ISA_MIPS32R2_NOT_32R6_64R6;
2495}
2496
2497class TLB<string asmstr, InstrItinClass itin = NoItinerary> :
2498  InstSE<(outs), (ins), asmstr, [], itin, FrmOther, asmstr>;
2499let AdditionalPredicates = [NotInMicroMips] in {
2500  def TLBP : MMRel, TLB<"tlbp", II_TLBP>, COP0_TLB_FM<0x08>, ISA_MIPS1;
2501  def TLBR : MMRel, TLB<"tlbr", II_TLBR>, COP0_TLB_FM<0x01>, ISA_MIPS1;
2502  def TLBWI : MMRel, TLB<"tlbwi", II_TLBWI>, COP0_TLB_FM<0x02>, ISA_MIPS1;
2503  def TLBWR : MMRel, TLB<"tlbwr", II_TLBWR>, COP0_TLB_FM<0x06>, ISA_MIPS1;
2504}
2505class CacheOp<string instr_asm, Operand MemOpnd,
2506              InstrItinClass itin = NoItinerary> :
2507    InstSE<(outs), (ins  MemOpnd:$addr, uimm5:$hint),
2508           !strconcat(instr_asm, "\t$hint, $addr"), [], itin, FrmOther,
2509           instr_asm> {
2510  let DecoderMethod = "DecodeCacheOp";
2511}
2512
2513let AdditionalPredicates = [NotInMicroMips] in {
2514  def CACHE : MMRel, CacheOp<"cache", mem, II_CACHE>, CACHEOP_FM<0b101111>,
2515              INSN_MIPS3_32_NOT_32R6_64R6;
2516  def PREF :  MMRel, CacheOp<"pref", mem, II_PREF>, CACHEOP_FM<0b110011>,
2517              INSN_MIPS3_32_NOT_32R6_64R6;
2518}
2519// FIXME: We are missing the prefx instruction.
2520def ROL : MipsAsmPseudoInst<(outs),
2521                            (ins GPR32Opnd:$rs, GPR32Opnd:$rt, GPR32Opnd:$rd),
2522                            "rol\t$rs, $rt, $rd">;
2523def ROLImm : MipsAsmPseudoInst<(outs),
2524                               (ins GPR32Opnd:$rs, GPR32Opnd:$rt, simm16:$imm),
2525                               "rol\t$rs, $rt, $imm">;
2526def : MipsInstAlias<"rol $rd, $rs",
2527                    (ROL GPR32Opnd:$rd, GPR32Opnd:$rd, GPR32Opnd:$rs), 0>;
2528def : MipsInstAlias<"rol $rd, $imm",
2529                    (ROLImm GPR32Opnd:$rd, GPR32Opnd:$rd, simm16:$imm), 0>;
2530
2531def ROR : MipsAsmPseudoInst<(outs),
2532                            (ins GPR32Opnd:$rs, GPR32Opnd:$rt, GPR32Opnd:$rd),
2533                            "ror\t$rs, $rt, $rd">;
2534def RORImm : MipsAsmPseudoInst<(outs),
2535                               (ins GPR32Opnd:$rs, GPR32Opnd:$rt, simm16:$imm),
2536                               "ror\t$rs, $rt, $imm">;
2537def : MipsInstAlias<"ror $rd, $rs",
2538                    (ROR GPR32Opnd:$rd, GPR32Opnd:$rd, GPR32Opnd:$rs), 0>;
2539def : MipsInstAlias<"ror $rd, $imm",
2540                    (RORImm GPR32Opnd:$rd, GPR32Opnd:$rd, simm16:$imm), 0>;
2541
2542def DROL : MipsAsmPseudoInst<(outs),
2543                             (ins GPR32Opnd:$rs, GPR32Opnd:$rt, GPR32Opnd:$rd),
2544                             "drol\t$rs, $rt, $rd">, ISA_MIPS64;
2545def DROLImm : MipsAsmPseudoInst<(outs),
2546                                (ins GPR32Opnd:$rs, GPR32Opnd:$rt, simm16:$imm),
2547                                "drol\t$rs, $rt, $imm">, ISA_MIPS64;
2548def : MipsInstAlias<"drol $rd, $rs",
2549                    (DROL GPR32Opnd:$rd, GPR32Opnd:$rd, GPR32Opnd:$rs), 0>, ISA_MIPS64;
2550def : MipsInstAlias<"drol $rd, $imm",
2551                    (DROLImm GPR32Opnd:$rd, GPR32Opnd:$rd, simm16:$imm), 0>, ISA_MIPS64;
2552
2553def DROR : MipsAsmPseudoInst<(outs),
2554                             (ins GPR32Opnd:$rs, GPR32Opnd:$rt, GPR32Opnd:$rd),
2555                             "dror\t$rs, $rt, $rd">, ISA_MIPS64;
2556def DRORImm : MipsAsmPseudoInst<(outs),
2557                                (ins GPR32Opnd:$rs, GPR32Opnd:$rt, simm16:$imm),
2558                                "dror\t$rs, $rt, $imm">, ISA_MIPS64;
2559def : MipsInstAlias<"dror $rd, $rs",
2560                    (DROR GPR32Opnd:$rd, GPR32Opnd:$rd, GPR32Opnd:$rs), 0>, ISA_MIPS64;
2561def : MipsInstAlias<"dror $rd, $imm",
2562                    (DRORImm GPR32Opnd:$rd, GPR32Opnd:$rd, simm16:$imm), 0>, ISA_MIPS64;
2563
2564def ABSMacro : MipsAsmPseudoInst<(outs GPR32Opnd:$rd), (ins GPR32Opnd:$rs),
2565                                 "abs\t$rd, $rs">;
2566
2567def SEQMacro : MipsAsmPseudoInst<(outs GPR32Opnd:$rd),
2568                                 (ins GPR32Opnd:$rs, GPR32Opnd:$rt),
2569                                 "seq $rd, $rs, $rt">, NOT_ASE_CNMIPS;
2570
2571def : MipsInstAlias<"seq $rd, $rs",
2572                    (SEQMacro GPR32Opnd:$rd, GPR32Opnd:$rd, GPR32Opnd:$rs), 0>,
2573                    NOT_ASE_CNMIPS;
2574
2575def SEQIMacro : MipsAsmPseudoInst<(outs GPR32Opnd:$rd),
2576                                  (ins GPR32Opnd:$rs, simm32_relaxed:$imm),
2577                                  "seq $rd, $rs, $imm">, NOT_ASE_CNMIPS;
2578
2579def : MipsInstAlias<"seq $rd, $imm",
2580                    (SEQIMacro GPR32Opnd:$rd, GPR32Opnd:$rd, simm32:$imm), 0>,
2581                    NOT_ASE_CNMIPS;
2582
2583def MULImmMacro : MipsAsmPseudoInst<(outs), (ins GPR32Opnd:$rd, GPR32Opnd:$rs,
2584                                                 simm32_relaxed:$imm),
2585                                    "mul\t$rd, $rs, $imm">,
2586                  ISA_MIPS1_NOT_32R6_64R6;
2587def MULOMacro : MipsAsmPseudoInst<(outs), (ins GPR32Opnd:$rd, GPR32Opnd:$rs,
2588                                               GPR32Opnd:$rt),
2589                                  "mulo\t$rd, $rs, $rt">,
2590                ISA_MIPS1_NOT_32R6_64R6;
2591def MULOUMacro : MipsAsmPseudoInst<(outs), (ins GPR32Opnd:$rd, GPR32Opnd:$rs,
2592                                                GPR32Opnd:$rt),
2593                                   "mulou\t$rd, $rs, $rt">,
2594                 ISA_MIPS1_NOT_32R6_64R6;
2595
2596// Virtualization ASE
2597class HYPCALL_FT<string opstr> :
2598  InstSE<(outs), (ins uimm10:$code_),
2599         !strconcat(opstr, "\t$code_"), [], II_HYPCALL, FrmOther, opstr> {
2600  let BaseOpcode = opstr;
2601}
2602
2603let AdditionalPredicates = [NotInMicroMips] in {
2604  def MFGC0    : MMRel, MFC3OP<"mfgc0", GPR32Opnd, COP0Opnd, II_MFGC0>,
2605                 MFC3OP_FM<0x10, 3, 0>, ISA_MIPS32R5, ASE_VIRT;
2606  def MTGC0    : MMRel, MTC3OP<"mtgc0", COP0Opnd, GPR32Opnd, II_MTGC0>,
2607                 MFC3OP_FM<0x10, 3, 2>, ISA_MIPS32R5, ASE_VIRT;
2608  def MFHGC0   : MMRel, MFC3OP<"mfhgc0", GPR32Opnd, COP0Opnd, II_MFHGC0>,
2609                 MFC3OP_FM<0x10, 3, 4>, ISA_MIPS32R5, ASE_VIRT;
2610  def MTHGC0   : MMRel, MTC3OP<"mthgc0", COP0Opnd, GPR32Opnd, II_MTHGC0>,
2611                 MFC3OP_FM<0x10, 3, 6>, ISA_MIPS32R5, ASE_VIRT;
2612  def TLBGINV  : MMRel, TLB<"tlbginv", II_TLBGINV>, COP0_TLB_FM<0b001011>,
2613                 ISA_MIPS32R5, ASE_VIRT;
2614  def TLBGINVF : MMRel, TLB<"tlbginvf", II_TLBGINVF>, COP0_TLB_FM<0b001100>,
2615                 ISA_MIPS32R5, ASE_VIRT;
2616  def TLBGP    : MMRel, TLB<"tlbgp", II_TLBGP>, COP0_TLB_FM<0b010000>,
2617                 ISA_MIPS32R5, ASE_VIRT;
2618  def TLBGR    : MMRel, TLB<"tlbgr", II_TLBGR>, COP0_TLB_FM<0b001001>,
2619                 ISA_MIPS32R5, ASE_VIRT;
2620  def TLBGWI   : MMRel, TLB<"tlbgwi", II_TLBGWI>, COP0_TLB_FM<0b001010>,
2621                 ISA_MIPS32R5, ASE_VIRT;
2622  def TLBGWR   : MMRel, TLB<"tlbgwr", II_TLBGWR>, COP0_TLB_FM<0b001110>,
2623                 ISA_MIPS32R5, ASE_VIRT;
2624  def HYPCALL  : MMRel, HYPCALL_FT<"hypcall">,
2625                 HYPCALL_FM<0b101000>, ISA_MIPS32R5, ASE_VIRT;
2626}
2627
2628//===----------------------------------------------------------------------===//
2629// Instruction aliases
2630//===----------------------------------------------------------------------===//
2631
2632multiclass OneOrTwoOperandMacroImmediateAlias<string Memnomic,
2633                                              Instruction Opcode,
2634                                              RegisterOperand RO = GPR32Opnd,
2635                                              Operand Imm = simm32_relaxed> {
2636  def : MipsInstAlias<!strconcat(Memnomic, " $rs, $rt, $imm"),
2637                                (Opcode RO:$rs,
2638                                        RO:$rt,
2639                                        Imm:$imm), 0>;
2640  def : MipsInstAlias<!strconcat(Memnomic, " $rs, $imm"),
2641                                (Opcode RO:$rs,
2642                                        RO:$rs,
2643                                        Imm:$imm), 0>;
2644}
2645
2646let AdditionalPredicates = [NotInMicroMips] in {
2647  def : MipsInstAlias<"move $dst, $src",
2648                      (OR GPR32Opnd:$dst, GPR32Opnd:$src, ZERO), 1>,
2649        GPR_32, ISA_MIPS1;
2650  def : MipsInstAlias<"move $dst, $src",
2651                      (ADDu GPR32Opnd:$dst, GPR32Opnd:$src, ZERO), 1>,
2652        GPR_32, ISA_MIPS1;
2653
2654  def : MipsInstAlias<"bal $offset", (BGEZAL ZERO, brtarget:$offset), 1>,
2655        ISA_MIPS1_NOT_32R6_64R6;
2656
2657  def : MipsInstAlias<"j $rs", (JR GPR32Opnd:$rs), 0>, ISA_MIPS1;
2658
2659  def : MipsInstAlias<"jalr $rs", (JALR RA, GPR32Opnd:$rs), 0>;
2660
2661  def : MipsInstAlias<"jalr.hb $rs", (JALR_HB RA, GPR32Opnd:$rs), 1>,
2662        ISA_MIPS32;
2663
2664  def : MipsInstAlias<"neg $rt, $rs",
2665                      (SUB GPR32Opnd:$rt, ZERO, GPR32Opnd:$rs), 1>, ISA_MIPS1;
2666  def : MipsInstAlias<"neg $rt",
2667                      (SUB GPR32Opnd:$rt, ZERO, GPR32Opnd:$rt), 1>, ISA_MIPS1;
2668  def : MipsInstAlias<"negu $rt, $rs",
2669                      (SUBu GPR32Opnd:$rt, ZERO, GPR32Opnd:$rs), 1>, ISA_MIPS1;
2670  def : MipsInstAlias<"negu $rt",
2671                      (SUBu GPR32Opnd:$rt, ZERO, GPR32Opnd:$rt), 1>, ISA_MIPS1;
2672  def : MipsInstAlias<
2673          "sgt $rd, $rs, $rt",
2674          (SLT GPR32Opnd:$rd, GPR32Opnd:$rt, GPR32Opnd:$rs), 0>, ISA_MIPS1;
2675  def : MipsInstAlias<
2676          "sgt $rs, $rt",
2677          (SLT GPR32Opnd:$rs, GPR32Opnd:$rt, GPR32Opnd:$rs), 0>, ISA_MIPS1;
2678  def : MipsInstAlias<
2679          "sgtu $rd, $rs, $rt",
2680          (SLTu GPR32Opnd:$rd, GPR32Opnd:$rt, GPR32Opnd:$rs), 0>, ISA_MIPS1;
2681  def : MipsInstAlias<
2682          "sgtu $$rs, $rt",
2683          (SLTu GPR32Opnd:$rs, GPR32Opnd:$rt, GPR32Opnd:$rs), 0>, ISA_MIPS1;
2684  def : MipsInstAlias<
2685          "not $rt, $rs",
2686          (NOR GPR32Opnd:$rt, GPR32Opnd:$rs, ZERO), 0>, ISA_MIPS1;
2687  def : MipsInstAlias<
2688          "not $rt",
2689          (NOR GPR32Opnd:$rt, GPR32Opnd:$rt, ZERO), 0>, ISA_MIPS1;
2690
2691  def : MipsInstAlias<"nop", (SLL ZERO, ZERO, 0), 1>, ISA_MIPS1;
2692
2693  defm : OneOrTwoOperandMacroImmediateAlias<"add", ADDi>, ISA_MIPS1_NOT_32R6_64R6;
2694
2695  defm : OneOrTwoOperandMacroImmediateAlias<"addu", ADDiu>, ISA_MIPS1;
2696
2697  defm : OneOrTwoOperandMacroImmediateAlias<"and", ANDi>, ISA_MIPS1, GPR_32;
2698
2699  defm : OneOrTwoOperandMacroImmediateAlias<"or", ORi>, ISA_MIPS1, GPR_32;
2700
2701  defm : OneOrTwoOperandMacroImmediateAlias<"xor", XORi>, ISA_MIPS1, GPR_32;
2702
2703  defm : OneOrTwoOperandMacroImmediateAlias<"slt", SLTi>, ISA_MIPS1, GPR_32;
2704
2705  defm : OneOrTwoOperandMacroImmediateAlias<"sltu", SLTiu>, ISA_MIPS1, GPR_32;
2706
2707  def : MipsInstAlias<"mfgc0 $rt, $rd",
2708                      (MFGC0 GPR32Opnd:$rt, COP0Opnd:$rd, 0), 0>,
2709                      ISA_MIPS32R5, ASE_VIRT;
2710  def : MipsInstAlias<"mtgc0 $rt, $rd",
2711                      (MTGC0 COP0Opnd:$rd, GPR32Opnd:$rt, 0), 0>,
2712                      ISA_MIPS32R5, ASE_VIRT;
2713  def : MipsInstAlias<"mfhgc0 $rt, $rd",
2714                      (MFHGC0 GPR32Opnd:$rt, COP0Opnd:$rd, 0), 0>,
2715                      ISA_MIPS32R5, ASE_VIRT;
2716  def : MipsInstAlias<"mthgc0 $rt, $rd",
2717                      (MTHGC0 COP0Opnd:$rd, GPR32Opnd:$rt, 0), 0>,
2718                      ISA_MIPS32R5, ASE_VIRT;
2719  def : MipsInstAlias<"mfc0 $rt, $rd", (MFC0 GPR32Opnd:$rt, COP0Opnd:$rd, 0), 0>,
2720        ISA_MIPS1;
2721  def : MipsInstAlias<"mtc0 $rt, $rd", (MTC0 COP0Opnd:$rd, GPR32Opnd:$rt, 0), 0>,
2722        ISA_MIPS1;
2723  def : MipsInstAlias<"mfc2 $rt, $rd", (MFC2 GPR32Opnd:$rt, COP2Opnd:$rd, 0), 0>,
2724        ISA_MIPS1;
2725  def : MipsInstAlias<"mtc2 $rt, $rd", (MTC2 COP2Opnd:$rd, GPR32Opnd:$rt, 0), 0>,
2726        ISA_MIPS1;
2727
2728  def : MipsInstAlias<"b $offset", (BEQ ZERO, ZERO, brtarget:$offset), 0>,
2729        ISA_MIPS1;
2730
2731  def : MipsInstAlias<"bnez $rs,$offset",
2732                      (BNE GPR32Opnd:$rs, ZERO, brtarget:$offset), 0>,
2733        ISA_MIPS1;
2734  def : MipsInstAlias<"bnezl $rs,$offset",
2735                      (BNEL GPR32Opnd:$rs, ZERO, brtarget:$offset), 0>,
2736        ISA_MIPS2;
2737  def : MipsInstAlias<"beqz $rs,$offset",
2738                      (BEQ GPR32Opnd:$rs, ZERO, brtarget:$offset), 0>,
2739        ISA_MIPS1;
2740  def : MipsInstAlias<"beqzl $rs,$offset",
2741                      (BEQL GPR32Opnd:$rs, ZERO, brtarget:$offset), 0>,
2742        ISA_MIPS2;
2743
2744  def : MipsInstAlias<"syscall", (SYSCALL 0), 1>, ISA_MIPS1;
2745
2746  def : MipsInstAlias<"break", (BREAK 0, 0), 1>, ISA_MIPS1;
2747  def : MipsInstAlias<"break $imm", (BREAK uimm10:$imm, 0), 1>, ISA_MIPS1;
2748  def : MipsInstAlias<"ei", (EI ZERO), 1>, ISA_MIPS32R2;
2749  def : MipsInstAlias<"di", (DI ZERO), 1>, ISA_MIPS32R2;
2750
2751  def : MipsInstAlias<"teq $rs, $rt",
2752                      (TEQ GPR32Opnd:$rs, GPR32Opnd:$rt, 0), 1>, ISA_MIPS2;
2753  def : MipsInstAlias<"tge $rs, $rt",
2754                      (TGE GPR32Opnd:$rs, GPR32Opnd:$rt, 0), 1>, ISA_MIPS2;
2755  def : MipsInstAlias<"tgeu $rs, $rt",
2756                      (TGEU GPR32Opnd:$rs, GPR32Opnd:$rt, 0), 1>, ISA_MIPS2;
2757  def : MipsInstAlias<"tlt $rs, $rt",
2758                      (TLT GPR32Opnd:$rs, GPR32Opnd:$rt, 0), 1>, ISA_MIPS2;
2759  def : MipsInstAlias<"tltu $rs, $rt",
2760                      (TLTU GPR32Opnd:$rs, GPR32Opnd:$rt, 0), 1>, ISA_MIPS2;
2761  def : MipsInstAlias<"tne $rs, $rt",
2762                      (TNE GPR32Opnd:$rs, GPR32Opnd:$rt, 0), 1>, ISA_MIPS2;
2763  def : MipsInstAlias<"rdhwr $rt, $rs",
2764                      (RDHWR GPR32Opnd:$rt, HWRegsOpnd:$rs, 0), 1>, ISA_MIPS1;
2765
2766}
2767def : MipsInstAlias<"sub, $rd, $rs, $imm",
2768                    (ADDi GPR32Opnd:$rd, GPR32Opnd:$rs,
2769                          InvertedImOperand:$imm), 0>, ISA_MIPS1_NOT_32R6_64R6;
2770def : MipsInstAlias<"sub $rs, $imm",
2771                    (ADDi GPR32Opnd:$rs, GPR32Opnd:$rs, InvertedImOperand:$imm),
2772                    0>, ISA_MIPS1_NOT_32R6_64R6;
2773def : MipsInstAlias<"subu, $rd, $rs, $imm",
2774                    (ADDiu GPR32Opnd:$rd, GPR32Opnd:$rs,
2775                           InvertedImOperand:$imm), 0>;
2776def : MipsInstAlias<"subu $rs, $imm", (ADDiu GPR32Opnd:$rs, GPR32Opnd:$rs,
2777                                             InvertedImOperand:$imm), 0>;
2778let AdditionalPredicates = [NotInMicroMips] in {
2779  def : MipsInstAlias<"sll $rd, $rt, $rs",
2780                      (SLLV GPR32Opnd:$rd, GPR32Opnd:$rt, GPR32Opnd:$rs), 0>;
2781  def : MipsInstAlias<"sra $rd, $rt, $rs",
2782                      (SRAV GPR32Opnd:$rd, GPR32Opnd:$rt, GPR32Opnd:$rs), 0>;
2783  def : MipsInstAlias<"srl $rd, $rt, $rs",
2784                      (SRLV GPR32Opnd:$rd, GPR32Opnd:$rt, GPR32Opnd:$rs), 0>;
2785  def : MipsInstAlias<"sll $rd, $rt",
2786                      (SLLV GPR32Opnd:$rd, GPR32Opnd:$rd, GPR32Opnd:$rt), 0>;
2787  def : MipsInstAlias<"sra $rd, $rt",
2788                      (SRAV GPR32Opnd:$rd, GPR32Opnd:$rd, GPR32Opnd:$rt), 0>;
2789  def : MipsInstAlias<"srl $rd, $rt",
2790                      (SRLV GPR32Opnd:$rd, GPR32Opnd:$rd, GPR32Opnd:$rt), 0>;
2791  def : MipsInstAlias<"seh $rd", (SEH GPR32Opnd:$rd, GPR32Opnd:$rd), 0>,
2792                     ISA_MIPS32R2;
2793  def : MipsInstAlias<"seb $rd", (SEB GPR32Opnd:$rd, GPR32Opnd:$rd), 0>,
2794                     ISA_MIPS32R2;
2795}
2796def : MipsInstAlias<"sdbbp", (SDBBP 0)>, ISA_MIPS32_NOT_32R6_64R6;
2797let AdditionalPredicates = [NotInMicroMips] in
2798  def : MipsInstAlias<"sync", (SYNC 0), 1>, ISA_MIPS2;
2799
2800def : MipsInstAlias<"mulo $rs, $rt",
2801                    (MULOMacro GPR32Opnd:$rs, GPR32Opnd:$rs, GPR32Opnd:$rt), 0>,
2802                    ISA_MIPS1_NOT_32R6_64R6;
2803def : MipsInstAlias<"mulou $rs, $rt",
2804                    (MULOUMacro GPR32Opnd:$rs, GPR32Opnd:$rs, GPR32Opnd:$rt), 0>,
2805                    ISA_MIPS1_NOT_32R6_64R6;
2806
2807let AdditionalPredicates = [NotInMicroMips] in
2808  def : MipsInstAlias<"hypcall", (HYPCALL 0), 1>, ISA_MIPS32R5, ASE_VIRT;
2809
2810//===----------------------------------------------------------------------===//
2811// Assembler Pseudo Instructions
2812//===----------------------------------------------------------------------===//
2813
2814// We use uimm32_coerced to accept a 33 bit signed number that is rendered into
2815// a 32 bit number.
2816class LoadImmediate32<string instr_asm, Operand Od, RegisterOperand RO> :
2817  MipsAsmPseudoInst<(outs RO:$rt), (ins Od:$imm32),
2818                     !strconcat(instr_asm, "\t$rt, $imm32")> ;
2819def LoadImm32 : LoadImmediate32<"li", uimm32_coerced, GPR32Opnd>;
2820
2821class LoadAddressFromReg32<string instr_asm, Operand MemOpnd,
2822                           RegisterOperand RO> :
2823  MipsAsmPseudoInst<(outs RO:$rt), (ins MemOpnd:$addr),
2824                     !strconcat(instr_asm, "\t$rt, $addr")> ;
2825def LoadAddrReg32 : LoadAddressFromReg32<"la", mem, GPR32Opnd>;
2826
2827class LoadAddressFromImm32<string instr_asm, Operand Od, RegisterOperand RO> :
2828  MipsAsmPseudoInst<(outs RO:$rt), (ins Od:$imm32),
2829                     !strconcat(instr_asm, "\t$rt, $imm32")> ;
2830def LoadAddrImm32 : LoadAddressFromImm32<"la", i32imm, GPR32Opnd>;
2831
2832def JalTwoReg : MipsAsmPseudoInst<(outs GPR32Opnd:$rd), (ins GPR32Opnd:$rs),
2833                      "jal\t$rd, $rs"> ;
2834def JalOneReg : MipsAsmPseudoInst<(outs), (ins GPR32Opnd:$rs),
2835                      "jal\t$rs"> ;
2836
2837class NORIMM_DESC_BASE<RegisterOperand RO, DAGOperand Imm> :
2838   MipsAsmPseudoInst<(outs RO:$rs), (ins RO:$rt, Imm:$imm),
2839                      "nor\t$rs, $rt, $imm">;
2840def NORImm : NORIMM_DESC_BASE<GPR32Opnd, simm32_relaxed>, GPR_32;
2841def : MipsInstAlias<"nor\t$rs, $imm", (NORImm GPR32Opnd:$rs, GPR32Opnd:$rs,
2842                                              simm32_relaxed:$imm)>, GPR_32;
2843
2844let hasDelaySlot = 1, isCTI = 1 in {
2845def BneImm : MipsAsmPseudoInst<(outs GPR32Opnd:$rt),
2846                               (ins imm64:$imm64, brtarget:$offset),
2847                               "bne\t$rt, $imm64, $offset">;
2848def BeqImm : MipsAsmPseudoInst<(outs GPR32Opnd:$rt),
2849                               (ins imm64:$imm64, brtarget:$offset),
2850                               "beq\t$rt, $imm64, $offset">;
2851
2852class CondBranchPseudo<string instr_asm> :
2853  MipsAsmPseudoInst<(outs), (ins GPR32Opnd:$rs, GPR32Opnd:$rt,
2854                                 brtarget:$offset),
2855                    !strconcat(instr_asm, "\t$rs, $rt, $offset")>;
2856}
2857
2858def BLT : CondBranchPseudo<"blt">;
2859def BLE : CondBranchPseudo<"ble">;
2860def BGE : CondBranchPseudo<"bge">;
2861def BGT : CondBranchPseudo<"bgt">;
2862def BLTU : CondBranchPseudo<"bltu">;
2863def BLEU : CondBranchPseudo<"bleu">;
2864def BGEU : CondBranchPseudo<"bgeu">;
2865def BGTU : CondBranchPseudo<"bgtu">;
2866def BLTL : CondBranchPseudo<"bltl">, ISA_MIPS2_NOT_32R6_64R6;
2867def BLEL : CondBranchPseudo<"blel">, ISA_MIPS2_NOT_32R6_64R6;
2868def BGEL : CondBranchPseudo<"bgel">, ISA_MIPS2_NOT_32R6_64R6;
2869def BGTL : CondBranchPseudo<"bgtl">, ISA_MIPS2_NOT_32R6_64R6;
2870def BLTUL: CondBranchPseudo<"bltul">, ISA_MIPS2_NOT_32R6_64R6;
2871def BLEUL: CondBranchPseudo<"bleul">, ISA_MIPS2_NOT_32R6_64R6;
2872def BGEUL: CondBranchPseudo<"bgeul">, ISA_MIPS2_NOT_32R6_64R6;
2873def BGTUL: CondBranchPseudo<"bgtul">, ISA_MIPS2_NOT_32R6_64R6;
2874
2875let isCTI = 1 in
2876class CondBranchImmPseudo<string instr_asm> :
2877  MipsAsmPseudoInst<(outs), (ins GPR32Opnd:$rs, imm64:$imm, brtarget:$offset),
2878                    !strconcat(instr_asm, "\t$rs, $imm, $offset")>;
2879
2880def BEQLImmMacro : CondBranchImmPseudo<"beql">, ISA_MIPS2_NOT_32R6_64R6;
2881def BNELImmMacro : CondBranchImmPseudo<"bnel">, ISA_MIPS2_NOT_32R6_64R6;
2882
2883def BLTImmMacro  : CondBranchImmPseudo<"blt">;
2884def BLEImmMacro  : CondBranchImmPseudo<"ble">;
2885def BGEImmMacro  : CondBranchImmPseudo<"bge">;
2886def BGTImmMacro  : CondBranchImmPseudo<"bgt">;
2887def BLTUImmMacro : CondBranchImmPseudo<"bltu">;
2888def BLEUImmMacro : CondBranchImmPseudo<"bleu">;
2889def BGEUImmMacro : CondBranchImmPseudo<"bgeu">;
2890def BGTUImmMacro : CondBranchImmPseudo<"bgtu">;
2891def BLTLImmMacro : CondBranchImmPseudo<"bltl">, ISA_MIPS2_NOT_32R6_64R6;
2892def BLELImmMacro : CondBranchImmPseudo<"blel">, ISA_MIPS2_NOT_32R6_64R6;
2893def BGELImmMacro : CondBranchImmPseudo<"bgel">, ISA_MIPS2_NOT_32R6_64R6;
2894def BGTLImmMacro : CondBranchImmPseudo<"bgtl">, ISA_MIPS2_NOT_32R6_64R6;
2895def BLTULImmMacro : CondBranchImmPseudo<"bltul">, ISA_MIPS2_NOT_32R6_64R6;
2896def BLEULImmMacro : CondBranchImmPseudo<"bleul">, ISA_MIPS2_NOT_32R6_64R6;
2897def BGEULImmMacro : CondBranchImmPseudo<"bgeul">, ISA_MIPS2_NOT_32R6_64R6;
2898def BGTULImmMacro : CondBranchImmPseudo<"bgtul">, ISA_MIPS2_NOT_32R6_64R6;
2899
2900// FIXME: Predicates are removed because instructions are matched regardless of
2901// predicates, because PredicateControl was not in the hierarchy. This was
2902// done to emit more precise error message from expansion function.
2903// Once the tablegen-erated errors are made better, this needs to be fixed and
2904// predicates needs to be restored.
2905
2906def SDivMacro : MipsAsmPseudoInst<(outs GPR32NonZeroOpnd:$rd),
2907                                  (ins GPR32Opnd:$rs, GPR32Opnd:$rt),
2908                                  "div\t$rd, $rs, $rt">,
2909                ISA_MIPS1_NOT_32R6_64R6;
2910def SDivIMacro : MipsAsmPseudoInst<(outs GPR32Opnd:$rd),
2911                                   (ins GPR32Opnd:$rs, simm32:$imm),
2912                                   "div\t$rd, $rs, $imm">,
2913                 ISA_MIPS1_NOT_32R6_64R6;
2914def UDivMacro : MipsAsmPseudoInst<(outs GPR32Opnd:$rd),
2915                                  (ins GPR32Opnd:$rs, GPR32Opnd:$rt),
2916                                  "divu\t$rd, $rs, $rt">,
2917                ISA_MIPS1_NOT_32R6_64R6;
2918def UDivIMacro : MipsAsmPseudoInst<(outs GPR32Opnd:$rd),
2919                                   (ins GPR32Opnd:$rs, simm32:$imm),
2920                                   "divu\t$rd, $rs, $imm">,
2921                 ISA_MIPS1_NOT_32R6_64R6;
2922
2923
2924def : MipsInstAlias<"div $rs, $rt", (SDIV GPR32ZeroOpnd:$rs,
2925                                          GPR32Opnd:$rt), 0>,
2926     ISA_MIPS1_NOT_32R6_64R6;
2927def : MipsInstAlias<"div $rs, $rt", (SDivMacro GPR32NonZeroOpnd:$rs,
2928                                               GPR32NonZeroOpnd:$rs,
2929                                               GPR32Opnd:$rt), 0>,
2930     ISA_MIPS1_NOT_32R6_64R6;
2931def : MipsInstAlias<"div $rd, $imm", (SDivIMacro GPR32Opnd:$rd, GPR32Opnd:$rd,
2932                                                 simm32:$imm), 0>,
2933      ISA_MIPS1_NOT_32R6_64R6;
2934
2935def : MipsInstAlias<"divu $rt, $rs", (UDIV GPR32ZeroOpnd:$rt,
2936                                           GPR32Opnd:$rs), 0>,
2937      ISA_MIPS1_NOT_32R6_64R6;
2938def : MipsInstAlias<"divu $rt, $rs", (UDivMacro GPR32NonZeroOpnd:$rt,
2939                                                GPR32NonZeroOpnd:$rt,
2940                                                GPR32Opnd:$rs), 0>,
2941      ISA_MIPS1_NOT_32R6_64R6;
2942
2943def : MipsInstAlias<"divu $rd, $imm", (UDivIMacro GPR32Opnd:$rd, GPR32Opnd:$rd,
2944                                                  simm32:$imm), 0>,
2945      ISA_MIPS1_NOT_32R6_64R6;
2946
2947def SRemMacro : MipsAsmPseudoInst<(outs GPR32Opnd:$rd),
2948                                  (ins GPR32Opnd:$rs, GPR32Opnd:$rt),
2949                                  "rem\t$rd, $rs, $rt">,
2950                ISA_MIPS1_NOT_32R6_64R6;
2951def SRemIMacro : MipsAsmPseudoInst<(outs GPR32Opnd:$rd),
2952                                   (ins GPR32Opnd:$rs, simm32_relaxed:$imm),
2953                                   "rem\t$rd, $rs, $imm">,
2954                 ISA_MIPS1_NOT_32R6_64R6;
2955def URemMacro : MipsAsmPseudoInst<(outs GPR32Opnd:$rd),
2956                                  (ins GPR32Opnd:$rs, GPR32Opnd:$rt),
2957                                  "remu\t$rd, $rs, $rt">,
2958                ISA_MIPS1_NOT_32R6_64R6;
2959def URemIMacro : MipsAsmPseudoInst<(outs GPR32Opnd:$rd),
2960                                   (ins GPR32Opnd:$rs, simm32_relaxed:$imm),
2961                                   "remu\t$rd, $rs, $imm">,
2962                 ISA_MIPS1_NOT_32R6_64R6;
2963
2964def : MipsInstAlias<"rem $rt, $rs", (SRemMacro GPR32Opnd:$rt, GPR32Opnd:$rt,
2965                                               GPR32Opnd:$rs), 0>,
2966      ISA_MIPS1_NOT_32R6_64R6;
2967def : MipsInstAlias<"rem $rd, $imm", (SRemIMacro GPR32Opnd:$rd, GPR32Opnd:$rd,
2968                                      simm32_relaxed:$imm), 0>,
2969      ISA_MIPS1_NOT_32R6_64R6;
2970def : MipsInstAlias<"remu $rt, $rs", (URemMacro GPR32Opnd:$rt, GPR32Opnd:$rt,
2971                                                GPR32Opnd:$rs), 0>,
2972      ISA_MIPS1_NOT_32R6_64R6;
2973def : MipsInstAlias<"remu $rd, $imm", (URemIMacro GPR32Opnd:$rd, GPR32Opnd:$rd,
2974                                       simm32_relaxed:$imm), 0>,
2975      ISA_MIPS1_NOT_32R6_64R6;
2976
2977def Ulh : MipsAsmPseudoInst<(outs GPR32Opnd:$rt), (ins mem:$addr),
2978                            "ulh\t$rt, $addr">; //, ISA_MIPS1_NOT_32R6_64R6;
2979
2980def Ulhu : MipsAsmPseudoInst<(outs GPR32Opnd:$rt), (ins mem:$addr),
2981                             "ulhu\t$rt, $addr">; //, ISA_MIPS1_NOT_32R6_64R6;
2982
2983def Ulw : MipsAsmPseudoInst<(outs GPR32Opnd:$rt), (ins mem:$addr),
2984                            "ulw\t$rt, $addr">; //, ISA_MIPS1_NOT_32R6_64R6;
2985
2986def Ush : MipsAsmPseudoInst<(outs GPR32Opnd:$rt), (ins mem:$addr),
2987                            "ush\t$rt, $addr">; //, ISA_MIPS1_NOT_32R6_64R6;
2988
2989def Usw : MipsAsmPseudoInst<(outs GPR32Opnd:$rt), (ins mem:$addr),
2990                            "usw\t$rt, $addr">; //, ISA_MIPS1_NOT_32R6_64R6;
2991
2992def LDMacro : MipsAsmPseudoInst<(outs GPR32Opnd:$rt),
2993                                (ins mem_simm16:$addr), "ld $rt, $addr">,
2994                                ISA_MIPS1_NOT_MIPS3;
2995def SDMacro : MipsAsmPseudoInst<(outs GPR32Opnd:$rt),
2996                                (ins mem_simm16:$addr), "sd $rt, $addr">,
2997                                ISA_MIPS1_NOT_MIPS3;
2998//===----------------------------------------------------------------------===//
2999//  Arbitrary patterns that map to one or more instructions
3000//===----------------------------------------------------------------------===//
3001
3002// Load/store pattern templates.
3003class LoadRegImmPat<Instruction LoadInst, ValueType ValTy, PatFrag Node> :
3004  MipsPat<(ValTy (Node addrRegImm:$a)), (LoadInst addrRegImm:$a)>;
3005
3006class StoreRegImmPat<Instruction StoreInst, ValueType ValTy> :
3007  MipsPat<(store ValTy:$v, addrRegImm:$a), (StoreInst ValTy:$v, addrRegImm:$a)>;
3008
3009// Materialize constants.
3010multiclass MaterializeImms<ValueType VT, Register ZEROReg,
3011                           Instruction ADDiuOp, Instruction LUiOp,
3012                           Instruction ORiOp> {
3013
3014// Constant synthesis previously relied on the ordering of the patterns below.
3015// By making the predicates they use non-overlapping, the patterns were
3016// reordered so that the effect of the newly introduced predicates can be
3017// observed.
3018
3019// Arbitrary immediates
3020def : MipsPat<(VT LUiORiPred:$imm), (ORiOp (LUiOp (HI16 imm:$imm)), (LO16 imm:$imm))>;
3021
3022// Bits 32-16 set, sign/zero extended.
3023def : MipsPat<(VT LUiPred:$imm), (LUiOp (HI16 imm:$imm))>;
3024
3025// Small immediates
3026def : MipsPat<(VT ORiPred:$imm), (ORiOp ZEROReg, imm:$imm)>;
3027def : MipsPat<(VT immSExt16:$imm), (ADDiuOp ZEROReg, imm:$imm)>;
3028}
3029
3030let AdditionalPredicates = [NotInMicroMips] in
3031  defm : MaterializeImms<i32, ZERO, ADDiu, LUi, ORi>, ISA_MIPS1;
3032
3033// Carry MipsPatterns
3034let AdditionalPredicates = [NotInMicroMips] in {
3035  def : MipsPat<(subc GPR32:$lhs, GPR32:$rhs),
3036                (SUBu GPR32:$lhs, GPR32:$rhs)>, ISA_MIPS1;
3037}
3038def : MipsPat<(addc GPR32:$lhs, GPR32:$rhs),
3039              (ADDu GPR32:$lhs, GPR32:$rhs)>, ISA_MIPS1, ASE_NOT_DSP;
3040def : MipsPat<(addc  GPR32:$src, immSExt16:$imm),
3041              (ADDiu GPR32:$src, imm:$imm)>, ISA_MIPS1, ASE_NOT_DSP;
3042
3043// Support multiplication for pre-Mips32 targets that don't have
3044// the MUL instruction.
3045def : MipsPat<(mul GPR32:$lhs, GPR32:$rhs),
3046              (PseudoMFLO (PseudoMULT GPR32:$lhs, GPR32:$rhs))>,
3047      ISA_MIPS1_NOT_32R6_64R6;
3048
3049// SYNC
3050def : MipsPat<(MipsSync (i32 immz)),
3051              (SYNC 0)>, ISA_MIPS2;
3052
3053// Call
3054def : MipsPat<(MipsJmpLink (i32 texternalsym:$dst)),
3055              (JAL texternalsym:$dst)>, ISA_MIPS1;
3056//def : MipsPat<(MipsJmpLink GPR32:$dst),
3057//              (JALR GPR32:$dst)>;
3058
3059// Tail call
3060let AdditionalPredicates = [NotInMicroMips] in {
3061  def : MipsPat<(MipsTailCall (iPTR tglobaladdr:$dst)),
3062                (TAILCALL tglobaladdr:$dst)>, ISA_MIPS1;
3063  def : MipsPat<(MipsTailCall (iPTR texternalsym:$dst)),
3064                (TAILCALL texternalsym:$dst)>, ISA_MIPS1;
3065}
3066// hi/lo relocs
3067multiclass MipsHiLoRelocs<Instruction Lui, Instruction Addiu,
3068                          Register ZeroReg, RegisterOperand GPROpnd> {
3069  def : MipsPat<(MipsHi tglobaladdr:$in), (Lui tglobaladdr:$in)>;
3070  def : MipsPat<(MipsHi tblockaddress:$in), (Lui tblockaddress:$in)>;
3071  def : MipsPat<(MipsHi tjumptable:$in), (Lui tjumptable:$in)>;
3072  def : MipsPat<(MipsHi tconstpool:$in), (Lui tconstpool:$in)>;
3073  def : MipsPat<(MipsHi texternalsym:$in), (Lui texternalsym:$in)>;
3074
3075  def : MipsPat<(MipsLo tglobaladdr:$in), (Addiu ZeroReg, tglobaladdr:$in)>;
3076  def : MipsPat<(MipsLo tblockaddress:$in),
3077                (Addiu ZeroReg, tblockaddress:$in)>;
3078  def : MipsPat<(MipsLo tjumptable:$in), (Addiu ZeroReg, tjumptable:$in)>;
3079  def : MipsPat<(MipsLo tconstpool:$in), (Addiu ZeroReg, tconstpool:$in)>;
3080  def : MipsPat<(MipsLo tglobaltlsaddr:$in),
3081                (Addiu ZeroReg, tglobaltlsaddr:$in)>;
3082  def : MipsPat<(MipsLo texternalsym:$in), (Addiu ZeroReg, texternalsym:$in)>;
3083
3084  def : MipsPat<(add GPROpnd:$hi, (MipsLo tglobaladdr:$lo)),
3085              (Addiu GPROpnd:$hi, tglobaladdr:$lo)>;
3086  def : MipsPat<(add GPROpnd:$hi, (MipsLo tblockaddress:$lo)),
3087              (Addiu GPROpnd:$hi, tblockaddress:$lo)>;
3088  def : MipsPat<(add GPROpnd:$hi, (MipsLo tjumptable:$lo)),
3089              (Addiu GPROpnd:$hi, tjumptable:$lo)>;
3090  def : MipsPat<(add GPROpnd:$hi, (MipsLo tconstpool:$lo)),
3091              (Addiu GPROpnd:$hi, tconstpool:$lo)>;
3092  def : MipsPat<(add GPROpnd:$hi, (MipsLo tglobaltlsaddr:$lo)),
3093              (Addiu GPROpnd:$hi, tglobaltlsaddr:$lo)>;
3094}
3095
3096// wrapper_pic
3097class WrapperPat<SDNode node, Instruction ADDiuOp, RegisterClass RC>:
3098      MipsPat<(MipsWrapper RC:$gp, node:$in), (ADDiuOp RC:$gp, node:$in)>;
3099
3100let AdditionalPredicates = [NotInMicroMips] in {
3101  defm : MipsHiLoRelocs<LUi, ADDiu, ZERO, GPR32Opnd>, ISA_MIPS1;
3102
3103  def : MipsPat<(MipsGotHi tglobaladdr:$in), (LUi tglobaladdr:$in)>, ISA_MIPS1;
3104  def : MipsPat<(MipsGotHi texternalsym:$in), (LUi texternalsym:$in)>,
3105        ISA_MIPS1;
3106
3107  def : MipsPat<(MipsTlsHi tglobaltlsaddr:$in), (LUi tglobaltlsaddr:$in)>,
3108        ISA_MIPS1;
3109
3110  // gp_rel relocs
3111  def : MipsPat<(add GPR32:$gp, (MipsGPRel tglobaladdr:$in)),
3112                (ADDiu GPR32:$gp, tglobaladdr:$in)>, ISA_MIPS1, ABI_NOT_N64;
3113  def : MipsPat<(add GPR32:$gp, (MipsGPRel tconstpool:$in)),
3114                (ADDiu GPR32:$gp, tconstpool:$in)>, ISA_MIPS1, ABI_NOT_N64;
3115
3116  def : WrapperPat<tglobaladdr, ADDiu, GPR32>, ISA_MIPS1;
3117  def : WrapperPat<tconstpool, ADDiu, GPR32>, ISA_MIPS1;
3118  def : WrapperPat<texternalsym, ADDiu, GPR32>, ISA_MIPS1;
3119  def : WrapperPat<tblockaddress, ADDiu, GPR32>, ISA_MIPS1;
3120  def : WrapperPat<tjumptable, ADDiu, GPR32>, ISA_MIPS1;
3121  def : WrapperPat<tglobaltlsaddr, ADDiu, GPR32>, ISA_MIPS1;
3122
3123  // Mips does not have "not", so we expand our way
3124  def : MipsPat<(not GPR32:$in),
3125                (NOR GPR32Opnd:$in, ZERO)>, ISA_MIPS1;
3126}
3127
3128// extended loads
3129let AdditionalPredicates = [NotInMicroMips] in {
3130  def : MipsPat<(i32 (extloadi1  addr:$src)), (LBu addr:$src)>, ISA_MIPS1;
3131  def : MipsPat<(i32 (extloadi8  addr:$src)), (LBu addr:$src)>, ISA_MIPS1;
3132  def : MipsPat<(i32 (extloadi16 addr:$src)), (LHu addr:$src)>, ISA_MIPS1;
3133
3134  // peepholes
3135  def : MipsPat<(store (i32 0), addr:$dst), (SW ZERO, addr:$dst)>, ISA_MIPS1;
3136}
3137
3138// brcond patterns
3139multiclass BrcondPats<RegisterClass RC, Instruction BEQOp, Instruction BEQOp1,
3140                      Instruction BNEOp, Instruction SLTOp, Instruction SLTuOp,
3141                      Instruction SLTiOp, Instruction SLTiuOp,
3142                      Register ZEROReg> {
3143def : MipsPat<(brcond (i32 (setne RC:$lhs, 0)), bb:$dst),
3144              (BNEOp RC:$lhs, ZEROReg, bb:$dst)>;
3145def : MipsPat<(brcond (i32 (seteq RC:$lhs, 0)), bb:$dst),
3146              (BEQOp RC:$lhs, ZEROReg, bb:$dst)>;
3147
3148def : MipsPat<(brcond (i32 (setge RC:$lhs, RC:$rhs)), bb:$dst),
3149              (BEQOp1 (SLTOp RC:$lhs, RC:$rhs), ZERO, bb:$dst)>;
3150def : MipsPat<(brcond (i32 (setuge RC:$lhs, RC:$rhs)), bb:$dst),
3151              (BEQOp1 (SLTuOp RC:$lhs, RC:$rhs), ZERO, bb:$dst)>;
3152def : MipsPat<(brcond (i32 (setge RC:$lhs, immSExt16:$rhs)), bb:$dst),
3153              (BEQOp1 (SLTiOp RC:$lhs, immSExt16:$rhs), ZERO, bb:$dst)>;
3154def : MipsPat<(brcond (i32 (setuge RC:$lhs, immSExt16:$rhs)), bb:$dst),
3155              (BEQOp1 (SLTiuOp RC:$lhs, immSExt16:$rhs), ZERO, bb:$dst)>;
3156def : MipsPat<(brcond (i32 (setgt RC:$lhs, immSExt16Plus1:$rhs)), bb:$dst),
3157              (BEQOp1 (SLTiOp RC:$lhs, (Plus1 imm:$rhs)), ZERO, bb:$dst)>;
3158def : MipsPat<(brcond (i32 (setugt RC:$lhs, immSExt16Plus1:$rhs)), bb:$dst),
3159              (BEQOp1 (SLTiuOp RC:$lhs, (Plus1 imm:$rhs)), ZERO, bb:$dst)>;
3160
3161def : MipsPat<(brcond (i32 (setle RC:$lhs, RC:$rhs)), bb:$dst),
3162              (BEQOp1 (SLTOp RC:$rhs, RC:$lhs), ZERO, bb:$dst)>;
3163def : MipsPat<(brcond (i32 (setule RC:$lhs, RC:$rhs)), bb:$dst),
3164              (BEQOp1 (SLTuOp RC:$rhs, RC:$lhs), ZERO, bb:$dst)>;
3165
3166def : MipsPat<(brcond RC:$cond, bb:$dst),
3167              (BNEOp RC:$cond, ZEROReg, bb:$dst)>;
3168}
3169let AdditionalPredicates = [NotInMicroMips] in {
3170  defm : BrcondPats<GPR32, BEQ, BEQ, BNE, SLT, SLTu, SLTi, SLTiu, ZERO>,
3171         ISA_MIPS1;
3172  def : MipsPat<(brcond (i32 (setlt i32:$lhs, 1)), bb:$dst),
3173                (BLEZ i32:$lhs, bb:$dst)>, ISA_MIPS1;
3174  def : MipsPat<(brcond (i32 (setgt i32:$lhs, -1)), bb:$dst),
3175                (BGEZ i32:$lhs, bb:$dst)>, ISA_MIPS1;
3176}
3177
3178// setcc patterns
3179multiclass SeteqPats<RegisterClass RC, Instruction SLTiuOp, Instruction XOROp,
3180                     Instruction SLTuOp, Register ZEROReg> {
3181  def : MipsPat<(seteq RC:$lhs, 0),
3182                (SLTiuOp RC:$lhs, 1)>;
3183  def : MipsPat<(setne RC:$lhs, 0),
3184                (SLTuOp ZEROReg, RC:$lhs)>;
3185  def : MipsPat<(seteq RC:$lhs, RC:$rhs),
3186                (SLTiuOp (XOROp RC:$lhs, RC:$rhs), 1)>;
3187  def : MipsPat<(setne RC:$lhs, RC:$rhs),
3188                (SLTuOp ZEROReg, (XOROp RC:$lhs, RC:$rhs))>;
3189}
3190
3191multiclass SetlePats<RegisterClass RC, Instruction XORiOp, Instruction SLTOp,
3192                     Instruction SLTuOp> {
3193  def : MipsPat<(setle RC:$lhs, RC:$rhs),
3194                (XORiOp (SLTOp RC:$rhs, RC:$lhs), 1)>;
3195  def : MipsPat<(setule RC:$lhs, RC:$rhs),
3196                (XORiOp (SLTuOp RC:$rhs, RC:$lhs), 1)>;
3197}
3198
3199multiclass SetgtPats<RegisterClass RC, Instruction SLTOp, Instruction SLTuOp> {
3200  def : MipsPat<(setgt RC:$lhs, RC:$rhs),
3201                (SLTOp RC:$rhs, RC:$lhs)>;
3202  def : MipsPat<(setugt RC:$lhs, RC:$rhs),
3203                (SLTuOp RC:$rhs, RC:$lhs)>;
3204}
3205
3206multiclass SetgePats<RegisterClass RC, Instruction XORiOp, Instruction SLTOp,
3207                     Instruction SLTuOp> {
3208  def : MipsPat<(setge RC:$lhs, RC:$rhs),
3209                (XORiOp (SLTOp RC:$lhs, RC:$rhs), 1)>;
3210  def : MipsPat<(setuge RC:$lhs, RC:$rhs),
3211                (XORiOp (SLTuOp RC:$lhs, RC:$rhs), 1)>;
3212}
3213
3214multiclass SetgeImmPats<RegisterClass RC, Instruction XORiOp,
3215                        Instruction SLTiOp, Instruction SLTiuOp> {
3216  def : MipsPat<(setge RC:$lhs, immSExt16:$rhs),
3217                (XORiOp (SLTiOp RC:$lhs, immSExt16:$rhs), 1)>;
3218  def : MipsPat<(setuge RC:$lhs, immSExt16:$rhs),
3219                (XORiOp (SLTiuOp RC:$lhs, immSExt16:$rhs), 1)>;
3220}
3221
3222let AdditionalPredicates = [NotInMicroMips] in {
3223  defm : SeteqPats<GPR32, SLTiu, XOR, SLTu, ZERO>, ISA_MIPS1;
3224  defm : SetlePats<GPR32, XORi, SLT, SLTu>, ISA_MIPS1;
3225  defm : SetgtPats<GPR32, SLT, SLTu>, ISA_MIPS1;
3226  defm : SetgePats<GPR32, XORi, SLT, SLTu>, ISA_MIPS1;
3227  defm : SetgeImmPats<GPR32, XORi, SLTi, SLTiu>, ISA_MIPS1;
3228
3229  // bswap pattern
3230  def : MipsPat<(bswap GPR32:$rt), (ROTR (WSBH GPR32:$rt), 16)>, ISA_MIPS32R2;
3231}
3232
3233// Load halfword/word patterns.
3234let AdditionalPredicates = [NotInMicroMips] in {
3235  let AddedComplexity = 40 in {
3236    def : LoadRegImmPat<LBu, i32, zextloadi8>, ISA_MIPS1;
3237    def : LoadRegImmPat<LHu, i32, zextloadi16>, ISA_MIPS1;
3238    def : LoadRegImmPat<LB, i32, sextloadi8>, ISA_MIPS1;
3239    def : LoadRegImmPat<LH, i32, sextloadi16>, ISA_MIPS1;
3240    def : LoadRegImmPat<LW, i32, load>, ISA_MIPS1;
3241  }
3242
3243  // Atomic load patterns.
3244  def : MipsPat<(atomic_load_8 addr:$a), (LB addr:$a)>, ISA_MIPS1;
3245  def : MipsPat<(atomic_load_16 addr:$a), (LH addr:$a)>, ISA_MIPS1;
3246  def : MipsPat<(atomic_load_32 addr:$a), (LW addr:$a)>, ISA_MIPS1;
3247
3248  // Atomic store patterns.
3249  def : MipsPat<(atomic_store_8 addr:$a, GPR32:$v), (SB GPR32:$v, addr:$a)>,
3250        ISA_MIPS1;
3251  def : MipsPat<(atomic_store_16 addr:$a, GPR32:$v), (SH GPR32:$v, addr:$a)>,
3252        ISA_MIPS1;
3253  def : MipsPat<(atomic_store_32 addr:$a, GPR32:$v), (SW GPR32:$v, addr:$a)>,
3254        ISA_MIPS1;
3255}
3256
3257//===----------------------------------------------------------------------===//
3258// Floating Point Support
3259//===----------------------------------------------------------------------===//
3260
3261include "MipsInstrFPU.td"
3262include "Mips64InstrInfo.td"
3263include "MipsCondMov.td"
3264
3265include "Mips32r6InstrInfo.td"
3266include "Mips64r6InstrInfo.td"
3267
3268//
3269// Mips16
3270
3271include "Mips16InstrFormats.td"
3272include "Mips16InstrInfo.td"
3273
3274// DSP
3275include "MipsDSPInstrFormats.td"
3276include "MipsDSPInstrInfo.td"
3277
3278// MSA
3279include "MipsMSAInstrFormats.td"
3280include "MipsMSAInstrInfo.td"
3281
3282// EVA
3283include "MipsEVAInstrFormats.td"
3284include "MipsEVAInstrInfo.td"
3285
3286// MT
3287include "MipsMTInstrFormats.td"
3288include "MipsMTInstrInfo.td"
3289
3290// Micromips
3291include "MicroMipsInstrFormats.td"
3292include "MicroMipsInstrInfo.td"
3293include "MicroMipsInstrFPU.td"
3294
3295// Micromips r6
3296include "MicroMips32r6InstrFormats.td"
3297include "MicroMips32r6InstrInfo.td"
3298
3299// Micromips DSP
3300include "MicroMipsDSPInstrFormats.td"
3301include "MicroMipsDSPInstrInfo.td"
3302