1//===-- VEInstrInfo.td - Target Description for VE Target -----------------===//
2//
3// Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
4// See https://llvm.org/LICENSE.txt for license information.
5// SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
6//
7//===----------------------------------------------------------------------===//
8//
9// This file describes the VE instructions in TableGen format.
10//
11//===----------------------------------------------------------------------===//
12
13//===----------------------------------------------------------------------===//
14// Instruction format superclass
15//===----------------------------------------------------------------------===//
16
17include "VEInstrFormats.td"
18
19//===----------------------------------------------------------------------===//
20// Helper functions to retrieve target constants.
21//
22// VE instructions have a space to hold following immediates
23//   $sy has 7 bits to represent simm7, uimm7, simm7fp, or uimm7fp.
24//   $sz also has 7 bits to represent mimm or mimmfp.
25//   $disp has 32 bits to represent simm32.
26//
27// The mimm is a special immediate value of sequential bit stream of 0 or 1.
28//     `(m)0`: Represents 0 sequence then 1 sequence like 0b00...0011...11,
29//             where `m` is equal to the number of leading zeros.
30//     `(m)1`: Represents 1 sequence then 0 sequence like 0b11...1100...00,
31//             where `m` is equal to the number of leading ones.
32// Each bit of mimm's 7 bits is used like below:
33//     bit 6  : If `(m)0`, this bit is 1.  Otherwise, this bit is 0.
34//     bit 5-0: Represents the m (0-63).
35// Use `!add(m, 64)` to generates an immediate value in pattern matchings.
36//
37// The floating point immediate value is not something like compacted value.
38// It is simple integer representation, so it works rarely.
39//     e.g. 0.0 (0x00000000) or -2.0 (0xC0000000=(2)1).
40//===----------------------------------------------------------------------===//
41
42def ULO7 : SDNodeXForm<imm, [{
43  return CurDAG->getTargetConstant(N->getZExtValue() & 0x7f,
44                                   SDLoc(N), MVT::i32);
45}]>;
46def LO7 : SDNodeXForm<imm, [{
47  return CurDAG->getTargetConstant(SignExtend32(N->getSExtValue(), 7),
48                                   SDLoc(N), MVT::i32);
49}]>;
50def MIMM : SDNodeXForm<imm, [{
51  return CurDAG->getTargetConstant(val2MImm(getImmVal(N)),
52                                   SDLoc(N), MVT::i32);
53}]>;
54def LO32 : SDNodeXForm<imm, [{
55  return CurDAG->getTargetConstant(Lo_32(N->getZExtValue()),
56                                   SDLoc(N), MVT::i32);
57}]>;
58def HI32 : SDNodeXForm<imm, [{
59  // Transformation function: shift the immediate value down into the low bits.
60  return CurDAG->getTargetConstant(Hi_32(N->getZExtValue()),
61                                   SDLoc(N), MVT::i32);
62}]>;
63
64def LO7FP : SDNodeXForm<fpimm, [{
65  uint64_t Val = getFpImmVal(N);
66  return CurDAG->getTargetConstant(SignExtend32(Val, 7), SDLoc(N), MVT::i32);
67}]>;
68def MIMMFP : SDNodeXForm<fpimm, [{
69  return CurDAG->getTargetConstant(val2MImm(getFpImmVal(N)),
70                                   SDLoc(N), MVT::i32);
71}]>;
72def LOFP32 : SDNodeXForm<fpimm, [{
73  return CurDAG->getTargetConstant(Lo_32(getFpImmVal(N) & 0xffffffff),
74                                   SDLoc(N), MVT::i32);
75}]>;
76def HIFP32 : SDNodeXForm<fpimm, [{
77  return CurDAG->getTargetConstant(Hi_32(getFpImmVal(N)), SDLoc(N), MVT::i32);
78}]>;
79
80def icond2cc : SDNodeXForm<cond, [{
81  VECC::CondCode VECC = intCondCode2Icc(N->get());
82  return CurDAG->getTargetConstant(VECC, SDLoc(N), MVT::i32);
83}]>;
84
85def icond2ccSwap : SDNodeXForm<cond, [{
86  ISD::CondCode CC = getSetCCSwappedOperands(N->get());
87  VECC::CondCode VECC = intCondCode2Icc(CC);
88  return CurDAG->getTargetConstant(VECC, SDLoc(N), MVT::i32);
89}]>;
90
91def fcond2cc : SDNodeXForm<cond, [{
92  VECC::CondCode VECC = fpCondCode2Fcc(N->get());
93  return CurDAG->getTargetConstant(VECC, SDLoc(N), MVT::i32);
94}]>;
95
96def fcond2ccSwap : SDNodeXForm<cond, [{
97  ISD::CondCode CC = getSetCCSwappedOperands(N->get());
98  VECC::CondCode VECC = fpCondCode2Fcc(CC);
99  return CurDAG->getTargetConstant(VECC, SDLoc(N), MVT::i32);
100}]>;
101
102def CCOP : SDNodeXForm<imm, [{
103  return CurDAG->getTargetConstant(N->getZExtValue(),
104                                   SDLoc(N), MVT::i32);
105}]>;
106
107//===----------------------------------------------------------------------===//
108// Feature predicates.
109//===----------------------------------------------------------------------===//
110
111//===----------------------------------------------------------------------===//
112// Instruction Pattern Stuff
113//===----------------------------------------------------------------------===//
114
115// zero
116def ZeroAsmOperand : AsmOperandClass {
117  let Name = "Zero";
118}
119def zero : Operand<i32>, PatLeaf<(imm), [{
120    return N->getSExtValue() == 0; }]> {
121  let ParserMatchClass = ZeroAsmOperand;
122}
123
124// uimm0to2 - Special immediate value represents 0, 1, and 2.
125def UImm0to2AsmOperand : AsmOperandClass {
126  let Name = "UImm0to2";
127}
128def uimm0to2 : Operand<i32>, PatLeaf<(imm), [{
129    return N->getZExtValue() < 3; }], ULO7> {
130  let ParserMatchClass = UImm0to2AsmOperand;
131}
132
133// uimm1 - Generic immediate value.
134def UImm1AsmOperand : AsmOperandClass {
135  let Name = "UImm1";
136}
137def uimm1 : Operand<i32>, PatLeaf<(imm), [{
138    return isUInt<1>(N->getZExtValue()); }], ULO7> {
139  let ParserMatchClass = UImm1AsmOperand;
140}
141
142// uimm2 - Generic immediate value.
143def UImm2AsmOperand : AsmOperandClass {
144  let Name = "UImm2";
145}
146def uimm2 : Operand<i32>, PatLeaf<(imm), [{
147    return isUInt<2>(N->getZExtValue()); }], ULO7> {
148  let ParserMatchClass = UImm2AsmOperand;
149}
150
151// uimm3 - Generic immediate value.
152def UImm3AsmOperand : AsmOperandClass {
153  let Name = "UImm3";
154}
155def uimm3 : Operand<i32>, PatLeaf<(imm), [{
156    return isUInt<3>(N->getZExtValue()); }], ULO7> {
157  let ParserMatchClass = UImm3AsmOperand;
158}
159
160// uimm4 - Generic immediate value.
161def UImm4AsmOperand : AsmOperandClass {
162  let Name = "UImm4";
163}
164def uimm4 : Operand<i32>, PatLeaf<(imm), [{
165    return isUInt<4>(N->getZExtValue()); }], ULO7> {
166  let ParserMatchClass = UImm4AsmOperand;
167}
168
169// uimm6 - Generic immediate value.
170def UImm6AsmOperand : AsmOperandClass {
171  let Name = "UImm6";
172}
173def uimm6 : Operand<i32>, PatLeaf<(imm), [{
174    return isUInt<6>(N->getZExtValue()); }], ULO7> {
175  let ParserMatchClass = UImm6AsmOperand;
176}
177
178// uimm7 - Generic immediate value.
179def UImm7AsmOperand : AsmOperandClass {
180  let Name = "UImm7";
181}
182def uimm7 : Operand<i32>, PatLeaf<(imm), [{
183    return isUInt<7>(N->getZExtValue()); }], ULO7> {
184  let ParserMatchClass = UImm7AsmOperand;
185}
186
187// simm7 - Generic immediate value.
188def SImm7AsmOperand : AsmOperandClass {
189  let Name = "SImm7";
190}
191def simm7 : Operand<i32>, PatLeaf<(imm), [{
192    return isInt<7>(N->getSExtValue()); }], LO7> {
193  let ParserMatchClass = SImm7AsmOperand;
194  let DecoderMethod = "DecodeSIMM7";
195}
196
197// mimm - Special immediate value of sequential bit stream of 0 or 1.
198def MImmAsmOperand : AsmOperandClass {
199  let Name = "MImm";
200  let ParserMethod = "parseMImmOperand";
201}
202def mimm : Operand<i32>, PatLeaf<(imm), [{
203    return isMImmVal(getImmVal(N)); }], MIMM> {
204  let ParserMatchClass = MImmAsmOperand;
205  let PrintMethod = "printMImmOperand";
206}
207
208// zerofp - Generic fp immediate zero value.
209def zerofp : Operand<i32>, PatLeaf<(fpimm), [{
210    return getFpImmVal(N) == 0; }]> {
211  let ParserMatchClass = ZeroAsmOperand;
212}
213
214// simm7fp - Generic fp immediate value.
215def simm7fp : Operand<i32>, PatLeaf<(fpimm), [{
216    return isInt<7>(getFpImmVal(N));
217  }], LO7FP> {
218  let ParserMatchClass = SImm7AsmOperand;
219  let DecoderMethod = "DecodeSIMM7";
220}
221
222// mimmfp - Special fp immediate value of sequential bit stream of 0 or 1.
223def mimmfp : Operand<i32>, PatLeaf<(fpimm), [{
224    return isMImmVal(getFpImmVal(N)); }], MIMMFP> {
225  let ParserMatchClass = MImmAsmOperand;
226  let PrintMethod = "printMImmOperand";
227}
228
229// mimmfp32 - 32 bit width mimmfp
230//   Float value places at higher bits, so ignore lower 32 bits.
231def mimmfp32 : Operand<i32>, PatLeaf<(fpimm), [{
232    return isMImm32Val(getFpImmVal(N) >> 32); }], MIMMFP> {
233  let ParserMatchClass = MImmAsmOperand;
234  let PrintMethod = "printMImmOperand";
235}
236
237// other generic patterns to use in pattern matchings
238def simm32      : PatLeaf<(imm), [{ return isInt<32>(N->getSExtValue()); }]>;
239def uimm32      : PatLeaf<(imm), [{ return isUInt<32>(N->getZExtValue()); }]>;
240def lomsbzero   : PatLeaf<(imm), [{ return (N->getZExtValue() & 0x80000000)
241                                      == 0; }]>;
242def lozero      : PatLeaf<(imm), [{ return (N->getZExtValue() & 0xffffffff)
243                                      == 0; }]>;
244def fplomsbzero : PatLeaf<(fpimm), [{ return (getFpImmVal(N) & 0x80000000)
245                                        == 0; }]>;
246def fplozero    : PatLeaf<(fpimm), [{ return (getFpImmVal(N) & 0xffffffff)
247                                        == 0; }]>;
248def nonzero     : PatLeaf<(imm), [{ return N->getSExtValue() !=0 ; }]>;
249
250def CCSIOp : PatLeaf<(cond), [{
251  switch (N->get()) {
252  default:          return true;
253  case ISD::SETULT:
254  case ISD::SETULE:
255  case ISD::SETUGT:
256  case ISD::SETUGE: return false;
257  }
258}]>;
259
260def CCUIOp : PatLeaf<(cond), [{
261  switch (N->get()) {
262  default:         return true;
263  case ISD::SETLT:
264  case ISD::SETLE:
265  case ISD::SETGT:
266  case ISD::SETGE: return false;
267  }
268}]>;
269
270//===----------------------------------------------------------------------===//
271// Addressing modes.
272// SX-Aurora has following fields.
273//    sz: register or 0
274//    sy: register or immediate (-64 to 63)
275//    disp: immediate (-2147483648 to 2147483647)
276//
277// There are two kinds of instruction.
278//    ASX format uses sz + sy + disp.
279//    AS format uses sz + disp.
280//
281// Moreover, there are four kinds of assembly instruction format.
282//    ASX format uses "disp", "disp(, sz)", "disp(sy)", "disp(sy, sz)",
283//    "(, sz)", "(sy)", or "(sy, sz)".
284//    AS format uses "disp", "disp(, sz)", or "(, sz)" in general.
285//    AS format in RRM format uses "disp", "disp(sz)", or "(sz)".
286//    AS format in RRM format for host memory access uses "sz", "(sz)",
287//    or "disp(sz)".
288//
289// We defined them below.
290//
291// ASX format:
292//    MEMrri, MEMrii, MEMzri, MEMzii
293// AS format:
294//    MEMriASX, MEMziASX    : simple AS format
295//    MEMriRRM, MEMziRRM    : AS format in RRM format
296//    MEMriHM, MEMziHM      : AS format in RRM format for host memory access
297//===----------------------------------------------------------------------===//
298
299// DAG selections for both ASX and AS formats.
300def ADDRrri : ComplexPattern<iPTR, 3, "selectADDRrri", [frameindex], []>;
301def ADDRrii : ComplexPattern<iPTR, 3, "selectADDRrii", [frameindex], []>;
302def ADDRzri : ComplexPattern<iPTR, 3, "selectADDRzri", [], []>;
303def ADDRzii : ComplexPattern<iPTR, 3, "selectADDRzii", [], []>;
304def ADDRri : ComplexPattern<iPTR, 2, "selectADDRri", [frameindex], []>;
305def ADDRzi : ComplexPattern<iPTR, 2, "selectADDRzi", [], []>;
306
307// ASX format.
308def VEMEMrriAsmOperand : AsmOperandClass {
309  let Name = "MEMrri";
310  let ParserMethod = "parseMEMOperand";
311}
312def VEMEMriiAsmOperand : AsmOperandClass {
313  let Name = "MEMrii";
314  let ParserMethod = "parseMEMOperand";
315}
316def VEMEMzriAsmOperand : AsmOperandClass {
317  let Name = "MEMzri";
318  let ParserMethod = "parseMEMOperand";
319}
320def VEMEMziiAsmOperand : AsmOperandClass {
321  let Name = "MEMzii";
322  let ParserMethod = "parseMEMOperand";
323}
324
325// ASX format uses single assembly instruction format.
326def MEMrri : Operand<iPTR> {
327  let PrintMethod = "printMemASXOperand";
328  let MIOperandInfo = (ops ptr_rc, ptr_rc, i64imm);
329  let ParserMatchClass = VEMEMrriAsmOperand;
330}
331def MEMrii : Operand<iPTR> {
332  let PrintMethod = "printMemASXOperand";
333  let MIOperandInfo = (ops ptr_rc, i32imm, i64imm);
334  let ParserMatchClass = VEMEMriiAsmOperand;
335}
336def MEMzri : Operand<iPTR> {
337  let PrintMethod = "printMemASXOperand";
338  let MIOperandInfo = (ops i32imm /* = 0 */, ptr_rc, i64imm);
339  let ParserMatchClass = VEMEMzriAsmOperand;
340}
341def MEMzii : Operand<iPTR> {
342  let PrintMethod = "printMemASXOperand";
343  let MIOperandInfo = (ops i32imm /* = 0 */, i32imm, i64imm);
344  let ParserMatchClass = VEMEMziiAsmOperand;
345}
346
347// AS format.
348def VEMEMriAsmOperand : AsmOperandClass {
349  let Name = "MEMri";
350  let ParserMethod = "parseMEMAsOperand";
351}
352def VEMEMziAsmOperand : AsmOperandClass {
353  let Name = "MEMzi";
354  let ParserMethod = "parseMEMAsOperand";
355}
356
357// AS format uses multiple assembly instruction formats
358//   1. AS generic assembly instruction format:
359def MEMriASX : Operand<iPTR> {
360  let PrintMethod = "printMemASOperandASX";
361  let MIOperandInfo = (ops ptr_rc, i32imm);
362  let ParserMatchClass = VEMEMriAsmOperand;
363}
364def MEMziASX : Operand<iPTR> {
365  let PrintMethod = "printMemASOperandASX";
366  let MIOperandInfo = (ops i32imm /* = 0 */, i32imm);
367  let ParserMatchClass = VEMEMziAsmOperand;
368}
369
370//   2. AS RRM style assembly instruction format:
371def MEMriRRM : Operand<iPTR> {
372  let PrintMethod = "printMemASOperandRRM";
373  let MIOperandInfo = (ops ptr_rc, i32imm);
374  let ParserMatchClass = VEMEMriAsmOperand;
375}
376def MEMziRRM : Operand<iPTR> {
377  let PrintMethod = "printMemASOperandRRM";
378  let MIOperandInfo = (ops i32imm /* = 0 */, i32imm);
379  let ParserMatchClass = VEMEMziAsmOperand;
380}
381
382//   3. AS HM style assembly instruction format:
383def MEMriHM : Operand<iPTR> {
384  let PrintMethod = "printMemASOperandHM";
385  let MIOperandInfo = (ops ptr_rc, i32imm);
386  let ParserMatchClass = VEMEMriAsmOperand;
387}
388def MEMziHM : Operand<iPTR> {
389  let PrintMethod = "printMemASOperandHM";
390  let MIOperandInfo = (ops i32imm /* = 0 */, i32imm);
391  let ParserMatchClass = VEMEMziAsmOperand;
392}
393
394//===----------------------------------------------------------------------===//
395// Other operands.
396//===----------------------------------------------------------------------===//
397
398// Branch targets have OtherVT type.
399def brtarget32 : Operand<OtherVT> {
400  let EncoderMethod = "getBranchTargetOpValue";
401  let DecoderMethod = "DecodeSIMM32";
402}
403
404// Operand for printing out a condition code.
405def CCOpAsmOperand : AsmOperandClass { let Name = "CCOp"; }
406def CCOp : Operand<i32>, ImmLeaf<i32, [{
407    return Imm >= 0 && Imm < 22; }], CCOP> {
408  let PrintMethod = "printCCOperand";
409  let DecoderMethod = "DecodeCCOperand";
410  let EncoderMethod = "getCCOpValue";
411  let ParserMatchClass = CCOpAsmOperand;
412}
413
414// Operand for a rounding mode code.
415def RDOpAsmOperand : AsmOperandClass {
416  let Name = "RDOp";
417}
418def RDOp : Operand<i32> {
419  let PrintMethod = "printRDOperand";
420  let DecoderMethod = "DecodeRDOperand";
421  let EncoderMethod = "getRDOpValue";
422  let ParserMatchClass = RDOpAsmOperand;
423}
424
425def VEhi    : SDNode<"VEISD::Hi", SDTIntUnaryOp>;
426def VElo    : SDNode<"VEISD::Lo", SDTIntUnaryOp>;
427
428//  These are target-independent nodes, but have target-specific formats.
429def SDT_SPCallSeqStart : SDCallSeqStart<[ SDTCisVT<0, i64>,
430                                          SDTCisVT<1, i64> ]>;
431def SDT_SPCallSeqEnd   : SDCallSeqEnd<[ SDTCisVT<0, i64>,
432                                        SDTCisVT<1, i64> ]>;
433
434def callseq_start : SDNode<"ISD::CALLSEQ_START", SDT_SPCallSeqStart,
435                           [SDNPHasChain, SDNPOutGlue]>;
436def callseq_end   : SDNode<"ISD::CALLSEQ_END",   SDT_SPCallSeqEnd,
437                           [SDNPHasChain, SDNPOptInGlue, SDNPOutGlue]>;
438
439def SDT_SPCall    : SDTypeProfile<0, -1, [SDTCisVT<0, i64>]>;
440def call          : SDNode<"VEISD::CALL", SDT_SPCall,
441                           [SDNPHasChain, SDNPOptInGlue, SDNPOutGlue,
442                            SDNPVariadic]>;
443
444def retflag       : SDNode<"VEISD::RET_FLAG", SDTNone,
445                           [SDNPHasChain, SDNPOptInGlue, SDNPVariadic]>;
446
447def getGOT        : Operand<iPTR>;
448
449def VEeh_sjlj_setjmp: SDNode<"VEISD::EH_SJLJ_SETJMP",
450                             SDTypeProfile<1, 1, [SDTCisInt<0>,
451                                                  SDTCisPtrTy<1>]>,
452                             [SDNPHasChain, SDNPSideEffect]>;
453def VEeh_sjlj_longjmp: SDNode<"VEISD::EH_SJLJ_LONGJMP",
454                              SDTypeProfile<0, 1, [SDTCisPtrTy<0>]>,
455                              [SDNPHasChain, SDNPSideEffect]>;
456def VEeh_sjlj_setup_dispatch: SDNode<"VEISD::EH_SJLJ_SETUP_DISPATCH",
457                                     SDTypeProfile<0, 0, []>,
458                                     [SDNPHasChain, SDNPSideEffect]>;
459
460// GETFUNPLT for PIC
461def GetFunPLT : SDNode<"VEISD::GETFUNPLT", SDTIntUnaryOp>;
462
463// GETTLSADDR for TLS
464def GetTLSAddr : SDNode<"VEISD::GETTLSADDR", SDT_SPCall,
465                        [SDNPHasChain, SDNPOptInGlue, SDNPOutGlue,
466                         SDNPVariadic]>;
467
468// GETSTACKTOP
469def GetStackTop : SDNode<"VEISD::GETSTACKTOP", SDTNone,
470                        [SDNPHasChain, SDNPSideEffect]>;
471
472// MEMBARRIER
473def MemBarrier : SDNode<"VEISD::MEMBARRIER", SDTNone,
474                        [SDNPHasChain, SDNPSideEffect]>;
475
476// TS1AM
477def SDT_TS1AM : SDTypeProfile<1, 3, [SDTCisSameAs<0, 3>, SDTCisPtrTy<1>,
478                                     SDTCisVT<2, i32>, SDTCisInt<3>]>;
479def ts1am     : SDNode<"VEISD::TS1AM", SDT_TS1AM,
480                       [SDNPHasChain, SDNPMayStore, SDNPMayLoad,
481                        SDNPMemOperand]>;
482
483//===----------------------------------------------------------------------===//
484// VE Flag Conditions
485//===----------------------------------------------------------------------===//
486
487// Note that these values must be kept in sync with the CCOp::CondCode enum
488// values.
489class CC_VAL<int N> : PatLeaf<(i32 N)>;
490def CC_IG    : CC_VAL< 0>;  // Greater
491def CC_IL    : CC_VAL< 1>;  // Less
492def CC_INE   : CC_VAL< 2>;  // Not Equal
493def CC_IEQ   : CC_VAL< 3>;  // Equal
494def CC_IGE   : CC_VAL< 4>;  // Greater or Equal
495def CC_ILE   : CC_VAL< 5>;  // Less or Equal
496def CC_AF    : CC_VAL< 6>;  // Always false
497def CC_G     : CC_VAL< 7>;  // Greater
498def CC_L     : CC_VAL< 8>;  // Less
499def CC_NE    : CC_VAL< 9>;  // Not Equal
500def CC_EQ    : CC_VAL<10>;  // Equal
501def CC_GE    : CC_VAL<11>;  // Greater or Equal
502def CC_LE    : CC_VAL<12>;  // Less or Equal
503def CC_NUM   : CC_VAL<13>;  // Number
504def CC_NAN   : CC_VAL<14>;  // NaN
505def CC_GNAN  : CC_VAL<15>;  // Greater or NaN
506def CC_LNAN  : CC_VAL<16>;  // Less or NaN
507def CC_NENAN : CC_VAL<17>;  // Not Equal or NaN
508def CC_EQNAN : CC_VAL<18>;  // Equal or NaN
509def CC_GENAN : CC_VAL<19>;  // Greater or Equal or NaN
510def CC_LENAN : CC_VAL<20>;  // Less or Equal or NaN
511def CC_AT    : CC_VAL<21>;  // Always true
512
513//===----------------------------------------------------------------------===//
514// VE Rounding Mode
515//===----------------------------------------------------------------------===//
516
517// Note that these values must be kept in sync with the VERD::RoundingMode enum
518// values.
519class RD_VAL<int N> : PatLeaf<(i32 N)>;
520def RD_NONE  : RD_VAL< 0>;  // According to PSW
521def RD_RZ    : RD_VAL< 8>;  // Round toward Zero
522def RD_RP    : RD_VAL< 9>;  // Round toward Plus infinity
523def RD_RM    : RD_VAL<10>;  // Round toward Minus infinity
524def RD_RN    : RD_VAL<11>;  // Round to Nearest (ties to Even)
525def RD_RA    : RD_VAL<12>;  // Round to Nearest (ties to Away)
526
527//===----------------------------------------------------------------------===//
528// VE Multiclasses for common instruction formats
529//===----------------------------------------------------------------------===//
530
531// Multiclass for generic RR type instructions
532let hasSideEffects = 0 in
533multiclass RRbm<string opcStr, bits<8>opc,
534                RegisterClass RCo, ValueType Tyo,
535                RegisterClass RCi, ValueType Tyi,
536                SDPatternOperator OpNode = null_frag,
537                Operand immOp = simm7, Operand mOp = mimm,
538                bit MoveImm = 0> {
539  def rr : RR<opc, (outs RCo:$sx), (ins RCi:$sy, RCi:$sz),
540              !strconcat(opcStr, " $sx, $sy, $sz"),
541              [(set Tyo:$sx, (OpNode Tyi:$sy, Tyi:$sz))]>;
542  // VE calculates (OpNode $sy, $sz), but llvm requires to have immediate
543  // in RHS, so we use following definition.
544  let cy = 0 in
545  def ri : RR<opc, (outs RCo:$sx), (ins RCi:$sz, immOp:$sy),
546              !strconcat(opcStr, " $sx, $sy, $sz"),
547              [(set Tyo:$sx, (OpNode Tyi:$sz, (Tyi immOp:$sy)))]>;
548  let cz = 0 in
549  def rm : RR<opc, (outs RCo:$sx), (ins RCi:$sy, mOp:$sz),
550              !strconcat(opcStr, " $sx, $sy, $sz"),
551              [(set Tyo:$sx, (OpNode Tyi:$sy, (Tyi mOp:$sz)))]>;
552  let cy = 0, cz = 0 in
553  def im : RR<opc, (outs RCo:$sx), (ins immOp:$sy, mOp:$sz),
554              !strconcat(opcStr, " $sx, $sy, $sz"),
555              [(set Tyo:$sx, (OpNode (Tyi immOp:$sy), (Tyi mOp:$sz)))]> {
556    // VE uses ORim as a move immediate instruction, so declare it here.
557    // An instruction declared as MoveImm will be optimized in FoldImmediate
558    // later.
559    let isMoveImm = MoveImm;
560  }
561}
562
563// Multiclass for non-commutative RR type instructions
564let hasSideEffects = 0 in
565multiclass RRNCbm<string opcStr, bits<8>opc,
566                RegisterClass RCo, ValueType Tyo,
567                RegisterClass RCi, ValueType Tyi,
568                SDPatternOperator OpNode = null_frag,
569                Operand immOp = simm7, Operand mOp = mimm> {
570  def rr : RR<opc, (outs RCo:$sx), (ins RCi:$sy, RCi:$sz),
571              !strconcat(opcStr, " $sx, $sy, $sz"),
572              [(set Tyo:$sx, (OpNode Tyi:$sy, Tyi:$sz))]>;
573  let cy = 0 in
574  def ir : RR<opc, (outs RCo:$sx), (ins immOp:$sy, RCi:$sz),
575              !strconcat(opcStr, " $sx, $sy, $sz"),
576              [(set Tyo:$sx, (OpNode (Tyi immOp:$sy), Tyi:$sz))]>;
577  let cz = 0 in
578  def rm : RR<opc, (outs RCo:$sx), (ins RCi:$sy, mOp:$sz),
579              !strconcat(opcStr, " $sx, $sy, $sz"),
580              [(set Tyo:$sx, (OpNode Tyi:$sy, (Tyi mOp:$sz)))]>;
581  let cy = 0, cz = 0 in
582  def im : RR<opc, (outs RCo:$sx), (ins immOp:$sy, mOp:$sz),
583              !strconcat(opcStr, " $sx, $sy, $sz"),
584              [(set Tyo:$sx, (OpNode (Tyi immOp:$sy), (Tyi mOp:$sz)))]>;
585}
586
587// Generic RR multiclass with 2 arguments.
588//   e.g. ADDUL, ADDSWSX, ADDSWZX, and etc.
589multiclass RRm<string opcStr, bits<8>opc,
590               RegisterClass RC, ValueType Ty,
591               SDPatternOperator OpNode = null_frag,
592               Operand immOp = simm7, Operand mOp = mimm, bit MoveImm = 0> :
593  RRbm<opcStr, opc, RC, Ty, RC, Ty, OpNode, immOp, mOp, MoveImm>;
594
595// Generic RR multiclass for non-commutative instructions with 2 arguments.
596//   e.g. SUBUL, SUBUW, SUBSWSX, and etc.
597multiclass RRNCm<string opcStr, bits<8>opc,
598                 RegisterClass RC, ValueType Ty,
599                 SDPatternOperator OpNode = null_frag,
600                 Operand immOp = simm7, Operand mOp = mimm> :
601  RRNCbm<opcStr, opc, RC, Ty, RC, Ty, OpNode, immOp, mOp>;
602
603// Generic RR multiclass for floating point instructions with 2 arguments.
604//   e.g. FADDD, FADDS, FSUBD, and etc.
605multiclass RRFm<string opcStr, bits<8>opc,
606                RegisterClass RC, ValueType Ty,
607                SDPatternOperator OpNode = null_frag,
608                Operand immOp = simm7fp, Operand mOp = mimmfp> :
609  RRNCbm<opcStr, opc, RC, Ty, RC, Ty, OpNode, immOp, mOp>;
610
611// Generic RR multiclass for shift instructions with 2 arguments.
612//   e.g. SLL, SRL, SLAWSX, and etc.
613let hasSideEffects = 0 in
614multiclass RRIm<string opcStr, bits<8>opc,
615                RegisterClass RC, ValueType Ty,
616                SDPatternOperator OpNode = null_frag> {
617  def rr : RR<opc, (outs RC:$sx), (ins RC:$sz, I32:$sy),
618              !strconcat(opcStr, " $sx, $sz, $sy"),
619              [(set Ty:$sx, (OpNode Ty:$sz, i32:$sy))]>;
620  let cz = 0 in
621  def mr : RR<opc, (outs RC:$sx), (ins mimm:$sz, I32:$sy),
622              !strconcat(opcStr, " $sx, $sz, $sy"),
623              [(set Ty:$sx, (OpNode (Ty mimm:$sz), i32:$sy))]>;
624  let cy = 0 in
625  def ri : RR<opc, (outs RC:$sx), (ins RC:$sz, uimm7:$sy),
626              !strconcat(opcStr, " $sx, $sz, $sy"),
627              [(set Ty:$sx, (OpNode Ty:$sz, (i32 uimm7:$sy)))]>;
628  let cy = 0, cz = 0 in
629  def mi : RR<opc, (outs RC:$sx), (ins mimm:$sz, uimm7:$sy),
630              !strconcat(opcStr, " $sx, $sz, $sy"),
631              [(set Ty:$sx, (OpNode (Ty mimm:$sz), (i32 uimm7:$sy)))]>;
632}
633
634// Special RR multiclass for 128 bits shift left instruction.
635//   e.g. SLD
636let Constraints = "$hi = $sx", DisableEncoding = "$hi", hasSideEffects = 0 in
637multiclass RRILDm<string opcStr, bits<8>opc, RegisterClass RC> {
638  def rrr : RR<opc, (outs RC:$sx), (ins RC:$hi, RC:$sz, I32:$sy),
639              !strconcat(opcStr, " $sx, $sz, $sy")>;
640  let cz = 0 in
641  def rmr : RR<opc, (outs RC:$sx), (ins RC:$hi, mimm:$sz, I32:$sy),
642              !strconcat(opcStr, " $sx, $sz, $sy")>;
643  let cy = 0 in
644  def rri : RR<opc, (outs RC:$sx), (ins RC:$hi, RC:$sz, uimm7:$sy),
645              !strconcat(opcStr, " $sx, $sz, $sy")>;
646  let cy = 0, cz = 0 in
647  def rmi : RR<opc, (outs RC:$sx), (ins RC:$hi, mimm:$sz, uimm7:$sy),
648              !strconcat(opcStr, " $sx, $sz, $sy")>;
649}
650
651// Special RR multiclass for 128 bits shift right instruction.
652//   e.g. SRD
653let Constraints = "$low = $sx", DisableEncoding = "$low", hasSideEffects = 0 in
654multiclass RRIRDm<string opcStr, bits<8>opc, RegisterClass RC> {
655  def rrr : RR<opc, (outs RC:$sx), (ins RC:$sz, RC:$low, I32:$sy),
656              !strconcat(opcStr, " $sx, $sz, $sy")>;
657  let cz = 0 in
658  def mrr : RR<opc, (outs RC:$sx), (ins mimm:$sz, RC:$low, I32:$sy),
659              !strconcat(opcStr, " $sx, $sz, $sy")>;
660  let cy = 0 in
661  def rri : RR<opc, (outs RC:$sx), (ins RC:$sz, RC:$low, uimm7:$sy),
662              !strconcat(opcStr, " $sx, $sz, $sy")>;
663  let cy = 0, cz = 0 in
664  def mri : RR<opc, (outs RC:$sx), (ins mimm:$sz, RC:$low, uimm7:$sy),
665              !strconcat(opcStr, " $sx, $sz, $sy")>;
666}
667
668// Generic RR multiclass with an argument.
669//   e.g. LDZ, PCNT, and  BRV
670let cy = 0, sy = 0, hasSideEffects = 0 in
671multiclass RRI1m<string opcStr, bits<8>opc, RegisterClass RC, ValueType Ty,
672                 SDPatternOperator OpNode = null_frag> {
673  def r : RR<opc, (outs RC:$sx), (ins RC:$sz), !strconcat(opcStr, " $sx, $sz"),
674             [(set Ty:$sx, (OpNode Ty:$sz))]>;
675  let cz = 0 in
676  def m : RR<opc, (outs RC:$sx), (ins mimm:$sz),
677             !strconcat(opcStr, " $sx, $sz"),
678             [(set Ty:$sx, (OpNode (Ty mimm:$sz)))]>;
679}
680
681// Special RR multiclass for MRG instruction.
682//   e.g. MRG
683let Constraints = "$sx = $sd", DisableEncoding = "$sd", hasSideEffects = 0 in
684multiclass RRMRGm<string opcStr, bits<8>opc, RegisterClass RC> {
685  def rr : RR<opc, (outs RC:$sx), (ins RC:$sy, RC:$sz, RC:$sd),
686              !strconcat(opcStr, " $sx, $sy, $sz")>;
687  let cy = 0 in
688  def ir : RR<opc, (outs RC:$sx), (ins simm7:$sy, RC:$sz, RC:$sd),
689              !strconcat(opcStr, " $sx, $sy, $sz")>;
690  let cz = 0 in
691  def rm : RR<opc, (outs RC:$sx), (ins RC:$sy, mimm:$sz, RC:$sd),
692              !strconcat(opcStr, " $sx, $sy, $sz")>;
693  let cy = 0, cz = 0 in
694  def im : RR<opc, (outs RC:$sx), (ins simm7:$sy, mimm:$sz, RC:$sd),
695              !strconcat(opcStr, " $sx, $sy, $sz")>;
696}
697
698// Special RR multiclass for BSWP instruction.
699//   e.g. BSWP
700let hasSideEffects = 0 in
701multiclass RRSWPm<string opcStr, bits<8>opc,
702                  RegisterClass RC, ValueType Ty,
703                  SDPatternOperator OpNode = null_frag> {
704  let cy = 0 in
705  def ri : RR<opc, (outs RC:$sx), (ins RC:$sz, uimm1:$sy),
706              !strconcat(opcStr, " $sx, $sz, $sy"),
707              [(set Ty:$sx, (OpNode Ty:$sz, (i32 uimm1:$sy)))]>;
708  let cy = 0, cz = 0 in
709  def mi : RR<opc, (outs RC:$sx), (ins mimm:$sz, uimm1:$sy),
710              !strconcat(opcStr, " $sx, $sz, $sy"),
711              [(set Ty:$sx, (OpNode (Ty mimm:$sz), (i32 uimm1:$sy)))]>;
712}
713
714// Multiclass for CMOV instructions.
715//   e.g. CMOVL, CMOVW, CMOVD, and etc.
716let Constraints = "$sx = $sd", DisableEncoding = "$sd", hasSideEffects = 0,
717    cfw = ? in
718multiclass RRCMOVm<string opcStr, bits<8>opc, RegisterClass RC> {
719  def rr : RR<opc, (outs I64:$sx), (ins CCOp:$cfw, RC:$sy, I64:$sz, I64:$sd),
720              !strconcat(opcStr, " $sx, $sz, $sy")>;
721  let cy = 0 in
722  def ir : RR<opc, (outs I64:$sx),
723              (ins CCOp:$cfw, simm7:$sy, I64:$sz, I64:$sd),
724              !strconcat(opcStr, " $sx, $sz, $sy")>;
725  let cz = 0 in
726  def rm : RR<opc, (outs I64:$sx),
727              (ins CCOp:$cfw, RC:$sy, mimm:$sz, I64:$sd),
728              !strconcat(opcStr, " $sx, $sz, $sy")>;
729  let cy = 0, cz = 0 in
730  def im : RR<opc, (outs I64:$sx),
731              (ins CCOp:$cfw, simm7:$sy, mimm:$sz, I64:$sd),
732              !strconcat(opcStr, " $sx, $sz, $sy")>;
733}
734
735// Multiclass for floating point conversion instructions.
736//   e.g. CVTWDSX, CVTWDZX, CVTWSSX, and etc.
737// sz{3-0} = rounding mode
738let cz = 0, hasSideEffects = 0 in
739multiclass CVTRDm<string opcStr, bits<8> opc, RegisterClass RCo,
740                  RegisterClass RCi> {
741  def r : RR<opc, (outs RCo:$sx), (ins RDOp:$rd, RCi:$sy),
742             !strconcat(opcStr, "${rd} $sx, $sy")> {
743    bits<4> rd;
744    let sz{5-4} = 0;
745    let sz{3-0} = rd;
746  }
747  let cy = 0 in
748  def i : RR<opc, (outs RCo:$sx), (ins RDOp:$rd, simm7:$sy),
749             !strconcat(opcStr, "${rd} $sx, $sy")> {
750    bits<4> rd;
751    let sz{5-4} = 0;
752    let sz{3-0} = rd;
753  }
754}
755
756// Multiclass for floating point conversion instructions.
757//   e.g. CVTDW, CVTSW, CVTDL, and etc.
758let cz = 0, sz = 0, hasSideEffects = 0 in
759multiclass CVTm<string opcStr, bits<8> opc, RegisterClass RCo, ValueType Tyo,
760                RegisterClass RCi, ValueType Tyi,
761                SDPatternOperator OpNode = null_frag> {
762  def r : RR<opc, (outs RCo:$sx), (ins RCi:$sy),
763             !strconcat(opcStr, " $sx, $sy"),
764             [(set Tyo:$sx, (OpNode Tyi:$sy))]>;
765  let cy = 0 in
766  def i : RR<opc, (outs RCo:$sx), (ins simm7:$sy),
767             !strconcat(opcStr, " $sx, $sy")>;
768}
769
770// Multiclass for PFCH instructions.
771//   e.g. PFCH
772let sx = 0, hasSideEffects = 0 in
773multiclass PFCHm<string opcStr, bits<8>opc> {
774  def rri : RM<opc, (outs), (ins MEMrri:$addr), !strconcat(opcStr, " $addr"),
775               [(prefetch ADDRrri:$addr, imm, imm, (i32 1))]>;
776  let cy = 0 in
777  def rii : RM<opc, (outs), (ins MEMrii:$addr), !strconcat(opcStr, " $addr"),
778               [(prefetch ADDRrii:$addr, imm, imm, (i32 1))]>;
779  let cz = 0 in
780  def zri : RM<opc, (outs), (ins MEMzri:$addr), !strconcat(opcStr, " $addr"),
781               [(prefetch ADDRzri:$addr, imm, imm, (i32 1))]>;
782  let cy = 0, cz = 0 in
783  def zii : RM<opc, (outs), (ins MEMzii:$addr), !strconcat(opcStr, " $addr"),
784               [(prefetch ADDRzii:$addr, imm, imm, (i32 1))]>;
785}
786
787// Multiclass for CAS instructions.
788//   e.g. TS1AML, TS1AMW, TS2AM, and etc.
789let Constraints = "$dest = $sd", DisableEncoding = "$sd",
790    mayStore=1, mayLoad = 1, hasSideEffects = 0 in
791multiclass RRCAStgm<string opcStr, bits<8>opc, RegisterClass RC, ValueType Ty,
792                    Operand immOp, Operand MEM, ComplexPattern ADDR,
793                    SDPatternOperator OpNode = null_frag> {
794  def r : RRM<opc, (outs RC:$dest), (ins MEM:$addr, RC:$sy, RC:$sd),
795              !strconcat(opcStr, " $dest, $addr, $sy"),
796              [(set Ty:$dest, (OpNode ADDR:$addr, Ty:$sy, Ty:$sd))]>;
797  let cy = 0 in
798  def i : RRM<opc, (outs RC:$dest), (ins MEM:$addr, immOp:$sy, RC:$sd),
799              !strconcat(opcStr, " $dest, $addr, $sy"),
800              [(set Ty:$dest, (OpNode ADDR:$addr, (Ty immOp:$sy), Ty:$sd))]>;
801}
802multiclass RRCASm<string opcStr, bits<8>opc, RegisterClass RC, ValueType Ty,
803                  Operand immOp, SDPatternOperator OpNode = null_frag> {
804  defm ri : RRCAStgm<opcStr, opc, RC, Ty, immOp, MEMriRRM, ADDRri, OpNode>;
805  let cz = 0 in
806  defm zi : RRCAStgm<opcStr, opc, RC, Ty, immOp, MEMziRRM, ADDRzi, OpNode>;
807}
808
809// Multiclass for branch instructions
810//   e.g. BCFL, BCFW, BCFD, and etc.
811let isBranch = 1, isTerminator = 1, isIndirectBranch = 1, hasSideEffects = 0 in
812multiclass BCbpfm<string opcStr, string cmpStr, bits<8> opc, dag cond,
813                  Operand ADDR> {
814  let bpf = 0 /* NONE */ in
815  def "" : CF<opc, (outs), !con(cond, (ins ADDR:$addr)),
816              !strconcat(opcStr, " ", cmpStr, "$addr")>;
817  let bpf = 2 /* NOT TAKEN */ in
818  def _nt : CF<opc, (outs), !con(cond, (ins ADDR:$addr)),
819               !strconcat(opcStr, ".nt ", cmpStr, "$addr")>;
820  let bpf = 3 /* TAKEN */ in
821  def _t : CF<opc, (outs), !con(cond, (ins ADDR:$addr)),
822              !strconcat(opcStr, ".t ", cmpStr, "$addr")>;
823}
824multiclass BCtgm<string opcStr, string cmpStr, bits<8> opc, dag cond> {
825  defm ri : BCbpfm<opcStr, cmpStr, opc, cond, MEMriASX>;
826  let cz = 0 in defm zi : BCbpfm<opcStr, cmpStr, opc, cond, MEMziASX>;
827}
828multiclass BCm<string opcStr, string opcStrAt, string opcStrAf, bits<8> opc,
829               RegisterClass RC, Operand immOp> {
830  let DecoderMethod = "DecodeBranchCondition" in
831  defm r : BCtgm<opcStr, "$comp, ", opc, (ins CCOp:$cond, RC:$comp)>;
832  let DecoderMethod = "DecodeBranchCondition", cy = 0 in
833  defm i : BCtgm<opcStr, "$comp, ", opc, (ins CCOp:$cond, immOp:$comp)>;
834  let DecoderMethod = "DecodeBranchConditionAlways", cy = 0, sy = 0,
835      cf = 15 /* AT */, isBarrier = 1 in
836  defm a : BCtgm<opcStrAt, "", opc, (ins)>;
837  let DecoderMethod = "DecodeBranchConditionAlways", cy = 0, sy = 0,
838      cf = 0 /* AF */ in
839  defm na : BCtgm<opcStrAf, "", opc, (ins)>;
840}
841
842// Multiclass for relative branch instructions
843//   e.g. BRCFL, BRCFW, BRCFD, and etc.
844let isBranch = 1, isTerminator = 1, hasSideEffects = 0 in
845multiclass BCRbpfm<string opcStr, string cmpStr, bits<8> opc, dag cond> {
846  let bpf = 0 /* NONE */ in
847  def "" : CF<opc, (outs), !con(cond, (ins brtarget32:$imm32)),
848              !strconcat(opcStr, " ", cmpStr, "$imm32")>;
849  let bpf = 2 /* NOT TAKEN */ in
850  def _nt : CF<opc, (outs), !con(cond, (ins brtarget32:$imm32)),
851               !strconcat(opcStr, ".nt ", cmpStr, "$imm32")>;
852  let bpf = 3 /* TAKEN */ in
853  def _t : CF<opc, (outs), !con(cond, (ins brtarget32:$imm32)),
854              !strconcat(opcStr, ".t ", cmpStr, "$imm32")>;
855}
856multiclass BCRm<string opcStr, string opcStrAt, string opcStrAf, bits<8> opc,
857               RegisterClass RC, Operand immOp, Operand zeroOp> {
858  defm rr : BCRbpfm<opcStr, "$sy, $sz, ", opc, (ins CCOp:$cf, RC:$sy, RC:$sz)>;
859  let cy = 0 in
860  defm ir : BCRbpfm<opcStr, "$sy, $sz, ", opc, (ins CCOp:$cf, immOp:$sy,
861                                                    RC:$sz)>;
862  let cz = 0 in
863  defm rz : BCRbpfm<opcStr, "$sy, $sz, ", opc, (ins CCOp:$cf, RC:$sy,
864                                                    zeroOp:$sz)>;
865  let cy = 0, cz = 0 in
866  defm iz : BCRbpfm<opcStr, "$sy, $sz, ", opc, (ins CCOp:$cf, immOp:$sy,
867                                                    zeroOp:$sz)>;
868  let cy = 0, sy = 0, cz = 0, sz = 0, cf = 15 /* AT */, isBarrier = 1 in
869  defm a : BCRbpfm<opcStrAt, "", opc, (ins)>;
870  let cy = 0, sy = 0, cz = 0, sz = 0, cf = 0 /* AF */ in
871  defm na : BCRbpfm<opcStrAf, "", opc, (ins)>;
872}
873
874// Multiclass for communication register instructions.
875//   e.g. LCR
876let hasSideEffects = 1 in
877multiclass LOADCRm<string opcStr, bits<8>opc, RegisterClass RC> {
878  def rr : RR<opc, (outs RC:$sx), (ins RC:$sy, RC:$sz),
879              !strconcat(opcStr, " $sx, $sy, $sz")>;
880  let cy = 0 in def ir : RR<opc, (outs RC:$sx), (ins simm7:$sy, RC:$sz),
881                            !strconcat(opcStr, " $sx, $sy, $sz")>;
882  let cz = 0 in def rz : RR<opc, (outs RC:$sx), (ins RC:$sy, zero:$sz),
883                            !strconcat(opcStr, " $sx, $sy, $sz")>;
884  let cy = 0, cz = 0 in
885  def iz : RR<opc, (outs RC:$sx), (ins simm7:$sy, zero:$sz),
886              !strconcat(opcStr, " $sx, $sy, $sz")>;
887}
888
889// Multiclass for communication register instructions.
890//   e.g. SCR
891let hasSideEffects = 1 in
892multiclass STORECRm<string opcStr, bits<8>opc, RegisterClass RC> {
893  def rrr : RR<opc, (outs), (ins RC:$sy, RC:$sz, RC:$sx),
894              !strconcat(opcStr, " $sx, $sy, $sz")>;
895  let cy = 0 in def irr : RR<opc, (outs), (ins simm7:$sy, RC:$sz, RC:$sx),
896                             !strconcat(opcStr, " $sx, $sy, $sz")>;
897  let cz = 0 in def rzr : RR<opc, (outs), (ins RC:$sy, zero:$sz, RC:$sx),
898                             !strconcat(opcStr, " $sx, $sy, $sz")>;
899  let cy = 0, cz = 0 in
900  def izr : RR<opc, (outs), (ins simm7:$sy, zero:$sz, RC:$sx),
901               !strconcat(opcStr, " $sx, $sy, $sz")>;
902}
903
904let hasSideEffects = 1, Constraints = "$sx = $sx_in", DisableEncoding = "$sx_in" in
905multiclass TSCRm<string opcStr, bits<8>opc, RegisterClass RC> {
906  def rrr : RR<opc, (outs RC:$sx), (ins RC:$sy, RC:$sz, RC:$sx_in),
907               !strconcat(opcStr, " $sx, $sy, $sz")>;
908  let cy = 0 in def irr : RR<opc, (outs RC:$sx), (ins simm7:$sy, RC:$sz, RC:$sx_in),
909                             !strconcat(opcStr, " $sx, $sy, $sz")>;
910  let cz = 0 in def rzr : RR<opc, (outs RC:$sx), (ins RC:$sy, zero:$sz, RC:$sx_in),
911                             !strconcat(opcStr, " $sx, $sy, $sz")>;
912  let cy = 0, cz = 0 in
913  def izr : RR<opc, (outs RC:$sx), (ins simm7:$sy, zero:$sz, RC:$sx_in),
914               !strconcat(opcStr, " $sx, $sy, $sz")>;
915}
916
917
918// Multiclass for communication register instructions.
919//   e.g. FIDCR
920let cz = 0, hasSideEffects = 1 in
921multiclass FIDCRm<string opcStr, bits<8>opc, RegisterClass RC> {
922  def ri : RR<opc, (outs RC:$sx), (ins RC:$sy, uimm3:$sz),
923              !strconcat(opcStr, " $sx, $sy, $sz")>;
924  let cy = 0 in def ii : RR<opc, (outs RC:$sx), (ins simm7:$sy, uimm3:$sz),
925                            !strconcat(opcStr, " $sx, $sy, $sz")>;
926}
927
928// Multiclass for LHM instruction.
929let mayLoad = 1, hasSideEffects = 0 in
930multiclass LHMm<string opcStr, bits<8> opc, RegisterClass RC> {
931  def ri : RRMHM<opc, (outs RC:$dest), (ins MEMriHM:$addr),
932                 !strconcat(opcStr, " $dest, $addr")>;
933  let cz = 0 in
934  def zi : RRMHM<opc, (outs RC:$dest), (ins MEMziHM:$addr),
935                 !strconcat(opcStr, " $dest, $addr")>;
936}
937
938// Multiclass for SHM instruction.
939let mayStore = 1, hasSideEffects = 0 in
940multiclass SHMm<string opcStr, bits<8> opc, RegisterClass RC> {
941  def ri : RRMHM<opc, (outs), (ins MEMriHM:$addr, RC:$sx),
942                 !strconcat(opcStr, " $sx, $addr")>;
943  let cz = 0 in
944  def zi : RRMHM<opc, (outs), (ins MEMziHM:$addr, RC:$sx),
945                 !strconcat(opcStr, " $sx, $addr")>;
946}
947
948//===----------------------------------------------------------------------===//
949// Instructions
950//
951// Define all scalar instructions defined in SX-Aurora TSUBASA Architecture
952// Guide here.  As those mnemonics, we use mnemonics defined in Vector Engine
953// Assembly Language Reference Manual.
954//===----------------------------------------------------------------------===//
955
956//-----------------------------------------------------------------------------
957// Section 8.2 - Load/Store instructions
958//-----------------------------------------------------------------------------
959
960// Multiclass for generic RM instructions
961multiclass RMm<string opcStr, bits<8>opc, RegisterClass RC, bit MoveImm = 0> {
962  def rri : RM<opc, (outs RC:$dest), (ins MEMrri:$addr),
963               !strconcat(opcStr, " $dest, $addr"), []>;
964  let cy = 0 in
965  def rii : RM<opc, (outs RC:$dest), (ins MEMrii:$addr),
966               !strconcat(opcStr, " $dest, $addr"), []>;
967  let cz = 0 in
968  def zri : RM<opc, (outs RC:$dest), (ins MEMzri:$addr),
969               !strconcat(opcStr, " $dest, $addr"), []>;
970  let cy = 0, cz = 0 in
971  def zii : RM<opc, (outs RC:$dest), (ins MEMzii:$addr),
972               !strconcat(opcStr, " $dest, $addr"), []> {
973    // VE uses LEAzii and LEASLzii as a move immediate instruction, so declare
974    // it here.  An instruction declared as MoveImm will be optimized in
975    // FoldImmediate later.
976    let isMoveImm = MoveImm;
977  }
978}
979
980// Section 8.2.1 - LEA
981let isReMaterializable = 1, isAsCheapAsAMove = 1,
982    DecoderMethod = "DecodeLoadI64" in {
983  let cx = 0 in defm LEA : RMm<"lea", 0x06, I64, /* MoveImm */ 1>;
984  let cx = 1 in defm LEASL : RMm<"lea.sl", 0x06, I64, /* MoveImm */ 1>;
985}
986
987// LEA basic patterns.
988//   Need to be defined here to prioritize LEA over ADX.
989def : Pat<(iPTR ADDRrri:$addr), (LEArri MEMrri:$addr)>;
990def : Pat<(iPTR ADDRrii:$addr), (LEArii MEMrii:$addr)>;
991def : Pat<(add I64:$base, simm32:$disp), (LEArii $base, 0, (LO32 $disp))>;
992def : Pat<(add I64:$base, lozero:$disp), (LEASLrii $base, 0, (HI32 $disp))>;
993
994// Multiclass for load instructions.
995let mayLoad = 1, hasSideEffects = 0 in
996multiclass LOADm<string opcStr, bits<8> opc, RegisterClass RC, ValueType Ty,
997                 SDPatternOperator OpNode = null_frag> {
998  def rri : RM<opc, (outs RC:$dest), (ins MEMrri:$addr),
999               !strconcat(opcStr, " $dest, $addr"),
1000               [(set Ty:$dest, (OpNode ADDRrri:$addr))]>;
1001  let cy = 0 in
1002  def rii : RM<opc, (outs RC:$dest), (ins MEMrii:$addr),
1003               !strconcat(opcStr, " $dest, $addr"),
1004               [(set Ty:$dest, (OpNode ADDRrii:$addr))]>;
1005  let cz = 0 in
1006  def zri : RM<opc, (outs RC:$dest), (ins MEMzri:$addr),
1007               !strconcat(opcStr, " $dest, $addr"),
1008               [(set Ty:$dest, (OpNode ADDRzri:$addr))]>;
1009  let cy = 0, cz = 0 in
1010  def zii : RM<opc, (outs RC:$dest), (ins MEMzii:$addr),
1011               !strconcat(opcStr, " $dest, $addr"),
1012               [(set Ty:$dest, (OpNode ADDRzii:$addr))]>;
1013}
1014
1015// Section 8.2.2 - LDS
1016let DecoderMethod = "DecodeLoadI64" in
1017defm LD : LOADm<"ld", 0x01, I64, i64, load>;
1018def : Pat<(f64 (load ADDRrri:$addr)), (LDrri MEMrri:$addr)>;
1019def : Pat<(f64 (load ADDRrii:$addr)), (LDrii MEMrii:$addr)>;
1020def : Pat<(f64 (load ADDRzri:$addr)), (LDzri MEMzri:$addr)>;
1021def : Pat<(f64 (load ADDRzii:$addr)), (LDzii MEMzii:$addr)>;
1022
1023// Section 8.2.3 - LDU
1024let DecoderMethod = "DecodeLoadF32" in
1025defm LDU : LOADm<"ldu", 0x02, F32, f32, load>;
1026
1027// Section 8.2.4 - LDL
1028let DecoderMethod = "DecodeLoadI32" in
1029defm LDLSX : LOADm<"ldl.sx", 0x03, I32, i32, load>;
1030let cx = 1, DecoderMethod = "DecodeLoadI32" in
1031defm LDLZX : LOADm<"ldl.zx", 0x03, I32, i32, load>;
1032
1033// Section 8.2.5 - LD2B
1034let DecoderMethod = "DecodeLoadI32" in
1035defm LD2BSX : LOADm<"ld2b.sx", 0x04, I32, i32, sextloadi16>;
1036let cx = 1, DecoderMethod = "DecodeLoadI32" in
1037defm LD2BZX : LOADm<"ld2b.zx", 0x04, I32, i32, zextloadi16>;
1038
1039// Section 8.2.6 - LD1B
1040let DecoderMethod = "DecodeLoadI32" in
1041defm LD1BSX : LOADm<"ld1b.sx", 0x05, I32, i32, sextloadi8>;
1042let cx = 1, DecoderMethod = "DecodeLoadI32" in
1043defm LD1BZX : LOADm<"ld1b.zx", 0x05, I32, i32, zextloadi8>;
1044
1045// LDQ pseudo instructions
1046let mayLoad = 1, hasSideEffects = 0 in {
1047  def LDQrii : Pseudo<(outs F128:$dest), (ins MEMrii:$addr),
1048                      "# pseudo ldq $dest, $addr",
1049                      [(set f128:$dest, (load ADDRrii:$addr))]>;
1050}
1051
1052// Multiclass for store instructions.
1053let mayStore = 1 in
1054multiclass STOREm<string opcStr, bits<8> opc, RegisterClass RC, ValueType Ty,
1055                  SDPatternOperator OpNode = null_frag> {
1056  def rri : RM<opc, (outs), (ins MEMrri:$addr, RC:$sx),
1057               !strconcat(opcStr, " $sx, $addr"),
1058               [(OpNode Ty:$sx, ADDRrri:$addr)]>;
1059  let cy = 0 in
1060  def rii : RM<opc, (outs), (ins MEMrii:$addr, RC:$sx),
1061               !strconcat(opcStr, " $sx, $addr"),
1062               [(OpNode Ty:$sx, ADDRrii:$addr)]>;
1063  let cz = 0 in
1064  def zri : RM<opc, (outs), (ins MEMzri:$addr, RC:$sx),
1065               !strconcat(opcStr, " $sx, $addr"),
1066               [(OpNode Ty:$sx, ADDRzri:$addr)]>;
1067  let cy = 0, cz = 0 in
1068  def zii : RM<opc, (outs), (ins MEMzii:$addr, RC:$sx),
1069               !strconcat(opcStr, " $sx, $addr"),
1070               [(OpNode Ty:$sx, ADDRzii:$addr)]>;
1071}
1072
1073// Section 8.2.7 - STS
1074let DecoderMethod = "DecodeStoreI64" in
1075defm ST : STOREm<"st", 0x11, I64, i64, store>;
1076def : Pat<(store f64:$src, ADDRrri:$addr), (STrri MEMrri:$addr, $src)>;
1077def : Pat<(store f64:$src, ADDRrii:$addr), (STrii MEMrii:$addr, $src)>;
1078def : Pat<(store f64:$src, ADDRzri:$addr), (STzri MEMzri:$addr, $src)>;
1079def : Pat<(store f64:$src, ADDRzii:$addr), (STzii MEMzii:$addr, $src)>;
1080
1081// Section 8.2.8 - STU
1082let DecoderMethod = "DecodeStoreF32" in
1083defm STU : STOREm<"stu", 0x12, F32, f32, store>;
1084
1085// Section 8.2.9 - STL
1086let DecoderMethod = "DecodeStoreI32" in
1087defm STL : STOREm<"stl", 0x13, I32, i32, store>;
1088
1089// Section 8.2.10 - ST2B
1090let DecoderMethod = "DecodeStoreI32" in
1091defm ST2B : STOREm<"st2b", 0x14, I32, i32, truncstorei16>;
1092
1093// Section 8.2.11 - ST1B
1094let DecoderMethod = "DecodeStoreI32" in
1095defm ST1B : STOREm<"st1b", 0x15, I32, i32, truncstorei8>;
1096
1097// STQ pseudo instructions
1098let mayStore = 1, hasSideEffects = 0 in {
1099  def STQrii : Pseudo<(outs), (ins MEMrii:$addr, F128:$sx),
1100                      "# pseudo stq $sx, $addr",
1101                      [(store f128:$sx, ADDRrii:$addr)]>;
1102}
1103
1104// Section 8.2.12 - DLDS
1105let DecoderMethod = "DecodeLoadI64" in
1106defm DLD : LOADm<"dld", 0x09, I64, i64, load>;
1107
1108// Section 8.2.13 - DLDU
1109let DecoderMethod = "DecodeLoadF32" in
1110defm DLDU : LOADm<"dldu", 0x0a, F32, f32, load>;
1111
1112// Section 8.2.14 - DLDL
1113let DecoderMethod = "DecodeLoadI32" in
1114defm DLDLSX : LOADm<"dldl.sx", 0x0b, I32, i32, load>;
1115let cx = 1, DecoderMethod = "DecodeLoadI32" in
1116defm DLDLZX : LOADm<"dldl.zx", 0x0b, I32, i32, load>;
1117
1118// Section 8.2.15 - PFCH
1119let DecoderMethod = "DecodeASX" in
1120defm PFCH : PFCHm<"pfch", 0x0c>;
1121
1122// Section 8.2.16 - TS1AM (Test and Set 1 AM)
1123let DecoderMethod = "DecodeTS1AMI64" in
1124defm TS1AML : RRCASm<"ts1am.l", 0x42, I64, i64, uimm7>;
1125let DecoderMethod = "DecodeTS1AMI32", cx = 1 in
1126defm TS1AMW : RRCASm<"ts1am.w", 0x42, I32, i32, uimm7>;
1127
1128// Section 8.2.17 - TS2AM (Test and Set 2 AM)
1129let DecoderMethod = "DecodeTS1AMI64" in
1130defm TS2AM : RRCASm<"ts2am", 0x43, I64, i64, uimm7>;
1131
1132// Section 8.2.18 - TS3AM (Test and Set 3 AM)
1133let DecoderMethod = "DecodeTS1AMI64" in
1134defm TS3AM : RRCASm<"ts3am", 0x52, I64, i64, uimm1>;
1135
1136// Section 8.2.19 - ATMAM (Atomic AM)
1137let DecoderMethod = "DecodeTS1AMI64" in
1138defm ATMAM : RRCASm<"atmam", 0x53, I64, i64, uimm0to2>;
1139
1140// Section 8.2.20 - CAS (Compare and Swap)
1141let DecoderMethod = "DecodeCASI64" in
1142defm CASL : RRCASm<"cas.l", 0x62, I64, i64, simm7, atomic_cmp_swap_64>;
1143let DecoderMethod = "DecodeCASI32", cx = 1 in
1144defm CASW : RRCASm<"cas.w", 0x62, I32, i32, simm7, atomic_cmp_swap_32>;
1145
1146//-----------------------------------------------------------------------------
1147// Section 8.3 - Transfer Control Instructions
1148//-----------------------------------------------------------------------------
1149
1150// Section 8.3.1 - FENCE (Fence)
1151let hasSideEffects = 1 in {
1152  let avo = 1 in def FENCEI : RRFENCE<0x20, (outs), (ins), "fencei">;
1153  def FENCEM : RRFENCE<0x20, (outs), (ins uimm2:$kind), "fencem $kind"> {
1154    bits<2> kind;
1155    let lf = kind{1};
1156    let sf = kind{0};
1157  }
1158  def FENCEC : RRFENCE<0x20, (outs), (ins uimm3:$kind), "fencec $kind"> {
1159    bits<3> kind;
1160    let c2 = kind{2};
1161    let c1 = kind{1};
1162    let c0 = kind{0};
1163  }
1164}
1165
1166// Section 8.3.2 - SVOB (Set Vector Out-of-order memory access Boundary)
1167let sx = 0, cy = 0, sy = 0, cz = 0, sz = 0, hasSideEffects = 1 in
1168def SVOB : RR<0x30, (outs), (ins), "svob">;
1169
1170//-----------------------------------------------------------------------------
1171// Section 8.4 - Fixed-point Operation Instructions
1172//-----------------------------------------------------------------------------
1173
1174let isReMaterializable = 1, isAsCheapAsAMove = 1 in {
1175
1176// Section 8.4.1 - ADD (Add)
1177defm ADDUL : RRm<"addu.l", 0x48, I64, i64>;
1178let cx = 1 in defm ADDUW : RRm<"addu.w", 0x48, I32, i32>;
1179
1180// Section 8.4.2 - ADS (Add Single)
1181defm ADDSWSX : RRm<"adds.w.sx", 0x4A, I32, i32, add>;
1182let cx = 1 in defm ADDSWZX : RRm<"adds.w.zx", 0x4A, I32, i32>;
1183
1184// Section 8.4.3 - ADX (Add)
1185defm ADDSL : RRm<"adds.l", 0x59, I64, i64, add>;
1186
1187// Section 8.4.4 - SUB (Subtract)
1188defm SUBUL : RRNCm<"subu.l", 0x58, I64, i64>;
1189let cx = 1 in defm SUBUW : RRNCm<"subu.w", 0x58, I32, i32>;
1190
1191// Section 8.4.5 - SBS (Subtract Single)
1192defm SUBSWSX : RRNCm<"subs.w.sx", 0x5A, I32, i32, sub>;
1193let cx = 1 in defm SUBSWZX : RRNCm<"subs.w.zx", 0x5A, I32, i32>;
1194
1195// Section 8.4.6 - SBX (Subtract)
1196defm SUBSL : RRNCm<"subs.l", 0x5B, I64, i64, sub>;
1197
1198} // isReMaterializable, isAsCheapAsAMove
1199
1200// Section 8.4.7 - MPY (Multiply)
1201defm MULUL : RRm<"mulu.l", 0x49, I64, i64>;
1202let cx = 1 in defm MULUW : RRm<"mulu.w", 0x49, I32, i32>;
1203
1204// Section 8.4.8 - MPS (Multiply Single)
1205defm MULSWSX : RRm<"muls.w.sx", 0x4B, I32, i32, mul>;
1206let cx = 1 in defm MULSWZX : RRm<"muls.w.zx", 0x4B, I32, i32>;
1207
1208// Section 8.4.9 - MPX (Multiply)
1209defm MULSL : RRm<"muls.l", 0x6E, I64, i64, mul>;
1210
1211// Section 8.4.10 - MPD (Multiply)
1212defm MULSLW : RRbm<"muls.l.w", 0x6B, I64, i64, I32, i32>;
1213
1214// Section 8.4.11 - DIV (Divide)
1215defm DIVUL : RRNCm<"divu.l", 0x6F, I64, i64, udiv>;
1216let cx = 1 in defm DIVUW : RRNCm<"divu.w", 0x6F, I32, i32, udiv>;
1217
1218// Section 8.4.12 - DVS (Divide Single)
1219defm DIVSWSX : RRNCm<"divs.w.sx", 0x7B, I32, i32, sdiv>;
1220let cx = 1 in defm DIVSWZX : RRNCm<"divs.w.zx", 0x7B, I32, i32>;
1221
1222// Section 8.4.13 - DVX (Divide)
1223defm DIVSL : RRNCm<"divs.l", 0x7F, I64, i64, sdiv>;
1224
1225let isReMaterializable = 1, isAsCheapAsAMove = 1 in {
1226
1227// Section 8.4.14 - CMP (Compare)
1228defm CMPUL : RRNCm<"cmpu.l", 0x55, I64, i64>;
1229let cx = 1 in defm CMPUW : RRNCm<"cmpu.w", 0x55, I32, i32>;
1230
1231// Section 8.4.15 - CPS (Compare Single)
1232defm CMPSWSX : RRNCm<"cmps.w.sx", 0x7A, I32, i32>;
1233let cx = 1 in defm CMPSWZX : RRNCm<"cmps.w.zx", 0x7A, I32, i32>;
1234
1235// Section 8.4.16 - CPX (Compare)
1236defm CMPSL : RRNCm<"cmps.l", 0x6A, I64, i64>;
1237
1238// Section 8.4.17 - CMS (Compare and Select Maximum/Minimum Single)
1239// cx: sx/zx, cw: max/min
1240defm MAXSWSX : RRm<"maxs.w.sx", 0x78, I32, i32>;
1241let cx = 1 in defm MAXSWZX : RRm<"maxs.w.zx", 0x78, I32, i32>;
1242let cw = 1 in defm MINSWSX : RRm<"mins.w.sx", 0x78, I32, i32>;
1243let cx = 1, cw = 1 in defm MINSWZX : RRm<"mins.w.zx", 0x78, I32, i32>;
1244
1245// Section 8.4.18 - CMX (Compare and Select Maximum/Minimum)
1246defm MAXSL : RRm<"maxs.l", 0x68, I64, i64>;
1247let cw = 1 in defm MINSL : RRm<"mins.l", 0x68, I64, i64>;
1248
1249} // isReMaterializable, isAsCheapAsAMove
1250
1251//-----------------------------------------------------------------------------
1252// Section 8.5 - Logical Operation Instructions
1253//-----------------------------------------------------------------------------
1254
1255let isReMaterializable = 1, isAsCheapAsAMove = 1 in {
1256
1257// Section 8.5.1 - AND (AND)
1258defm AND : RRm<"and", 0x44, I64, i64, and>;
1259
1260// Section 8.5.2 - OR (OR)
1261defm OR : RRm<"or", 0x45, I64, i64, or, simm7, mimm, /* MoveImm */ 1>;
1262
1263// Section 8.5.3 - XOR (Exclusive OR)
1264defm XOR : RRm<"xor", 0x46, I64, i64, xor>;
1265
1266// Section 8.5.4 - EQV (Equivalence)
1267defm EQV : RRm<"eqv", 0x47, I64, i64>;
1268
1269} // isReMaterializable, isAsCheapAsAMove
1270
1271// Section 8.5.5 - NND (Negate AND)
1272def and_not : PatFrags<(ops node:$x, node:$y),
1273                       [(and (not node:$x), node:$y)]>;
1274let isReMaterializable = 1, isAsCheapAsAMove = 1 in
1275defm NND : RRNCm<"nnd", 0x54, I64, i64, and_not>;
1276
1277// Section 8.5.6 - MRG (Merge)
1278defm MRG : RRMRGm<"mrg", 0x56, I64>;
1279
1280// Section 8.5.7 - LDZ (Leading Zero Count)
1281def ctlz_pat : PatFrags<(ops node:$src),
1282                        [(ctlz node:$src),
1283                         (ctlz_zero_undef node:$src)]>;
1284let isReMaterializable = 1, isAsCheapAsAMove = 1 in
1285defm LDZ : RRI1m<"ldz", 0x67, I64, i64, ctlz_pat>;
1286
1287// Section 8.5.8 - PCNT (Population Count)
1288defm PCNT : RRI1m<"pcnt", 0x38, I64, i64, ctpop>;
1289
1290// Section 8.5.9 - BRV (Bit Reverse)
1291let isReMaterializable = 1, isAsCheapAsAMove = 1 in
1292defm BRV : RRI1m<"brv", 0x39, I64, i64, bitreverse>;
1293
1294// Section 8.5.10 - BSWP (Byte Swap)
1295let isReMaterializable = 1, isAsCheapAsAMove = 1 in
1296defm BSWP : RRSWPm<"bswp", 0x2B, I64, i64>;
1297
1298def : Pat<(i64 (bswap i64:$src)),
1299          (BSWPri $src, 0)>;
1300def : Pat<(i64 (bswap (i64 mimm:$src))),
1301          (BSWPmi (MIMM $src), 0)>;
1302def : Pat<(i32 (bswap i32:$src)),
1303          (EXTRACT_SUBREG
1304              (BSWPri (INSERT_SUBREG (i64 (IMPLICIT_DEF)), $src, sub_i32), 1),
1305              sub_i32)>;
1306def : Pat<(i32 (bswap (i32 mimm:$src))),
1307          (EXTRACT_SUBREG (BSWPmi (MIMM $src), 1), sub_i32)>;
1308
1309// Section 8.5.11 - CMOV (Conditional Move)
1310let cw = 0, cw2 = 0 in defm CMOVL : RRCMOVm<"cmov.l.${cfw}", 0x3B, I64>;
1311let cw = 1, cw2 = 0 in defm CMOVW : RRCMOVm<"cmov.w.${cfw}", 0x3B, I32>;
1312let cw = 0, cw2 = 1 in defm CMOVD : RRCMOVm<"cmov.d.${cfw}", 0x3B, I64>;
1313let cw = 1, cw2 = 1 in defm CMOVS : RRCMOVm<"cmov.s.${cfw}", 0x3B, F32>;
1314def : MnemonicAlias<"cmov.l", "cmov.l.at">;
1315def : MnemonicAlias<"cmov.w", "cmov.w.at">;
1316def : MnemonicAlias<"cmov.d", "cmov.d.at">;
1317def : MnemonicAlias<"cmov.s", "cmov.s.at">;
1318
1319//-----------------------------------------------------------------------------
1320// Section 8.6 - Shift Operation Instructions
1321//-----------------------------------------------------------------------------
1322
1323// Section 8.6.1 - SLL (Shift Left Logical)
1324let isReMaterializable = 1, isAsCheapAsAMove = 1 in
1325defm SLL : RRIm<"sll", 0x65, I64, i64, shl>;
1326
1327// Section 8.6.2 - SLD (Shift Left Double)
1328defm SLD : RRILDm<"sld", 0x64, I64>;
1329
1330// Section 8.6.3 - SRL (Shift Right Logical)
1331let isReMaterializable = 1, isAsCheapAsAMove = 1 in
1332defm SRL : RRIm<"srl", 0x75, I64, i64, srl>;
1333
1334// Section 8.6.4 - SRD (Shift Right Double)
1335defm SRD : RRIRDm<"srd", 0x74, I64>;
1336
1337let isReMaterializable = 1, isAsCheapAsAMove = 1 in {
1338
1339// Section 8.6.5 - SLA (Shift Left Arithmetic)
1340defm SLAWSX : RRIm<"sla.w.sx", 0x66, I32, i32, shl>;
1341let cx = 1 in defm SLAWZX : RRIm<"sla.w.zx", 0x66, I32, i32>;
1342
1343// Section 8.6.6 - SLAX (Shift Left Arithmetic)
1344defm SLAL : RRIm<"sla.l", 0x57, I64, i64>;
1345
1346// Section 8.6.7 - SRA (Shift Right Arithmetic)
1347defm SRAWSX : RRIm<"sra.w.sx", 0x76, I32, i32, sra>;
1348let cx = 1 in defm SRAWZX : RRIm<"sra.w.zx", 0x76, I32, i32>;
1349
1350// Section 8.6.8 - SRAX (Shift Right Arithmetic)
1351defm SRAL : RRIm<"sra.l", 0x77, I64, i64, sra>;
1352
1353} // isReMaterializable, isAsCheapAsAMove
1354
1355def : Pat<(i32 (srl i32:$src, (i32 simm7:$val))),
1356          (EXTRACT_SUBREG (SRLri (ANDrm (INSERT_SUBREG (i64 (IMPLICIT_DEF)),
1357            $src, sub_i32), !add(32, 64)), imm:$val), sub_i32)>;
1358def : Pat<(i32 (srl i32:$src, i32:$val)),
1359          (EXTRACT_SUBREG (SRLrr (ANDrm (INSERT_SUBREG (i64 (IMPLICIT_DEF)),
1360            $src, sub_i32), !add(32, 64)), $val), sub_i32)>;
1361
1362//-----------------------------------------------------------------------------
1363// Section 8.7 - Floating-point Arithmetic Instructions
1364//-----------------------------------------------------------------------------
1365
1366// Section 8.7.1 - FAD (Floating Add)
1367defm FADDD : RRFm<"fadd.d", 0x4C, I64, f64, fadd>;
1368let cx = 1 in
1369defm FADDS : RRFm<"fadd.s", 0x4C, F32, f32, fadd, simm7fp, mimmfp32>;
1370
1371// Section 8.7.2 - FSB (Floating Subtract)
1372defm FSUBD : RRFm<"fsub.d", 0x5C, I64, f64, fsub>;
1373let cx = 1 in
1374defm FSUBS : RRFm<"fsub.s", 0x5C, F32, f32, fsub, simm7fp, mimmfp32>;
1375
1376// Section 8.7.3 - FMP (Floating Multiply)
1377defm FMULD : RRFm<"fmul.d", 0x4D, I64, f64, fmul>;
1378let cx = 1 in
1379defm FMULS : RRFm<"fmul.s", 0x4D, F32, f32, fmul, simm7fp, mimmfp32>;
1380
1381// Section 8.7.4 - FDV (Floating Divide)
1382defm FDIVD : RRFm<"fdiv.d", 0x5D, I64, f64, fdiv>;
1383let cx = 1 in
1384defm FDIVS : RRFm<"fdiv.s", 0x5D, F32, f32, fdiv, simm7fp, mimmfp32>;
1385
1386// Section 8.7.5 - FCP (Floating Compare)
1387defm FCMPD : RRFm<"fcmp.d", 0x7E, I64, f64>;
1388let cx = 1 in
1389defm FCMPS : RRFm<"fcmp.s", 0x7E, F32, f32, null_frag, simm7fp, mimmfp32>;
1390
1391// Section 8.7.6 - CMS (Compare and Select Maximum/Minimum Single)
1392// cx: double/float, cw: max/min
1393let cw = 0, cx = 0 in
1394defm FMAXD : RRFm<"fmax.d", 0x3E, I64, f64, fmaxnum>;
1395let cw = 0, cx = 1 in
1396defm FMAXS : RRFm<"fmax.s", 0x3E, F32, f32, fmaxnum, simm7fp, mimmfp32>;
1397let cw = 1, cx = 0 in
1398defm FMIND : RRFm<"fmin.d", 0x3E, I64, f64, fminnum>;
1399let cw = 1, cx = 1 in
1400defm FMINS : RRFm<"fmin.s", 0x3E, F32, f32, fminnum, simm7fp, mimmfp32>;
1401
1402// Section 8.7.7 - FAQ (Floating Add Quadruple)
1403defm FADDQ : RRFm<"fadd.q", 0x6C, F128, f128, fadd>;
1404
1405// Section 8.7.8 - FSQ (Floating Subtract Quadruple)
1406defm FSUBQ : RRFm<"fsub.q", 0x7C, F128, f128, fsub>;
1407
1408// Section 8.7.9 - FMQ (Floating Subtract Quadruple)
1409defm FMULQ : RRFm<"fmul.q", 0x6D, F128, f128, fmul>;
1410
1411// Section 8.7.10 - FCQ (Floating Compare Quadruple)
1412defm FCMPQ : RRNCbm<"fcmp.q", 0x7D, I64, f64, F128, f128, null_frag, simm7fp,
1413                    mimmfp>;
1414
1415// Section 8.7.11 - FIX (Convert to Fixed Point)
1416// cx: double/float, cw: sx/zx, sz{0-3} = round
1417let cx = 0, cw = 0 /* sign extend */ in
1418defm CVTWDSX : CVTRDm<"cvt.w.d.sx", 0x4E, I32, I64>;
1419let cx = 0, cw = 1 /* zero extend */ in
1420defm CVTWDZX : CVTRDm<"cvt.w.d.zx", 0x4E, I32, I64>;
1421let cx = 1, cw = 0 /* sign extend */ in
1422defm CVTWSSX : CVTRDm<"cvt.w.s.sx", 0x4E, I32, F32>;
1423let cx = 1, cw = 1 /* zero extend */ in
1424defm CVTWSZX : CVTRDm<"cvt.w.s.zx", 0x4E, I32, F32>;
1425
1426// Section 8.7.12 - FIXX (Convert to Fixed Point)
1427defm CVTLD : CVTRDm<"cvt.l.d", 0x4F, I64, I64>;
1428
1429// Section 8.7.13 - FLT (Convert to Floating Point)
1430defm CVTDW : CVTm<"cvt.d.w", 0x5E, I64, f64, I32, i32, sint_to_fp>;
1431let cx = 1 in
1432defm CVTSW : CVTm<"cvt.s.w", 0x5E, F32, f32, I32, i32, sint_to_fp>;
1433
1434// Section 8.7.14 - FLTX (Convert to Floating Point)
1435defm CVTDL : CVTm<"cvt.d.l", 0x5F, I64, f64, I64, i64, sint_to_fp>;
1436
1437// Section 8.7.15 - CVS (Convert to Single-format)
1438defm CVTSD : CVTm<"cvt.s.d", 0x1F, F32, f32, I64, f64, fpround>;
1439let cx = 1 in
1440defm CVTSQ : CVTm<"cvt.s.q", 0x1F, F32, f32, F128, f128, fpround>;
1441
1442// Section 8.7.16 - CVD (Convert to Double-format)
1443defm CVTDS : CVTm<"cvt.d.s", 0x0F, I64, f64, F32, f32, fpextend>;
1444let cx = 1 in
1445defm CVTDQ : CVTm<"cvt.d.q", 0x0F, I64, f64, F128, f128, fpround>;
1446
1447// Section 8.7.17 - CVQ (Convert to Single-format)
1448defm CVTQD : CVTm<"cvt.q.d", 0x2D, F128, f128, I64, f64, fpextend>;
1449let cx = 1 in
1450defm CVTQS : CVTm<"cvt.q.s", 0x2D, F128, f128, F32, f32, fpextend>;
1451
1452//-----------------------------------------------------------------------------
1453// Section 8.8 - Branch instructions
1454//-----------------------------------------------------------------------------
1455
1456// Section 8.8.1 - BC (Branch on Codition)
1457defm BCFL : BCm<"b${cond}.l", "b.l", "baf.l", 0x19, I64, simm7>;
1458
1459// Indirect branch aliases
1460def : Pat<(brind I64:$reg), (BCFLari_t $reg, 0)>;
1461def : Pat<(brind tblockaddress:$imm), (BCFLazi_t 0, $imm)>;
1462
1463// Return instruction is a special case of jump.
1464let Uses = [SX10], bpf = 3 /* TAKEN */, cf = 15 /* AT */, cy = 0, sy = 0,
1465    sz = 10 /* SX10 */, imm32 = 0, isReturn = 1, isTerminator = 1,
1466    isBarrier = 1, isCodeGenOnly = 1, hasSideEffects = 0 in
1467def RET : CF<0x19, (outs), (ins), "b.l.t (, %s10)", [(retflag)]>;
1468
1469// Section 8.8.2 - BCS (Branch on Condition Single)
1470defm BCFW : BCm<"b${cond}.w", "b.w", "baf.w", 0x1B, I32, simm7>;
1471
1472// Section 8.8.3 - BCF (Branch on Condition Floating Point)
1473defm BCFD : BCm<"b${cond}.d", "b.d", "baf.d", 0x1C, I64, simm7fp>;
1474let cx = 1 in
1475defm BCFS : BCm<"b${cond}.s", "b.s", "baf.s", 0x1C, F32, simm7fp>;
1476
1477// Section 8.8.4 - BCR (Branch on Condition Relative)
1478let cx = 0, cx2 = 0 in
1479defm BRCFL : BCRm<"br${cf}.l", "br.l", "braf.l", 0x18, I64, simm7, zero>;
1480let cx = 1, cx2 = 0 in
1481defm BRCFW : BCRm<"br${cf}.w", "br.w", "braf.w", 0x18, I32, simm7, zero>;
1482let cx = 0, cx2 = 1 in
1483defm BRCFD : BCRm<"br${cf}.d", "br.d", "braf.d", 0x18, I64, simm7fp, zerofp>;
1484let cx = 1, cx2 = 1 in
1485defm BRCFS : BCRm<"br${cf}.s", "br.s", "braf.s", 0x18, F32, simm7fp, zerofp>;
1486
1487// Section 8.8.5 - BSIC (Branch and Save IC)
1488let isCall = 1, hasSideEffects = 0, DecoderMethod = "DecodeCall" in
1489defm BSIC : RMm<"bsic", 0x08, I64>;
1490
1491// Call instruction is a special case of BSIC.
1492let Defs = [SX10], sx = 10 /* SX10 */, cy = 0, sy = 0, imm32 = 0,
1493    isCall = 1, isCodeGenOnly = 1, hasSideEffects = 0 in
1494def CALLr : RM<0x08, (outs), (ins I64:$sz, variable_ops),
1495               "bsic %s10, (, $sz)", [(call i64:$sz)]>;
1496
1497//-----------------------------------------------------------------------------
1498// Section 8.19 - Control Instructions
1499//-----------------------------------------------------------------------------
1500
1501// Section 8.19.1 - SIC (Save Instruction Counter)
1502let cy = 0, sy = 0, cz = 0, sz = 0, hasSideEffects = 1, Uses = [IC] in
1503def SIC : RR<0x28, (outs I32:$sx), (ins), "sic $sx">;
1504
1505// Section 8.19.2 - LPM (Load Program Mode Flags)
1506let sx = 0, cz = 0, sz = 0, hasSideEffects = 1, Defs = [PSW] in
1507def LPM : RR<0x3a, (outs), (ins I64:$sy), "lpm $sy">;
1508
1509// Section 8.19.3 - SPM (Save Program Mode Flags)
1510let cy = 0, sy = 0, cz = 0, sz = 0, hasSideEffects = 1, Uses = [PSW] in
1511def SPM : RR<0x2a, (outs I64:$sx), (ins), "spm $sx">;
1512
1513// Section 8.19.4 - LFR (Load Flag Register)
1514let sx = 0, cz = 0, sz = 0, hasSideEffects = 1, Defs = [PSW] in {
1515  def LFRr : RR<0x69, (outs), (ins I64:$sy), "lfr $sy">;
1516  let cy = 0 in def LFRi : RR<0x69, (outs), (ins uimm6:$sy), "lfr $sy">;
1517}
1518
1519// Section 8.19.5 - SFR (Save Flag Register)
1520let cy = 0, sy = 0, cz = 0, sz = 0, hasSideEffects = 1, Uses = [PSW] in
1521def SFR : RR<0x29, (outs I64:$sx), (ins), "sfr $sx">;
1522
1523// Section 8.19.6 - SMIR (Save Miscellaneous Register)
1524let cy = 0, cz = 0, sz = 0, hasSideEffects = 1 in {
1525  def SMIR : RR<0x22, (outs I64:$sx), (ins MISC:$sy), "smir $sx, $sy">;
1526}
1527
1528// Section 8.19.7 - NOP (No Operation)
1529let sx = 0, cy = 0, sy = 0, cz = 0, sz = 0, hasSideEffects = 0 in
1530def NOP : RR<0x79, (outs), (ins), "nop">;
1531
1532// Section 8.19.8 - MONC (Monitor Call)
1533let sx = 0, cy = 0, sy = 0, cz = 0, sz = 0, hasSideEffects = 1 in {
1534  def MONC : RR<0x3F, (outs), (ins), "monc">;
1535  let cx = 1, isTrap = 1 in def MONCHDB : RR<0x3F, (outs), (ins), "monc.hdb">;
1536}
1537
1538// Section 8.19.9 - LCR (Load Communication Register)
1539defm LCR : LOADCRm<"lcr", 0x40, I64>;
1540
1541// Section 8.19.10 - SCR (Save Communication Register)
1542defm SCR : STORECRm<"scr", 0x50, I64>;
1543
1544// Section 8.19.11 - TSCR (Test & Set Communication Register)
1545defm TSCR : TSCRm<"tscr", 0x41, I64>;
1546
1547// Section 8.19.12 - FIDCR (Fetch & Increment/Decrement CR)
1548defm FIDCR : FIDCRm<"fidcr", 0x51, I64>;
1549
1550//-----------------------------------------------------------------------------
1551// Section 8.20 - Host Memory Access Instructions
1552//-----------------------------------------------------------------------------
1553
1554// Section 8.20.1 - LHM (Load Host Memory)
1555let ry = 3, DecoderMethod = "DecodeLoadASI64" in
1556defm LHML : LHMm<"lhm.l", 0x21, I64>;
1557let ry = 2, DecoderMethod = "DecodeLoadASI64" in
1558defm LHMW : LHMm<"lhm.w", 0x21, I64>;
1559let ry = 1, DecoderMethod = "DecodeLoadASI64" in
1560defm LHMH : LHMm<"lhm.h", 0x21, I64>;
1561let ry = 0, DecoderMethod = "DecodeLoadASI64" in
1562defm LHMB : LHMm<"lhm.b", 0x21, I64>;
1563
1564// Section 8.20.2 - SHM (Store Host Memory)
1565let ry = 3, DecoderMethod = "DecodeStoreASI64" in
1566defm SHML : SHMm<"shm.l", 0x31, I64>;
1567let ry = 2, DecoderMethod = "DecodeStoreASI64" in
1568defm SHMW : SHMm<"shm.w", 0x31, I64>;
1569let ry = 1, DecoderMethod = "DecodeStoreASI64" in
1570defm SHMH : SHMm<"shm.h", 0x31, I64>;
1571let ry = 0, DecoderMethod = "DecodeStoreASI64" in
1572defm SHMB : SHMm<"shm.b", 0x31, I64>;
1573
1574//===----------------------------------------------------------------------===//
1575// Instructions for CodeGenOnly
1576//===----------------------------------------------------------------------===//
1577
1578//===----------------------------------------------------------------------===//
1579// Pattern Matchings
1580//===----------------------------------------------------------------------===//
1581
1582// Basic cast between registers.  This is often used in ISel patterns, so make
1583// them as OutPatFrag.
1584def i2l : OutPatFrag<(ops node:$exp),
1585                     (INSERT_SUBREG (i64 (IMPLICIT_DEF)), $exp, sub_i32)>;
1586def l2i : OutPatFrag<(ops node:$exp),
1587                     (EXTRACT_SUBREG $exp, sub_i32)>;
1588def f2l : OutPatFrag<(ops node:$exp),
1589                     (INSERT_SUBREG (i64 (IMPLICIT_DEF)), $exp, sub_f32)>;
1590def l2f : OutPatFrag<(ops node:$exp),
1591                     (EXTRACT_SUBREG $exp, sub_f32)>;
1592
1593// Zero out subregisters.
1594def zero_i32 : OutPatFrag<(ops node:$expr),
1595                          (ANDrm $expr, 32)>;
1596def zero_f32 : OutPatFrag<(ops node:$expr),
1597                          (ANDrm $expr, !add(32, 64))>;
1598
1599// Small immediates.
1600def : Pat<(i32 simm7:$val), (EXTRACT_SUBREG (ORim (LO7 $val), 0), sub_i32)>;
1601def : Pat<(i64 simm7:$val), (ORim (LO7 $val), 0)>;
1602// Medium immediates.
1603def : Pat<(i32 simm32:$val),
1604          (EXTRACT_SUBREG (LEAzii 0, 0, (LO32 $val)), sub_i32)>;
1605def : Pat<(i64 simm32:$val), (LEAzii 0, 0, (LO32 $val))>;
1606def : Pat<(i64 uimm32:$val), (ANDrm (LEAzii 0, 0, (LO32 $val)), !add(32, 64))>;
1607// Arbitrary immediates.
1608def : Pat<(i64 lozero:$val),
1609          (LEASLzii 0, 0, (HI32 imm:$val))>;
1610def : Pat<(i64 lomsbzero:$val),
1611          (LEASLrii (LEAzii 0, 0, (LO32 imm:$val)), 0, (HI32 imm:$val))>;
1612def : Pat<(i64 imm:$val),
1613          (LEASLrii (ANDrm (LEAzii 0, 0, (LO32 imm:$val)), !add(32, 64)), 0,
1614                    (HI32 imm:$val))>;
1615
1616// LEA patterns
1617def lea_add : PatFrags<(ops node:$base, node:$idx, node:$disp),
1618                       [(add (add node:$base, node:$idx), node:$disp),
1619                        (add (add node:$base, node:$disp), node:$idx),
1620                        (add node:$base, (add $idx, $disp))]>;
1621def : Pat<(lea_add I64:$base, simm7:$idx, simm32:$disp),
1622          (LEArii $base, (LO7 $idx), (LO32 $disp))>;
1623def : Pat<(lea_add I64:$base, I64:$idx, simm32:$disp),
1624          (LEArri $base, $idx, (LO32 $disp))>;
1625def : Pat<(lea_add I64:$base, simm7:$idx, lozero:$disp),
1626          (LEASLrii $base, (LO7 $idx), (HI32 $disp))>;
1627def : Pat<(lea_add I64:$base, I64:$idx, lozero:$disp),
1628          (LEASLrri $base, $idx, (HI32 $disp))>;
1629
1630// Address calculation patterns and optimizations
1631//
1632// Generate following instructions:
1633//   1. LEA %reg, label@LO32
1634//      AND %reg, %reg, (32)0
1635//   2. LEASL %reg, label@HI32
1636//   3. (LEA %reg, label@LO32)
1637//      (AND %reg, %reg, (32)0)
1638//      LEASL %reg, label@HI32(, %reg)
1639//   4. (LEA %reg, label@LO32)
1640//      (AND %reg, %reg, (32)0)
1641//      LEASL %reg, label@HI32(%reg, %got)
1642//
1643def velo_only : OutPatFrag<(ops node:$lo),
1644                           (ANDrm (LEAzii 0, 0, $lo), !add(32, 64))>;
1645def vehi_only : OutPatFrag<(ops node:$hi),
1646                           (LEASLzii 0, 0, $hi)>;
1647def vehi_lo : OutPatFrag<(ops node:$hi, node:$lo),
1648                         (LEASLrii $lo, 0, $hi)>;
1649def vehi_lo_imm : OutPatFrag<(ops node:$hi, node:$lo, node:$idx),
1650                             (LEASLrii $lo, $idx, $hi)>;
1651def vehi_baselo : OutPatFrag<(ops node:$base, node:$hi, node:$lo),
1652                             (LEASLrri $base, $lo, $hi)>;
1653foreach type = [ "tblockaddress", "tconstpool", "texternalsym", "tglobaladdr",
1654                 "tglobaltlsaddr", "tjumptable" ] in {
1655  def : Pat<(VElo !cast<SDNode>(type):$lo), (velo_only $lo)>;
1656  def : Pat<(VEhi !cast<SDNode>(type):$hi), (vehi_only $hi)>;
1657  def : Pat<(add (VEhi !cast<SDNode>(type):$hi), I64:$lo), (vehi_lo $hi, $lo)>;
1658  def : Pat<(add (add (VEhi !cast<SDNode>(type):$hi), I64:$lo), simm7:$val),
1659            (vehi_lo_imm $hi, $lo, (LO7 $val))>;
1660  def : Pat<(add I64:$base, (add (VEhi !cast<SDNode>(type):$hi), I64:$lo)),
1661            (vehi_baselo $base, $hi, $lo)>;
1662}
1663
1664// floating point
1665def : Pat<(f32 fpimm:$val),
1666          (EXTRACT_SUBREG (LEASLzii 0, 0, (HIFP32 $val)), sub_f32)>;
1667def : Pat<(f64 fplozero:$val),
1668          (LEASLzii 0, 0, (HIFP32 $val))>;
1669def : Pat<(f64 fplomsbzero:$val),
1670          (LEASLrii (LEAzii 0, 0, (LOFP32 $val)), 0, (HIFP32 $val))>;
1671def : Pat<(f64 fpimm:$val),
1672          (LEASLrii (ANDrm (LEAzii 0, 0, (LOFP32 $val)), !add(32, 64)), 0,
1673                    (HIFP32 $val))>;
1674
1675// The same integer registers are used for i32 and i64 values.
1676// When registers hold i32 values, the high bits are unused.
1677
1678// TODO Use standard expansion for shift-based lowering of sext_inreg
1679
1680// Cast to i1
1681def : Pat<(sext_inreg I32:$src, i1),
1682          (SRAWSXri (SLAWSXri $src, 31), 31)>;
1683def : Pat<(sext_inreg I64:$src, i1),
1684          (SRALri (SLLri $src, 63), 63)>;
1685
1686// Cast to i8
1687def : Pat<(sext_inreg I32:$src, i8),
1688          (SRAWSXri (SLAWSXri $src, 24), 24)>;
1689def : Pat<(sext_inreg I64:$src, i8),
1690          (SRALri (SLLri $src, 56), 56)>;
1691def : Pat<(sext_inreg (i32 (trunc i64:$src)), i8),
1692          (EXTRACT_SUBREG (SRALri (SLLri $src, 56), 56), sub_i32)>;
1693def : Pat<(i32 (and (trunc i64:$src), 0xff)),
1694          (EXTRACT_SUBREG (ANDrm $src, !add(56, 64)), sub_i32)>;
1695
1696// Cast to i16
1697def : Pat<(sext_inreg I32:$src, i16),
1698          (SRAWSXri (SLAWSXri $src, 16), 16)>;
1699def : Pat<(sext_inreg I64:$src, i16),
1700          (SRALri (SLLri $src, 48), 48)>;
1701def : Pat<(sext_inreg (i32 (trunc i64:$src)), i16),
1702          (EXTRACT_SUBREG (SRALri (SLLri $src, 48), 48), sub_i32)>;
1703def : Pat<(i32 (and (trunc i64:$src), 0xffff)),
1704          (EXTRACT_SUBREG (ANDrm $src, !add(48, 64)), sub_i32)>;
1705
1706// Cast to i32
1707def : Pat<(i32 (trunc i64:$src)),
1708          (EXTRACT_SUBREG (ANDrm $src, !add(32, 64)), sub_i32)>;
1709def : Pat<(i32 (fp_to_sint f32:$src)), (CVTWSSXr RD_RZ, $src)>;
1710def : Pat<(i32 (fp_to_sint f64:$src)), (CVTWDSXr RD_RZ, $src)>;
1711def : Pat<(i32 (fp_to_sint f128:$src)), (CVTWDSXr RD_RZ, (CVTDQr $src))>;
1712
1713// Cast to i64
1714def : Pat<(sext_inreg i64:$src, i32),
1715          (INSERT_SUBREG (i64 (IMPLICIT_DEF)),
1716            (ADDSWSXrm (EXTRACT_SUBREG $src, sub_i32), 0), sub_i32)>;
1717def : Pat<(i64 (sext i32:$src)),
1718          (INSERT_SUBREG (i64 (IMPLICIT_DEF)), (ADDSWSXrm $src, 0), sub_i32)>;
1719def : Pat<(i64 (zext i32:$src)),
1720          (INSERT_SUBREG (i64 (IMPLICIT_DEF)), (ADDSWZXrm $src, 0), sub_i32)>;
1721def : Pat<(i64 (fp_to_sint f32:$src)), (CVTLDr RD_RZ, (CVTDSr $src))>;
1722def : Pat<(i64 (fp_to_sint f64:$src)), (CVTLDr RD_RZ, $src)>;
1723def : Pat<(i64 (fp_to_sint f128:$src)), (CVTLDr RD_RZ, (CVTDQr $src))>;
1724
1725// Cast to f32
1726def : Pat<(f32 (sint_to_fp i64:$src)), (CVTSDr (CVTDLr i64:$src))>;
1727
1728// Cast to f128
1729def : Pat<(f128 (sint_to_fp i32:$src)), (CVTQDr (CVTDWr $src))>;
1730def : Pat<(f128 (sint_to_fp i64:$src)), (CVTQDr (CVTDLr $src))>;
1731
1732def : Pat<(i64 (anyext i32:$sy)),
1733          (INSERT_SUBREG (i64 (IMPLICIT_DEF)), $sy, sub_i32)>;
1734
1735
1736// extload, sextload and zextload stuff
1737multiclass EXT64m<SDPatternOperator from,
1738                  RM torri,
1739                  RM torii,
1740                  RM tozri,
1741                  RM tozii> {
1742  def : Pat<(i64 (from ADDRrri:$addr)),
1743            (INSERT_SUBREG (i64 (IMPLICIT_DEF)), (torri MEMrri:$addr),
1744                           sub_i32)>;
1745  def : Pat<(i64 (from ADDRrii:$addr)),
1746            (INSERT_SUBREG (i64 (IMPLICIT_DEF)), (torii MEMrii:$addr),
1747                           sub_i32)>;
1748  def : Pat<(i64 (from ADDRzri:$addr)),
1749            (INSERT_SUBREG (i64 (IMPLICIT_DEF)), (tozri MEMzri:$addr),
1750                           sub_i32)>;
1751  def : Pat<(i64 (from ADDRzii:$addr)),
1752            (INSERT_SUBREG (i64 (IMPLICIT_DEF)), (tozii MEMzii:$addr),
1753                           sub_i32)>;
1754}
1755defm : EXT64m<sextloadi8, LD1BSXrri, LD1BSXrii, LD1BSXzri, LD1BSXzii>;
1756defm : EXT64m<zextloadi8, LD1BZXrri, LD1BZXrii, LD1BZXzri, LD1BZXzii>;
1757defm : EXT64m<extloadi8, LD1BZXrri, LD1BZXrii, LD1BZXzri, LD1BZXzii>;
1758defm : EXT64m<sextloadi16, LD2BSXrri, LD2BSXrii, LD2BSXzri, LD2BSXzii>;
1759defm : EXT64m<zextloadi16, LD2BZXrri, LD2BZXrii, LD2BZXzri, LD2BZXzii>;
1760defm : EXT64m<extloadi16, LD2BZXrri, LD2BZXrii, LD2BZXzri, LD2BZXzii>;
1761defm : EXT64m<sextloadi32, LDLSXrri, LDLSXrii, LDLSXzri, LDLSXzii>;
1762defm : EXT64m<zextloadi32, LDLZXrri, LDLZXrii, LDLZXzri, LDLZXzii>;
1763defm : EXT64m<extloadi32, LDLSXrri, LDLSXrii, LDLSXzri, LDLSXzii>;
1764
1765// anyextload
1766multiclass EXT32m<SDPatternOperator from,
1767                  RM torri,
1768                  RM torii,
1769                  RM tozri,
1770                  RM tozii> {
1771  def : Pat<(from ADDRrri:$addr), (torri MEMrri:$addr)>;
1772  def : Pat<(from ADDRrii:$addr), (torii MEMrii:$addr)>;
1773  def : Pat<(from ADDRzri:$addr), (tozri MEMzri:$addr)>;
1774  def : Pat<(from ADDRzii:$addr), (tozii MEMzii:$addr)>;
1775}
1776defm : EXT32m<extloadi8, LD1BZXrri, LD1BZXrii, LD1BZXzri, LD1BZXzii>;
1777defm : EXT32m<extloadi16, LD2BZXrri, LD2BZXrii, LD2BZXzri, LD2BZXzii>;
1778
1779// truncstore
1780multiclass TRUNC64m<SDPatternOperator from,
1781                    RM torri,
1782                    RM torii,
1783                    RM tozri,
1784                    RM tozii> {
1785  def : Pat<(from i64:$src, ADDRrri:$addr),
1786            (torri MEMrri:$addr, (EXTRACT_SUBREG $src, sub_i32))>;
1787  def : Pat<(from i64:$src, ADDRrii:$addr),
1788            (torii MEMrii:$addr, (EXTRACT_SUBREG $src, sub_i32))>;
1789  def : Pat<(from i64:$src, ADDRzri:$addr),
1790            (tozri MEMzri:$addr, (EXTRACT_SUBREG $src, sub_i32))>;
1791  def : Pat<(from i64:$src, ADDRzii:$addr),
1792            (tozii MEMzii:$addr, (EXTRACT_SUBREG $src, sub_i32))>;
1793}
1794defm : TRUNC64m<truncstorei8, ST1Brri, ST1Brii, ST1Bzri, ST1Bzii>;
1795defm : TRUNC64m<truncstorei16, ST2Brri, ST2Brii, ST2Bzri, ST2Bzii>;
1796defm : TRUNC64m<truncstorei32, STLrri, STLrii, STLzri, ST1Bzii>;
1797
1798// Atomic loads
1799multiclass ATMLDm<SDPatternOperator from,
1800                  RM torri, RM torii,
1801                  RM tozri, RM tozii> {
1802  def : Pat<(from ADDRrri:$addr), (torri MEMrri:$addr)>;
1803  def : Pat<(from ADDRrii:$addr), (torii MEMrii:$addr)>;
1804  def : Pat<(from ADDRzri:$addr), (tozri MEMzri:$addr)>;
1805  def : Pat<(from ADDRzii:$addr), (tozii MEMzii:$addr)>;
1806}
1807defm : ATMLDm<atomic_load_8, LD1BZXrri, LD1BZXrii, LD1BZXzri, LD1BZXzii>;
1808defm : ATMLDm<atomic_load_16, LD2BZXrri, LD2BZXrii, LD2BZXzri, LD2BZXzii>;
1809defm : ATMLDm<atomic_load_32, LDLZXrri, LDLZXrii, LDLZXzri, LDLZXzii>;
1810defm : ATMLDm<atomic_load_64, LDrri, LDrii, LDzri, LDzii>;
1811
1812// Optimized atomic loads with sext
1813multiclass SXATMLDm<SDPatternOperator from, ValueType TY,
1814                    RM torri, RM torii,
1815                    RM tozri, RM tozii> {
1816  def : Pat<(i64 (sext_inreg (i64 (anyext (from ADDRrri:$addr))), TY)),
1817            (i2l (torri MEMrri:$addr))>;
1818  def : Pat<(i64 (sext_inreg (i64 (anyext (from ADDRrii:$addr))), TY)),
1819            (i2l (torii MEMrii:$addr))>;
1820  def : Pat<(i64 (sext_inreg (i64 (anyext (from ADDRzri:$addr))), TY)),
1821            (i2l (tozri MEMzri:$addr))>;
1822  def : Pat<(i64 (sext_inreg (i64 (anyext (from ADDRzii:$addr))), TY)),
1823            (i2l (tozii MEMzii:$addr))>;
1824}
1825multiclass SXATMLD32m<SDPatternOperator from,
1826                      RM torri, RM torii,
1827                      RM tozri, RM tozii> {
1828  def : Pat<(i64 (sext (from ADDRrri:$addr))),
1829            (i2l (torri MEMrri:$addr))>;
1830  def : Pat<(i64 (sext (from ADDRrii:$addr))),
1831            (i2l (torii MEMrii:$addr))>;
1832  def : Pat<(i64 (sext (from ADDRzri:$addr))),
1833            (i2l (tozri MEMzri:$addr))>;
1834  def : Pat<(i64 (sext (from ADDRzii:$addr))),
1835            (i2l (tozii MEMzii:$addr))>;
1836}
1837defm : SXATMLDm<atomic_load_8, i8, LD1BSXrri, LD1BSXrii, LD1BSXzri, LD1BSXzii>;
1838defm : SXATMLDm<atomic_load_16, i16, LD2BSXrri, LD2BSXrii, LD2BSXzri,
1839                LD2BSXzii>;
1840defm : SXATMLD32m<atomic_load_32, LDLSXrri, LDLSXrii, LDLSXzri, LDLSXzii>;
1841
1842// Optimized atomic loads with zext
1843multiclass ZXATMLDm<SDPatternOperator from, int VAL,
1844                    RM torri, RM torii,
1845                    RM tozri, RM tozii> {
1846  def : Pat<(i64 (and (anyext (from ADDRrri:$addr)), VAL)),
1847            (i2l (torri MEMrri:$addr))>;
1848  def : Pat<(i64 (and (anyext (from ADDRrii:$addr)), VAL)),
1849            (i2l (torii MEMrii:$addr))>;
1850  def : Pat<(i64 (and (anyext (from ADDRzri:$addr)), VAL)),
1851            (i2l (tozri MEMzri:$addr))>;
1852  def : Pat<(i64 (and (anyext (from ADDRzii:$addr)), VAL)),
1853            (i2l (tozii MEMzii:$addr))>;
1854}
1855multiclass ZXATMLD32m<SDPatternOperator from,
1856                      RM torri, RM torii,
1857                      RM tozri, RM tozii> {
1858  def : Pat<(i64 (zext (from ADDRrri:$addr))),
1859            (i2l (torri MEMrri:$addr))>;
1860  def : Pat<(i64 (zext (from ADDRrii:$addr))),
1861            (i2l (torii MEMrii:$addr))>;
1862  def : Pat<(i64 (zext (from ADDRzri:$addr))),
1863            (i2l (tozri MEMzri:$addr))>;
1864  def : Pat<(i64 (zext (from ADDRzii:$addr))),
1865            (i2l (tozii MEMzii:$addr))>;
1866}
1867defm : ZXATMLDm<atomic_load_8, 0xFF, LD1BZXrri, LD1BZXrii, LD1BZXzri,
1868                LD1BZXzii>;
1869defm : ZXATMLDm<atomic_load_16, 0xFFFF, LD2BZXrri, LD2BZXrii, LD2BZXzri,
1870                LD2BZXzii>;
1871defm : ZXATMLD32m<atomic_load_32, LDLZXrri, LDLZXrii, LDLZXzri, LDLZXzii>;
1872
1873// Atomic stores
1874multiclass ATMSTm<SDPatternOperator from, ValueType ty,
1875                  RM torri, RM torii,
1876                  RM tozri, RM tozii> {
1877  def : Pat<(from ADDRrri:$addr, ty:$src), (torri MEMrri:$addr, $src)>;
1878  def : Pat<(from ADDRrii:$addr, ty:$src), (torii MEMrii:$addr, $src)>;
1879  def : Pat<(from ADDRzri:$addr, ty:$src), (tozri MEMzri:$addr, $src)>;
1880  def : Pat<(from ADDRzii:$addr, ty:$src), (tozii MEMzii:$addr, $src)>;
1881}
1882defm : ATMSTm<atomic_store_8, i32, ST1Brri, ST1Brii, ST1Bzri, ST1Bzii>;
1883defm : ATMSTm<atomic_store_16, i32, ST2Brri, ST2Brii, ST2Bzri, ST2Bzii>;
1884defm : ATMSTm<atomic_store_32, i32, STLrri, STLrii, STLzri, STLzii>;
1885defm : ATMSTm<atomic_store_64, i64, STrri, STrii, STzri, STzii>;
1886
1887// Optimized atomic stores with truncate
1888multiclass TRATMSTm<SDPatternOperator from,
1889                  RM torri,
1890                  RM torii,
1891                  RM tozri,
1892                  RM tozii> {
1893  def : Pat<(from ADDRrri:$addr, (i32 (trunc i64:$src))),
1894            (torri MEMrri:$addr, (EXTRACT_SUBREG $src, sub_i32))>;
1895  def : Pat<(from ADDRrii:$addr, (i32 (trunc i64:$src))),
1896            (torii MEMrii:$addr, (EXTRACT_SUBREG $src, sub_i32))>;
1897  def : Pat<(from ADDRzri:$addr, (i32 (trunc i64:$src))),
1898            (tozri MEMzri:$addr, (EXTRACT_SUBREG $src, sub_i32))>;
1899  def : Pat<(from ADDRzii:$addr, (i32 (trunc i64:$src))),
1900            (tozii MEMzii:$addr, (EXTRACT_SUBREG $src, sub_i32))>;
1901}
1902defm : TRATMSTm<atomic_store_8, ST1Brri, ST1Brii, ST1Bzri, ST1Bzii>;
1903defm : TRATMSTm<atomic_store_16, ST2Brri, ST2Brii, ST2Bzri, ST2Bzii>;
1904defm : TRATMSTm<atomic_store_32, STLrri, STLrii, STLzri, STLzii>;
1905
1906// Atomic swaps
1907def : Pat<(i32 (ts1am i64:$src, i32:$flag, i32:$new)),
1908          (TS1AMWrir $src, 0, $flag, $new)>;
1909def : Pat<(i32 (atomic_swap_32 ADDRri:$src, i32:$new)),
1910          (TS1AMWrii MEMriRRM:$src, 15, $new)>;
1911def : Pat<(i64 (atomic_swap_64 ADDRri:$src, i64:$new)),
1912          (TS1AMLrir MEMriRRM:$src, (LEAzii 0, 0, 255), i64:$new)>;
1913
1914//===----------------------------------------------------------------------===//
1915// SJLJ Exception handling patterns
1916//===----------------------------------------------------------------------===//
1917
1918let hasSideEffects = 1, isBarrier = 1, isCodeGenOnly = 1,
1919    usesCustomInserter = 1 in {
1920  let isTerminator = 1 in
1921  def EH_SjLj_LongJmp : Pseudo<(outs), (ins I64:$buf),
1922                               "# EH_SJLJ_LONGJMP",
1923                               [(VEeh_sjlj_longjmp I64:$buf)]>;
1924
1925  def EH_SjLj_SetJmp  : Pseudo<(outs I32:$dst), (ins I64:$buf),
1926                               "# EH_SJLJ_SETJMP",
1927                               [(set I32:$dst, (VEeh_sjlj_setjmp I64:$buf))]>;
1928
1929  def EH_SjLj_Setup_Dispatch : Pseudo<(outs), (ins), "# EH_SJLJ_SETUP_DISPATCH",
1930                                      [(VEeh_sjlj_setup_dispatch)]>;
1931}
1932
1933let isTerminator = 1, isBranch = 1, isCodeGenOnly = 1 in
1934  def EH_SjLj_Setup : Pseudo<(outs), (ins brtarget32:$dst),
1935                             "# EH_SJlJ_SETUP $dst">;
1936
1937//===----------------------------------------------------------------------===//
1938// Branch related patterns
1939//===----------------------------------------------------------------------===//
1940
1941// Branches
1942def : Pat<(br bb:$addr), (BRCFLa bb:$addr)>;
1943
1944// brcc
1945// integer brcc
1946multiclass BRCCIm<ValueType ty, CF BrOpNode1,
1947                 CF BrOpNode2,
1948                 RR CmpOpNode1,
1949                 RR CmpOpNode2> {
1950  def : Pat<(brcc CCSIOp:$cond, ty:$l, simm7:$r, bb:$addr),
1951            (BrOpNode2 (icond2ccSwap $cond), (LO7 $r), $l, bb:$addr)>;
1952  def : Pat<(brcc CCSIOp:$cond, ty:$l, ty:$r, bb:$addr),
1953            (BrOpNode1 (icond2cc $cond), $l, $r, bb:$addr)>;
1954  def : Pat<(brcc CCUIOp:$cond, ty:$l, simm7:$r, bb:$addr),
1955            (BrOpNode2 (icond2cc $cond), 0, (CmpOpNode2 (LO7 $r), $l),
1956                       bb:$addr)>;
1957  def : Pat<(brcc CCUIOp:$cond, ty:$l, ty:$r, bb:$addr),
1958            (BrOpNode2 (icond2cc $cond), 0, (CmpOpNode1 $r, $l), bb:$addr)>;
1959}
1960defm : BRCCIm<i32, BRCFWrr, BRCFWir, CMPUWrr, CMPUWir>;
1961defm : BRCCIm<i64, BRCFLrr, BRCFLir, CMPULrr, CMPULir>;
1962
1963// floating point brcc
1964multiclass BRCCFm<ValueType ty, CF BrOpNode1, CF BrOpNode2> {
1965  def : Pat<(brcc cond:$cond, ty:$l, simm7fp:$r, bb:$addr),
1966            (BrOpNode2 (fcond2ccSwap $cond), (LO7FP $r), $l, bb:$addr)>;
1967  def : Pat<(brcc cond:$cond, ty:$l, ty:$r, bb:$addr),
1968            (BrOpNode1 (fcond2cc $cond), $l, $r, bb:$addr)>;
1969}
1970defm : BRCCFm<f32, BRCFSrr, BRCFSir>;
1971defm : BRCCFm<f64, BRCFDrr, BRCFDir>;
1972def : Pat<(brcc cond:$cond, f128:$l, f128:$r, bb:$addr),
1973          (BRCFDir (fcond2cc $cond), 0, (FCMPQrr $r, $l), bb:$addr)>;
1974
1975//===----------------------------------------------------------------------===//
1976// Pseudo Instructions
1977//===----------------------------------------------------------------------===//
1978
1979// GETGOT for PIC
1980let Defs = [SX15 /* %got */, SX16 /* %plt */], hasSideEffects = 0 in {
1981  def GETGOT : Pseudo<(outs getGOT:$getpcseq), (ins), "$getpcseq">;
1982}
1983
1984// GETFUNPLT for PIC
1985let hasSideEffects = 0 in
1986def GETFUNPLT : Pseudo<(outs I64:$dst), (ins i64imm:$addr),
1987                       "$dst, $addr",
1988                       [(set iPTR:$dst, (GetFunPLT tglobaladdr:$addr))] >;
1989
1990def : Pat<(GetFunPLT tglobaladdr:$dst),
1991          (GETFUNPLT tglobaladdr:$dst)>;
1992def : Pat<(GetFunPLT texternalsym:$dst),
1993          (GETFUNPLT texternalsym:$dst)>;
1994
1995// GETTLSADDR for TLS
1996let Defs = [SX0, SX10, SX12], hasSideEffects = 0 in
1997def GETTLSADDR : Pseudo<(outs), (ins i64imm:$addr),
1998                        "# GETTLSADDR $addr",
1999                        [(GetTLSAddr tglobaltlsaddr:$addr)] >;
2000
2001def : Pat<(GetTLSAddr tglobaltlsaddr:$dst),
2002          (GETTLSADDR tglobaltlsaddr:$dst)>;
2003
2004let Defs = [SX11], Uses = [SX11], hasSideEffects = 0 in {
2005def ADJCALLSTACKDOWN : Pseudo<(outs), (ins i64imm:$amt, i64imm:$amt2),
2006                              "# ADJCALLSTACKDOWN $amt, $amt2",
2007                              [(callseq_start timm:$amt, timm:$amt2)]>;
2008def ADJCALLSTACKUP : Pseudo<(outs), (ins i64imm:$amt1, i64imm:$amt2),
2009                            "# ADJCALLSTACKUP $amt1",
2010                            [(callseq_end timm:$amt1, timm:$amt2)]>;
2011}
2012
2013let Defs = [SX8], Uses = [SX8, SX11], hasSideEffects = 0 in
2014def EXTEND_STACK : Pseudo<(outs), (ins),
2015                          "# EXTEND STACK",
2016                          []>;
2017let  hasSideEffects = 0 in
2018def EXTEND_STACK_GUARD : Pseudo<(outs), (ins),
2019                                "# EXTEND STACK GUARD",
2020                                []>;
2021
2022// Dynamic stack allocation yields a __llvm_grow_stack for VE targets.
2023// These calls are needed to probe the stack when allocating more over
2024// %s8 (%sl - stack limit).
2025
2026let Uses = [SX11], hasSideEffects = 1 in
2027def GETSTACKTOP : Pseudo<(outs I64:$dst), (ins),
2028                         "# GET STACK TOP",
2029                         [(set iPTR:$dst, (GetStackTop))]>;
2030
2031// MEMBARRIER
2032let hasSideEffects = 1 in
2033def MEMBARRIER : Pseudo<(outs), (ins), "# MEMBARRIER", [(MemBarrier)] >;
2034
2035//===----------------------------------------------------------------------===//
2036// Other patterns
2037//===----------------------------------------------------------------------===//
2038
2039// SETCC pattern matches
2040//
2041//   CMP  %tmp, lhs, rhs     ; compare lhs and rhs
2042//   or   %res, 0, (0)1      ; initialize by 0
2043//   CMOV %res, (63)0, %tmp  ; set 1 if %tmp is true
2044
2045class setccrr<Instruction INSN> :
2046    OutPatFrag<(ops node:$cond, node:$comp),
2047               (EXTRACT_SUBREG
2048                   (INSN $cond, $comp,
2049                         !add(63, 64), // means (63)0 == 1
2050                         (ORim 0, 0)), sub_i32)>;
2051
2052def : Pat<(i32 (setcc i32:$l, i32:$r, CCSIOp:$cond)),
2053          (setccrr<CMOVWrm> (icond2cc $cond), (CMPSWSXrr $l, $r))>;
2054def : Pat<(i32 (setcc i32:$l, i32:$r, CCUIOp:$cond)),
2055          (setccrr<CMOVWrm> (icond2cc $cond), (CMPUWrr $l, $r))>;
2056def : Pat<(i32 (setcc i64:$l, i64:$r, CCSIOp:$cond)),
2057          (setccrr<CMOVLrm> (icond2cc $cond), (CMPSLrr $l, $r))>;
2058def : Pat<(i32 (setcc i64:$l, i64:$r, CCUIOp:$cond)),
2059          (setccrr<CMOVLrm> (icond2cc $cond), (CMPULrr $l, $r))>;
2060def : Pat<(i32 (setcc f32:$l, f32:$r, cond:$cond)),
2061          (setccrr<CMOVSrm> (fcond2cc $cond), (FCMPSrr $l, $r))>;
2062def : Pat<(i32 (setcc f64:$l, f64:$r, cond:$cond)),
2063          (setccrr<CMOVDrm> (fcond2cc $cond), (FCMPDrr $l, $r))>;
2064def : Pat<(i32 (setcc f128:$l, f128:$r, cond:$cond)),
2065          (setccrr<CMOVDrm> (fcond2cc $cond), (FCMPQrr $l, $r))>;
2066
2067// Special SELECTCC pattern matches
2068// Use min/max for better performance.
2069//
2070//   MAX/MIN  %res, %lhs, %rhs
2071
2072def : Pat<(f64 (selectcc f64:$LHS, f64:$RHS, f64:$LHS, f64:$RHS, SETOGT)),
2073          (FMAXDrr $LHS, $RHS)>;
2074def : Pat<(f32 (selectcc f32:$LHS, f32:$RHS, f32:$LHS, f32:$RHS, SETOGT)),
2075          (FMAXSrr $LHS, $RHS)>;
2076def : Pat<(i64 (selectcc i64:$LHS, i64:$RHS, i64:$LHS, i64:$RHS, SETGT)),
2077          (MAXSLrr $LHS, $RHS)>;
2078def : Pat<(i32 (selectcc i32:$LHS, i32:$RHS, i32:$LHS, i32:$RHS, SETGT)),
2079          (MAXSWSXrr $LHS, $RHS)>;
2080def : Pat<(f64 (selectcc f64:$LHS, f64:$RHS, f64:$LHS, f64:$RHS, SETOGE)),
2081          (FMAXDrr $LHS, $RHS)>;
2082def : Pat<(f32 (selectcc f32:$LHS, f32:$RHS, f32:$LHS, f32:$RHS, SETOGE)),
2083          (FMAXSrr $LHS, $RHS)>;
2084def : Pat<(i64 (selectcc i64:$LHS, i64:$RHS, i64:$LHS, i64:$RHS, SETGE)),
2085          (MAXSLrr $LHS, $RHS)>;
2086def : Pat<(i32 (selectcc i32:$LHS, i32:$RHS, i32:$LHS, i32:$RHS, SETGE)),
2087          (MAXSWSXrr $LHS, $RHS)>;
2088
2089def : Pat<(f64 (selectcc f64:$LHS, f64:$RHS, f64:$LHS, f64:$RHS, SETOLT)),
2090          (FMINDrr $LHS, $RHS)>;
2091def : Pat<(f32 (selectcc f32:$LHS, f32:$RHS, f32:$LHS, f32:$RHS, SETOLT)),
2092          (FMINSrr $LHS, $RHS)>;
2093def : Pat<(i64 (selectcc i64:$LHS, i64:$RHS, i64:$LHS, i64:$RHS, SETLT)),
2094          (MINSLrr $LHS, $RHS)>;
2095def : Pat<(i32 (selectcc i32:$LHS, i32:$RHS, i32:$LHS, i32:$RHS, SETLT)),
2096          (MINSWSXrr $LHS, $RHS)>;
2097def : Pat<(f64 (selectcc f64:$LHS, f64:$RHS, f64:$LHS, f64:$RHS, SETOLE)),
2098          (FMINDrr $LHS, $RHS)>;
2099def : Pat<(f32 (selectcc f32:$LHS, f32:$RHS, f32:$LHS, f32:$RHS, SETOLE)),
2100          (FMINSrr $LHS, $RHS)>;
2101def : Pat<(i64 (selectcc i64:$LHS, i64:$RHS, i64:$LHS, i64:$RHS, SETLE)),
2102          (MINSLrr $LHS, $RHS)>;
2103def : Pat<(i32 (selectcc i32:$LHS, i32:$RHS, i32:$LHS, i32:$RHS, SETLE)),
2104          (MINSWSXrr $LHS, $RHS)>;
2105
2106// Helper classes to construct cmov patterns for the ease.
2107//
2108//   Hiding INSERT_SUBREG/EXTRACT_SUBREG patterns.
2109
2110class cmovrr<Instruction INSN> :
2111    OutPatFrag<(ops node:$cond, node:$comp, node:$t, node:$f),
2112               (INSN $cond, $comp, $t, $f)>;
2113class cmovrm<Instruction INSN, SDNodeXForm MOP = MIMM> :
2114    OutPatFrag<(ops node:$cond, node:$comp, node:$t, node:$f),
2115               (INSN $cond, $comp, (MOP $t), $f)>;
2116class cmov32rr<Instruction INSN, SubRegIndex sub_oty> :
2117    OutPatFrag<(ops node:$cond, node:$comp, node:$t, node:$f),
2118               (EXTRACT_SUBREG
2119                   (INSN $cond, $comp,
2120                         (INSERT_SUBREG (i64 (IMPLICIT_DEF)), $t, sub_oty),
2121                         (INSERT_SUBREG (i64 (IMPLICIT_DEF)), $f, sub_oty)),
2122                   sub_oty)>;
2123class cmov32rm<Instruction INSN, SubRegIndex sub_oty, SDNodeXForm MOP = MIMM> :
2124    OutPatFrag<(ops node:$cond, node:$comp, node:$t, node:$f),
2125               (EXTRACT_SUBREG
2126                   (INSN $cond, $comp,
2127                         (MOP $t),
2128                         (INSERT_SUBREG (i64 (IMPLICIT_DEF)), $f, sub_oty)),
2129                   sub_oty)>;
2130class cmov128rr<Instruction INSN> :
2131    OutPatFrag<(ops node:$cond, node:$comp, node:$t, node:$f),
2132               (INSERT_SUBREG
2133                 (INSERT_SUBREG (f128 (IMPLICIT_DEF)),
2134                   (INSN $cond, $comp,
2135                       (EXTRACT_SUBREG $t, sub_odd),
2136                       (EXTRACT_SUBREG $f, sub_odd)), sub_odd),
2137                 (INSN $cond, $comp,
2138                     (EXTRACT_SUBREG $t, sub_even),
2139                     (EXTRACT_SUBREG $f, sub_even)), sub_even)>;
2140
2141// Generic SELECTCC pattern matches
2142//
2143//   CMP  %tmp, %l, %r       ; compare %l and %r
2144//   or   %res, %f, (0)1     ; initialize by %f
2145//   CMOV %res, %t, %tmp     ; set %t if %tmp is true
2146
2147def : Pat<(i32 (selectcc i32:$l, i32:$r, i32:$t, i32:$f, CCSIOp:$cond)),
2148          (cmov32rr<CMOVWrr, sub_i32> (icond2cc $cond), (CMPSWSXrr $l, $r),
2149                                      $t, $f)>;
2150def : Pat<(i32 (selectcc i32:$l, i32:$r, i32:$t, i32:$f, CCUIOp:$cond)),
2151          (cmov32rr<CMOVWrr, sub_i32> (icond2cc $cond), (CMPUWrr $l, $r),
2152                                      $t, $f)>;
2153def : Pat<(i32 (selectcc i64:$l, i64:$r, i32:$t, i32:$f, CCSIOp:$cond)),
2154          (cmov32rr<CMOVLrr, sub_i32> (icond2cc $cond), (CMPSLrr $l, $r),
2155                                      $t, $f)>;
2156def : Pat<(i32 (selectcc i64:$l, i64:$r, i32:$t, i32:$f, CCUIOp:$cond)),
2157          (cmov32rr<CMOVLrr, sub_i32> (icond2cc $cond), (CMPULrr $l, $r),
2158                                      $t, $f)>;
2159def : Pat<(i32 (selectcc f32:$l, f32:$r, i32:$t, i32:$f, cond:$cond)),
2160          (cmov32rr<CMOVSrr, sub_i32> (fcond2cc $cond), (FCMPSrr $l, $r),
2161                                      $t, $f)>;
2162def : Pat<(i32 (selectcc f64:$l, f64:$r, i32:$t, i32:$f, cond:$cond)),
2163          (cmov32rr<CMOVDrr, sub_i32> (fcond2cc $cond), (FCMPDrr $l, $r),
2164                                      $t, $f)>;
2165def : Pat<(i32 (selectcc f128:$l, f128:$r, i32:$t, i32:$f, cond:$cond)),
2166          (cmov32rr<CMOVDrr, sub_i32> (fcond2cc $cond), (FCMPQrr $l, $r),
2167                                      $t, $f)>;
2168
2169def : Pat<(i64 (selectcc i32:$l, i32:$r, i64:$t, i64:$f, CCSIOp:$cond)),
2170          (cmovrr<CMOVWrr> (icond2cc $cond), (CMPSWSXrr $l, $r), $t, $f)>;
2171def : Pat<(i64 (selectcc i32:$l, i32:$r, i64:$t, i64:$f, CCUIOp:$cond)),
2172          (cmovrr<CMOVWrr> (icond2cc $cond), (CMPUWrr $l, $r), $t, $f)>;
2173def : Pat<(i64 (selectcc i64:$l, i64:$r, i64:$t, i64:$f, CCSIOp:$cond)),
2174          (cmovrr<CMOVLrr> (icond2cc $cond), (CMPSLrr $l, $r), $t, $f)>;
2175def : Pat<(i64 (selectcc i64:$l, i64:$r, i64:$t, i64:$f, CCUIOp:$cond)),
2176          (cmovrr<CMOVLrr> (icond2cc $cond), (CMPULrr $l, $r), $t, $f)>;
2177def : Pat<(i64 (selectcc f32:$l, f32:$r, i64:$t, i64:$f, cond:$cond)),
2178          (cmovrr<CMOVSrr> (fcond2cc $cond), (FCMPSrr $l, $r), $t, $f)>;
2179def : Pat<(i64 (selectcc f64:$l, f64:$r, i64:$t, i64:$f, cond:$cond)),
2180          (cmovrr<CMOVDrr> (fcond2cc $cond), (FCMPDrr $l, $r), $t, $f)>;
2181def : Pat<(i64 (selectcc f128:$l, f128:$r, i64:$t, i64:$f, cond:$cond)),
2182          (cmovrr<CMOVDrr> (fcond2cc $cond), (FCMPQrr $l, $r), $t, $f)>;
2183
2184def : Pat<(f32 (selectcc i32:$l, i32:$r, f32:$t, f32:$f, CCSIOp:$cond)),
2185          (cmov32rr<CMOVWrr, sub_f32> (icond2cc $cond), (CMPSWSXrr $l, $r),
2186                                      $t, $f)>;
2187def : Pat<(f32 (selectcc i32:$l, i32:$r, f32:$t, f32:$f, CCUIOp:$cond)),
2188          (cmov32rr<CMOVWrr, sub_f32> (icond2cc $cond), (CMPUWrr $l, $r),
2189                                      $t, $f)>;
2190def : Pat<(f32 (selectcc i64:$l, i64:$r, f32:$t, f32:$f, CCSIOp:$cond)),
2191          (cmov32rr<CMOVLrr, sub_f32> (icond2cc $cond), (CMPSLrr $l, $r),
2192                                      $t, $f)>;
2193def : Pat<(f32 (selectcc i64:$l, i64:$r, f32:$t, f32:$f, CCUIOp:$cond)),
2194          (cmov32rr<CMOVLrr, sub_f32> (icond2cc $cond), (CMPULrr $l, $r),
2195                                      $t, $f)>;
2196def : Pat<(f32 (selectcc f32:$l, f32:$r, f32:$t, f32:$f, cond:$cond)),
2197          (cmov32rr<CMOVSrr, sub_f32> (fcond2cc $cond), (FCMPSrr $l, $r),
2198                                      $t, $f)>;
2199def : Pat<(f32 (selectcc f64:$l, f64:$r, f32:$t, f32:$f, cond:$cond)),
2200          (cmov32rr<CMOVDrr, sub_f32> (fcond2cc $cond), (FCMPDrr $l, $r),
2201                                      $t, $f)>;
2202def : Pat<(f32 (selectcc f128:$l, f128:$r, f32:$t, f32:$f, cond:$cond)),
2203          (cmov32rr<CMOVDrr, sub_f32> (fcond2cc $cond), (FCMPQrr $l, $r),
2204                                      $t, $f)>;
2205
2206def : Pat<(f64 (selectcc i32:$l, i32:$r, f64:$t, f64:$f, CCSIOp:$cond)),
2207          (cmovrr<CMOVWrr> (icond2cc $cond), (CMPSWSXrr $l, $r), $t, $f)>;
2208def : Pat<(f64 (selectcc i32:$l, i32:$r, f64:$t, f64:$f, CCUIOp:$cond)),
2209          (cmovrr<CMOVWrr> (icond2cc $cond), (CMPUWrr $l, $r), $t, $f)>;
2210def : Pat<(f64 (selectcc i64:$l, i64:$r, f64:$t, f64:$f, CCSIOp:$cond)),
2211          (cmovrr<CMOVLrr> (icond2cc $cond), (CMPSLrr $l, $r), $t, $f)>;
2212def : Pat<(f64 (selectcc i64:$l, i64:$r, f64:$t, f64:$f, CCUIOp:$cond)),
2213          (cmovrr<CMOVLrr> (icond2cc $cond), (CMPULrr $l, $r), $t, $f)>;
2214def : Pat<(f64 (selectcc f32:$l, f32:$r, f64:$t, f64:$f, cond:$cond)),
2215          (cmovrr<CMOVSrr> (fcond2cc $cond), (FCMPSrr $l, $r), $t, $f)>;
2216def : Pat<(f64 (selectcc f64:$l, f64:$r, f64:$t, f64:$f, cond:$cond)),
2217          (cmovrr<CMOVDrr> (fcond2cc $cond), (FCMPDrr $l, $r), $t, $f)>;
2218def : Pat<(f64 (selectcc f128:$l, f128:$r, f64:$t, f64:$f, cond:$cond)),
2219          (cmovrr<CMOVDrr> (fcond2cc $cond), (FCMPQrr $l, $r), $t, $f)>;
2220
2221def : Pat<(f128 (selectcc i32:$l, i32:$r, f128:$t, f128:$f, CCSIOp:$cond)),
2222          (cmov128rr<CMOVWrr> (icond2cc $cond), (CMPSWSXrr $l, $r), $t, $f)>;
2223def : Pat<(f128 (selectcc i32:$l, i32:$r, f128:$t, f128:$f, CCUIOp:$cond)),
2224          (cmov128rr<CMOVWrr> (icond2cc $cond), (CMPUWrr $l, $r), $t, $f)>;
2225def : Pat<(f128 (selectcc i64:$l, i64:$r, f128:$t, f128:$f, CCSIOp:$cond)),
2226          (cmov128rr<CMOVLrr> (icond2cc $cond), (CMPSLrr $l, $r), $t, $f)>;
2227def : Pat<(f128 (selectcc i64:$l, i64:$r, f128:$t, f128:$f, CCUIOp:$cond)),
2228          (cmov128rr<CMOVLrr> (icond2cc $cond), (CMPULrr $l, $r), $t, $f)>;
2229def : Pat<(f128 (selectcc f32:$l, f32:$r, f128:$t, f128:$f, cond:$cond)),
2230          (cmov128rr<CMOVSrr> (fcond2cc $cond), (FCMPSrr $l, $r), $t, $f)>;
2231def : Pat<(f128 (selectcc f64:$l, f64:$r, f128:$t, f128:$f, cond:$cond)),
2232          (cmov128rr<CMOVDrr> (fcond2cc $cond), (FCMPDrr $l, $r), $t, $f)>;
2233def : Pat<(f128 (selectcc f128:$l, f128:$r, f128:$t, f128:$f, cond:$cond)),
2234          (cmov128rr<CMOVDrr> (fcond2cc $cond), (FCMPQrr $l, $r), $t, $f)>;
2235
2236// Generic SELECT pattern matches
2237// Use cmov.w for all cases since %pred holds i32.
2238//
2239//   CMOV.w.ne %res, %tval, %tmp  ; set tval if %tmp is true
2240
2241def : Pat<(i32 (select i32:$pred, i32:$t, i32:$f)),
2242          (cmov32rr<CMOVWrr, sub_i32> CC_INE, $pred, $t, $f)>;
2243def : Pat<(i32 (select i32:$pred, (i32 mimm:$t), i32:$f)),
2244          (cmov32rm<CMOVWrm, sub_i32> CC_INE, $pred, $t, $f)>;
2245def : Pat<(i32 (select i32:$pred, i32:$t, (i32 mimm:$f))),
2246          (cmov32rm<CMOVWrm, sub_i32> CC_IEQ, $pred, $f, $t)>;
2247
2248def : Pat<(i64 (select i32:$pred, i64:$t, i64:$f)),
2249          (cmovrr<CMOVWrr> CC_INE, $pred, $t, $f)>;
2250def : Pat<(i64 (select i32:$pred, (i64 mimm:$t), i64:$f)),
2251          (cmovrm<CMOVWrm, MIMM> CC_INE, $pred, $t, $f)>;
2252def : Pat<(i64 (select i32:$pred, i64:$t, (i64 mimm:$f))),
2253          (cmovrm<CMOVWrm, MIMM> CC_IEQ, $pred, $f, $t)>;
2254
2255def : Pat<(f32 (select i32:$pred, f32:$t, f32:$f)),
2256          (cmov32rr<CMOVWrr, sub_f32> CC_INE, $pred, $t, $f)>;
2257def : Pat<(f32 (select i32:$pred, (f32 mimmfp:$t), f32:$f)),
2258          (cmov32rm<CMOVWrm, sub_f32, MIMMFP> CC_INE, $pred, $t, $f)>;
2259def : Pat<(f32 (select i32:$pred, f32:$t, (f32 mimmfp:$f))),
2260          (cmov32rm<CMOVWrm, sub_f32, MIMMFP> CC_IEQ, $pred, $f, $t)>;
2261
2262def : Pat<(f64 (select i32:$pred, f64:$t, f64:$f)),
2263          (cmovrr<CMOVWrr> CC_INE, $pred, $t, $f)>;
2264def : Pat<(f64 (select i32:$pred, (f64 mimmfp:$t), f64:$f)),
2265          (cmovrm<CMOVWrm, MIMMFP> CC_INE, $pred, $t, $f)>;
2266def : Pat<(f64 (select i32:$pred, f64:$t, (f64 mimmfp:$f))),
2267          (cmovrm<CMOVWrm, MIMMFP> CC_IEQ, $pred, $f, $t)>;
2268
2269def : Pat<(f128 (select i32:$pred, f128:$t, f128:$f)),
2270          (cmov128rr<CMOVWrr> CC_INE, $pred, $t, $f)>;
2271
2272// bitconvert
2273def : Pat<(f64 (bitconvert i64:$src)), (COPY_TO_REGCLASS $src, I64)>;
2274def : Pat<(i64 (bitconvert f64:$src)), (COPY_TO_REGCLASS $src, I64)>;
2275
2276def : Pat<(i32 (bitconvert f32:$op)),
2277          (EXTRACT_SUBREG (SRALri (INSERT_SUBREG (i64 (IMPLICIT_DEF)),
2278            $op, sub_f32), 32), sub_i32)>;
2279def : Pat<(f32 (bitconvert i32:$op)),
2280          (EXTRACT_SUBREG (SLLri (INSERT_SUBREG (i64 (IMPLICIT_DEF)),
2281            $op, sub_i32), 32), sub_f32)>;
2282
2283// Optimize code A generated by `(unsigned char)c << 5` to B.
2284// A) sla.w.sx %s0, %s0, 5
2285//    lea %s1, 224           ; 0xE0
2286//    and %s0, %s0, %s1
2287// B) sla.w.sx %s0, %s0, 5
2288//    and %s0, %s0, (56)0
2289
2290def : Pat<(i32 (and i32:$val, 0xff)),
2291          (EXTRACT_SUBREG
2292              (ANDrm (INSERT_SUBREG (i64 (IMPLICIT_DEF)), $val, sub_i32),
2293                     !add(56, 64)), sub_i32)>;
2294def : Pat<(i32 (and i32:$val, 0xffff)),
2295          (EXTRACT_SUBREG
2296              (ANDrm (INSERT_SUBREG (i64 (IMPLICIT_DEF)), $val, sub_i32),
2297                     !add(48, 64)), sub_i32)>;
2298def : Pat<(i64 (and i64:$val, 0xffffffff)),
2299          (ANDrm $val, !add(32, 64))>;
2300
2301//===----------------------------------------------------------------------===//
2302// Vector Instruction Pattern Stuff
2303//===----------------------------------------------------------------------===//
2304
2305// Custom intermediate ISDs.
2306class IsVLVT<int OpIdx> : SDTCisVT<OpIdx,i32>;
2307def vec_broadcast       : SDNode<"VEISD::VEC_BROADCAST", SDTypeProfile<1, 2,
2308                                 [SDTCisVec<0>, IsVLVT<2>]>>;
2309
2310///// Packed mode Support /////
2311// unpack the lo part of this vector
2312def vec_unpack_lo   : SDNode<"VEISD::VEC_UNPACK_LO", SDTypeProfile<1, 2,
2313                             [SDTCisVec<0>, SDTCisVec<1>, IsVLVT<2>]>>;
2314// unpack the hipart of this vector
2315def vec_unpack_hi   : SDNode<"VEISD::VEC_UNPACK_HI", SDTypeProfile<1, 2,
2316                             [SDTCisVec<0>, SDTCisVec<1>, IsVLVT<2>]>>;
2317// re-pack v256i32, v256f32 back into tone v512.32
2318def vec_pack        : SDNode<"VEISD::VEC_PACK", SDTypeProfile<1, 3,
2319                             [SDTCisVec<0>, SDTCisVec<1>, SDTCisVec<2>,
2320                              SDTCisSameNumEltsAs<1,2>, IsVLVT<3>]>>;
2321
2322// replicate lower 32bit to upper 32bit (f32 scalar replication).
2323def repl_f32            : SDNode<"VEISD::REPL_F32",
2324                            SDTypeProfile<1, 1,
2325                              [SDTCisInt<0>, SDTCisFP<1>]>>;
2326// replicate upper 32bit to lower 32 bit (i32 scalar replication).
2327def repl_i32            : SDNode<"VEISD::REPL_I32",
2328                            SDTypeProfile<1, 1,
2329                              [SDTCisInt<0>, SDTCisInt<1>]>>;
2330
2331
2332// Whether this is an all-true mask (assuming undef-bits above VL are all-true).
2333def true_mask           : PatLeaf<
2334                            (vec_broadcast (i32 nonzero), (i32 srcvalue))>;
2335// Match any broadcast (ignoring VL).
2336def any_broadcast       : PatFrag<(ops node:$sx),
2337                                  (vec_broadcast node:$sx, (i32 srcvalue))>;
2338
2339// Vector instructions.
2340include "VEInstrVec.td"
2341
2342// The vevlintrin
2343include "VEInstrIntrinsicVL.td"
2344
2345// Patterns and intermediate SD nodes (VEC_*).
2346include "VEInstrPatternsVec.td"
2347
2348// Patterns and intermediate SD nodes (VVP_*).
2349include "VVPInstrPatternsVec.td"
2350