blob: 2dc39ebaf460f2ac8ca1eb88194341993e0e53b6 [file] [log] [blame]
Dan Gohmanf17a25c2007-07-18 16:29:46 +00001//===- AlphaInstrInfo.td - The Alpha Instruction Set -------*- tablegen -*-===//
2//
3// The LLVM Compiler Infrastructure
4//
Chris Lattner081ce942007-12-29 20:36:04 +00005// This file is distributed under the University of Illinois Open Source
6// License. See LICENSE.TXT for details.
Dan Gohmanf17a25c2007-07-18 16:29:46 +00007//
8//===----------------------------------------------------------------------===//
9//
10//
11//===----------------------------------------------------------------------===//
12
13include "AlphaInstrFormats.td"
14
15//********************
16//Custom DAG Nodes
17//********************
18
19def SDTFPUnaryOpUnC : SDTypeProfile<1, 1, [
20 SDTCisFP<1>, SDTCisFP<0>
21]>;
22def Alpha_cvtqt : SDNode<"AlphaISD::CVTQT_", SDTFPUnaryOpUnC, []>;
23def Alpha_cvtqs : SDNode<"AlphaISD::CVTQS_", SDTFPUnaryOpUnC, []>;
24def Alpha_cvttq : SDNode<"AlphaISD::CVTTQ_" , SDTFPUnaryOp, []>;
25def Alpha_gprello : SDNode<"AlphaISD::GPRelLo", SDTIntBinOp, []>;
26def Alpha_gprelhi : SDNode<"AlphaISD::GPRelHi", SDTIntBinOp, []>;
Chris Lattnerca4e0fe2008-01-10 05:12:37 +000027def Alpha_rellit : SDNode<"AlphaISD::RelLit", SDTIntBinOp, [SDNPMayLoad]>;
Dan Gohmanf17a25c2007-07-18 16:29:46 +000028
Chris Lattner3d254552008-01-15 22:02:54 +000029def retflag : SDNode<"AlphaISD::RET_FLAG", SDTNone,
Bill Wendling6c02cd22008-02-27 06:33:05 +000030 [SDNPHasChain, SDNPOptInFlag]>;
Dan Gohmanf17a25c2007-07-18 16:29:46 +000031
32// These are target-independent nodes, but have target-specific formats.
Bill Wendling7173da52007-11-13 09:19:02 +000033def SDT_AlphaCallSeqStart : SDCallSeqStart<[ SDTCisVT<0, i64> ]>;
34def SDT_AlphaCallSeqEnd : SDCallSeqEnd<[ SDTCisVT<0, i64>,
35 SDTCisVT<1, i64> ]>;
Bill Wendling22f8deb2007-11-13 00:44:25 +000036
Bill Wendling7173da52007-11-13 09:19:02 +000037def callseq_start : SDNode<"ISD::CALLSEQ_START", SDT_AlphaCallSeqStart,
Bill Wendling6c02cd22008-02-27 06:33:05 +000038 [SDNPHasChain, SDNPOutFlag]>;
Bill Wendling7173da52007-11-13 09:19:02 +000039def callseq_end : SDNode<"ISD::CALLSEQ_END", SDT_AlphaCallSeqEnd,
Bill Wendling22f8deb2007-11-13 00:44:25 +000040 [SDNPHasChain, SDNPOptInFlag, SDNPOutFlag]>;
Dan Gohmanf17a25c2007-07-18 16:29:46 +000041
42//********************
43//Paterns for matching
44//********************
45def invX : SDNodeXForm<imm, [{ //invert
46 return getI64Imm(~N->getValue());
47}]>;
48def negX : SDNodeXForm<imm, [{ //negate
49 return getI64Imm(~N->getValue() + 1);
50}]>;
51def SExt32 : SDNodeXForm<imm, [{ //signed extend int to long
52 return getI64Imm(((int64_t)N->getValue() << 32) >> 32);
53}]>;
54def SExt16 : SDNodeXForm<imm, [{ //signed extend int to long
55 return getI64Imm(((int64_t)N->getValue() << 48) >> 48);
56}]>;
57def LL16 : SDNodeXForm<imm, [{ //lda part of constant
58 return getI64Imm(get_lda16(N->getValue()));
59}]>;
60def LH16 : SDNodeXForm<imm, [{ //ldah part of constant (or more if too big)
61 return getI64Imm(get_ldah16(N->getValue()));
62}]>;
63def iZAPX : SDNodeXForm<and, [{ // get imm to ZAPi
64 ConstantSDNode *RHS = cast<ConstantSDNode>(N->getOperand(1));
Dan Gohman8181bd12008-07-27 21:46:04 +000065 return getI64Imm(get_zapImm(SDValue(), RHS->getValue()));
Dan Gohmanf17a25c2007-07-18 16:29:46 +000066}]>;
67def nearP2X : SDNodeXForm<imm, [{
68 return getI64Imm(Log2_64(getNearPower2((uint64_t)N->getValue())));
69}]>;
70def nearP2RemX : SDNodeXForm<imm, [{
71 uint64_t x = abs(N->getValue() - getNearPower2((uint64_t)N->getValue()));
72 return getI64Imm(Log2_64(x));
73}]>;
74
75def immUExt8 : PatLeaf<(imm), [{ //imm fits in 8 bit zero extended field
76 return (uint64_t)N->getValue() == (uint8_t)N->getValue();
77}]>;
78def immUExt8inv : PatLeaf<(imm), [{ //inverted imm fits in 8 bit zero extended field
79 return (uint64_t)~N->getValue() == (uint8_t)~N->getValue();
80}], invX>;
81def immUExt8neg : PatLeaf<(imm), [{ //negated imm fits in 8 bit zero extended field
82 return ((uint64_t)~N->getValue() + 1) == (uint8_t)((uint64_t)~N->getValue() + 1);
83}], negX>;
84def immSExt16 : PatLeaf<(imm), [{ //imm fits in 16 bit sign extended field
85 return ((int64_t)N->getValue() << 48) >> 48 == (int64_t)N->getValue();
86}]>;
87def immSExt16int : PatLeaf<(imm), [{ //(int)imm fits in a 16 bit sign extended field
88 return ((int64_t)N->getValue() << 48) >> 48 == ((int64_t)N->getValue() << 32) >> 32;
89}], SExt16>;
90
91def zappat : PatFrag<(ops node:$LHS), (and node:$LHS, imm:$L), [{
Dan Gohman8335c412008-08-20 15:24:22 +000092 ConstantSDNode *RHS = cast<ConstantSDNode>(N->getOperand(1));
93 uint64_t build = get_zapImm(N->getOperand(0), (uint64_t)RHS->getValue());
94 return build != 0;
Dan Gohmanf17a25c2007-07-18 16:29:46 +000095}]>;
96
97def immFPZ : PatLeaf<(fpimm), [{ //the only fpconstant nodes are +/- 0.0
98 (void)N; // silence warning.
99 return true;
100}]>;
101
102def immRem1 : PatLeaf<(imm), [{return chkRemNearPower2(N->getValue(),1, 0);}]>;
103def immRem2 : PatLeaf<(imm), [{return chkRemNearPower2(N->getValue(),2, 0);}]>;
104def immRem3 : PatLeaf<(imm), [{return chkRemNearPower2(N->getValue(),3, 0);}]>;
105def immRem4 : PatLeaf<(imm), [{return chkRemNearPower2(N->getValue(),4, 0);}]>;
106def immRem5 : PatLeaf<(imm), [{return chkRemNearPower2(N->getValue(),5, 0);}]>;
107def immRem1n : PatLeaf<(imm), [{return chkRemNearPower2(N->getValue(),1, 1);}]>;
108def immRem2n : PatLeaf<(imm), [{return chkRemNearPower2(N->getValue(),2, 1);}]>;
109def immRem3n : PatLeaf<(imm), [{return chkRemNearPower2(N->getValue(),3, 1);}]>;
110def immRem4n : PatLeaf<(imm), [{return chkRemNearPower2(N->getValue(),4, 1);}]>;
111def immRem5n : PatLeaf<(imm), [{return chkRemNearPower2(N->getValue(),5, 1);}]>;
112
113def immRemP2n : PatLeaf<(imm), [{
114 return isPowerOf2_64(getNearPower2((uint64_t)N->getValue()) - N->getValue());
115}]>;
116def immRemP2 : PatLeaf<(imm), [{
117 return isPowerOf2_64(N->getValue() - getNearPower2((uint64_t)N->getValue()));
118}]>;
119def immUExt8ME : PatLeaf<(imm), [{ //use this imm for mulqi
120 int64_t d = abs((int64_t)N->getValue() - (int64_t)getNearPower2((uint64_t)N->getValue()));
121 if (isPowerOf2_64(d)) return false;
122 switch (d) {
123 case 1: case 3: case 5: return false;
124 default: return (uint64_t)N->getValue() == (uint8_t)N->getValue();
125 };
126}]>;
127
128def intop : PatFrag<(ops node:$op), (sext_inreg node:$op, i32)>;
129def add4 : PatFrag<(ops node:$op1, node:$op2),
130 (add (shl node:$op1, 2), node:$op2)>;
131def sub4 : PatFrag<(ops node:$op1, node:$op2),
132 (sub (shl node:$op1, 2), node:$op2)>;
133def add8 : PatFrag<(ops node:$op1, node:$op2),
134 (add (shl node:$op1, 3), node:$op2)>;
135def sub8 : PatFrag<(ops node:$op1, node:$op2),
136 (sub (shl node:$op1, 3), node:$op2)>;
137class BinOpFrag<dag res> : PatFrag<(ops node:$LHS, node:$RHS), res>;
138class CmpOpFrag<dag res> : PatFrag<(ops node:$R), res>;
139
140//Pseudo ops for selection
141
Evan Chengb783fa32007-07-19 01:14:50 +0000142def WTF : PseudoInstAlpha<(outs), (ins variable_ops), "#wtf", [], s_pseudo>;
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000143
Chris Lattner1a1932c2008-01-06 23:38:27 +0000144let hasCtrlDep = 1, Defs = [R30], Uses = [R30] in {
Bill Wendling22f8deb2007-11-13 00:44:25 +0000145def ADJUSTSTACKUP : PseudoInstAlpha<(outs), (ins s64imm:$amt),
146 "; ADJUP $amt",
Evan Cheng6e4d1d92007-09-11 19:55:27 +0000147 [(callseq_start imm:$amt)], s_pseudo>;
Bill Wendling22f8deb2007-11-13 00:44:25 +0000148def ADJUSTSTACKDOWN : PseudoInstAlpha<(outs), (ins s64imm:$amt1, s64imm:$amt2),
149 "; ADJDOWN $amt1",
150 [(callseq_end imm:$amt1, imm:$amt2)], s_pseudo>;
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000151}
Bill Wendling22f8deb2007-11-13 00:44:25 +0000152
Evan Chengb783fa32007-07-19 01:14:50 +0000153def ALTENT : PseudoInstAlpha<(outs), (ins s64imm:$TARGET), "$$$TARGET..ng:\n", [], s_pseudo>;
154def PCLABEL : PseudoInstAlpha<(outs), (ins s64imm:$num), "PCMARKER_$num:\n",[], s_pseudo>;
155def MEMLABEL : PseudoInstAlpha<(outs), (ins s64imm:$i, s64imm:$j, s64imm:$k, s64imm:$m),
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000156 "LSMARKER$$$i$$$j$$$k$$$m:", [], s_pseudo>;
157
158
Andrew Lenharthe44f3902008-02-21 06:45:13 +0000159let usesCustomDAGSchedInserter = 1 in { // Expanded by the scheduler.
160def CAS32 : PseudoInstAlpha<(outs GPRC:$dst), (ins GPRC:$ptr, GPRC:$cmp, GPRC:$swp), "",
Mon P Wang6bde9ec2008-06-25 08:15:39 +0000161 [(set GPRC:$dst, (atomic_cmp_swap_32 GPRC:$ptr, GPRC:$cmp, GPRC:$swp))], s_pseudo>;
Andrew Lenharthe44f3902008-02-21 06:45:13 +0000162def CAS64 : PseudoInstAlpha<(outs GPRC:$dst), (ins GPRC:$ptr, GPRC:$cmp, GPRC:$swp), "",
Mon P Wang6bde9ec2008-06-25 08:15:39 +0000163 [(set GPRC:$dst, (atomic_cmp_swap_64 GPRC:$ptr, GPRC:$cmp, GPRC:$swp))], s_pseudo>;
Andrew Lenharthe44f3902008-02-21 06:45:13 +0000164
165def LAS32 : PseudoInstAlpha<(outs GPRC:$dst), (ins GPRC:$ptr, GPRC:$swp), "",
Mon P Wang6bde9ec2008-06-25 08:15:39 +0000166 [(set GPRC:$dst, (atomic_load_add_32 GPRC:$ptr, GPRC:$swp))], s_pseudo>;
Andrew Lenharthe44f3902008-02-21 06:45:13 +0000167def LAS64 :PseudoInstAlpha<(outs GPRC:$dst), (ins GPRC:$ptr, GPRC:$swp), "",
Mon P Wang6bde9ec2008-06-25 08:15:39 +0000168 [(set GPRC:$dst, (atomic_load_add_64 GPRC:$ptr, GPRC:$swp))], s_pseudo>;
Andrew Lenharthe44f3902008-02-21 06:45:13 +0000169
170def SWAP32 : PseudoInstAlpha<(outs GPRC:$dst), (ins GPRC:$ptr, GPRC:$swp), "",
171 [(set GPRC:$dst, (atomic_swap_32 GPRC:$ptr, GPRC:$swp))], s_pseudo>;
172def SWAP64 :PseudoInstAlpha<(outs GPRC:$dst), (ins GPRC:$ptr, GPRC:$swp), "",
173 [(set GPRC:$dst, (atomic_swap_64 GPRC:$ptr, GPRC:$swp))], s_pseudo>;
174}
175
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000176//***********************
177//Real instructions
178//***********************
179
180//Operation Form:
181
182//conditional moves, int
183
184multiclass cmov_inst<bits<7> fun, string asmstr, PatFrag OpNode> {
185def r : OForm4<0x11, fun, !strconcat(asmstr, " $RCOND,$RTRUE,$RDEST"),
186 [(set GPRC:$RDEST, (select (OpNode GPRC:$RCOND), GPRC:$RTRUE, GPRC:$RFALSE))], s_cmov>;
187def i : OForm4L<0x11, fun, !strconcat(asmstr, " $RCOND,$RTRUE,$RDEST"),
188 [(set GPRC:$RDEST, (select (OpNode GPRC:$RCOND), immUExt8:$RTRUE, GPRC:$RFALSE))], s_cmov>;
189}
190
191defm CMOVEQ : cmov_inst<0x24, "cmoveq", CmpOpFrag<(seteq node:$R, 0)>>;
192defm CMOVNE : cmov_inst<0x26, "cmovne", CmpOpFrag<(setne node:$R, 0)>>;
193defm CMOVLT : cmov_inst<0x44, "cmovlt", CmpOpFrag<(setlt node:$R, 0)>>;
194defm CMOVLE : cmov_inst<0x64, "cmovle", CmpOpFrag<(setle node:$R, 0)>>;
195defm CMOVGT : cmov_inst<0x66, "cmovgt", CmpOpFrag<(setgt node:$R, 0)>>;
196defm CMOVGE : cmov_inst<0x46, "cmovge", CmpOpFrag<(setge node:$R, 0)>>;
197defm CMOVLBC : cmov_inst<0x16, "cmovlbc", CmpOpFrag<(xor node:$R, 1)>>;
198defm CMOVLBS : cmov_inst<0x14, "cmovlbs", CmpOpFrag<(and node:$R, 1)>>;
199
200//General pattern for cmov
201def : Pat<(select GPRC:$which, GPRC:$src1, GPRC:$src2),
202 (CMOVNEr GPRC:$src2, GPRC:$src1, GPRC:$which)>;
203def : Pat<(select GPRC:$which, GPRC:$src1, immUExt8:$src2),
204 (CMOVEQi GPRC:$src1, immUExt8:$src2, GPRC:$which)>;
205
206//Invert sense when we can for constants:
207def : Pat<(select (setne GPRC:$RCOND, 0), GPRC:$RTRUE, immUExt8:$RFALSE),
208 (CMOVEQi GPRC:$RCOND, immUExt8:$RFALSE, GPRC:$RTRUE)>;
209def : Pat<(select (setgt GPRC:$RCOND, 0), GPRC:$RTRUE, immUExt8:$RFALSE),
210 (CMOVLEi GPRC:$RCOND, immUExt8:$RFALSE, GPRC:$RTRUE)>;
211def : Pat<(select (setge GPRC:$RCOND, 0), GPRC:$RTRUE, immUExt8:$RFALSE),
212 (CMOVLTi GPRC:$RCOND, immUExt8:$RFALSE, GPRC:$RTRUE)>;
213def : Pat<(select (setlt GPRC:$RCOND, 0), GPRC:$RTRUE, immUExt8:$RFALSE),
214 (CMOVGEi GPRC:$RCOND, immUExt8:$RFALSE, GPRC:$RTRUE)>;
215def : Pat<(select (setle GPRC:$RCOND, 0), GPRC:$RTRUE, immUExt8:$RFALSE),
216 (CMOVGTi GPRC:$RCOND, immUExt8:$RFALSE, GPRC:$RTRUE)>;
217
218multiclass all_inst<bits<6> opc, bits<7> funl, bits<7> funq,
219 string asmstr, PatFrag OpNode, InstrItinClass itin> {
220 def Lr : OForm< opc, funl, !strconcat(asmstr, "l $RA,$RB,$RC"),
221 [(set GPRC:$RC, (intop (OpNode GPRC:$RA, GPRC:$RB)))], itin>;
222 def Li : OFormL<opc, funl, !strconcat(asmstr, "l $RA,$L,$RC"),
223 [(set GPRC:$RC, (intop (OpNode GPRC:$RA, immUExt8:$L)))], itin>;
224 def Qr : OForm< opc, funq, !strconcat(asmstr, "q $RA,$RB,$RC"),
225 [(set GPRC:$RC, (OpNode GPRC:$RA, GPRC:$RB))], itin>;
226 def Qi : OFormL<opc, funq, !strconcat(asmstr, "q $RA,$L,$RC"),
227 [(set GPRC:$RC, (OpNode GPRC:$RA, immUExt8:$L))], itin>;
228}
229
230defm MUL : all_inst<0x13, 0x00, 0x20, "mul", BinOpFrag<(mul node:$LHS, node:$RHS)>, s_imul>;
231defm ADD : all_inst<0x10, 0x00, 0x20, "add", BinOpFrag<(add node:$LHS, node:$RHS)>, s_iadd>;
232defm S4ADD : all_inst<0x10, 0x02, 0x22, "s4add", add4, s_iadd>;
233defm S8ADD : all_inst<0x10, 0x12, 0x32, "s8add", add8, s_iadd>;
234defm S4SUB : all_inst<0x10, 0x0B, 0x2B, "s4sub", sub4, s_iadd>;
235defm S8SUB : all_inst<0x10, 0x1B, 0x3B, "s8sub", sub8, s_iadd>;
236defm SUB : all_inst<0x10, 0x09, 0x29, "sub", BinOpFrag<(sub node:$LHS, node:$RHS)>, s_iadd>;
237//Const cases since legalize does sub x, int -> add x, inv(int) + 1
238def : Pat<(intop (add GPRC:$RA, immUExt8neg:$L)), (SUBLi GPRC:$RA, immUExt8neg:$L)>;
239def : Pat<(add GPRC:$RA, immUExt8neg:$L), (SUBQi GPRC:$RA, immUExt8neg:$L)>;
240def : Pat<(intop (add4 GPRC:$RA, immUExt8neg:$L)), (S4SUBLi GPRC:$RA, immUExt8neg:$L)>;
241def : Pat<(add4 GPRC:$RA, immUExt8neg:$L), (S4SUBQi GPRC:$RA, immUExt8neg:$L)>;
242def : Pat<(intop (add8 GPRC:$RA, immUExt8neg:$L)), (S8SUBLi GPRC:$RA, immUExt8neg:$L)>;
243def : Pat<(add8 GPRC:$RA, immUExt8neg:$L), (S8SUBQi GPRC:$RA, immUExt8neg:$L)>;
244
245multiclass log_inst<bits<6> opc, bits<7> fun, string asmstr, SDNode OpNode, InstrItinClass itin> {
246def r : OForm<opc, fun, !strconcat(asmstr, " $RA,$RB,$RC"),
247 [(set GPRC:$RC, (OpNode GPRC:$RA, GPRC:$RB))], itin>;
248def i : OFormL<opc, fun, !strconcat(asmstr, " $RA,$L,$RC"),
249 [(set GPRC:$RC, (OpNode GPRC:$RA, immUExt8:$L))], itin>;
250}
251multiclass inv_inst<bits<6> opc, bits<7> fun, string asmstr, SDNode OpNode, InstrItinClass itin> {
252def r : OForm<opc, fun, !strconcat(asmstr, " $RA,$RB,$RC"),
253 [(set GPRC:$RC, (OpNode GPRC:$RA, (not GPRC:$RB)))], itin>;
254def i : OFormL<opc, fun, !strconcat(asmstr, " $RA,$L,$RC"),
255 [(set GPRC:$RC, (OpNode GPRC:$RA, immUExt8inv:$L))], itin>;
256}
257
258defm AND : log_inst<0x11, 0x00, "and", and, s_ilog>;
259defm BIC : inv_inst<0x11, 0x08, "bic", and, s_ilog>;
260defm BIS : log_inst<0x11, 0x20, "bis", or, s_ilog>;
261defm ORNOT : inv_inst<0x11, 0x28, "ornot", or, s_ilog>;
262defm XOR : log_inst<0x11, 0x40, "xor", xor, s_ilog>;
263defm EQV : inv_inst<0x11, 0x48, "eqv", xor, s_ilog>;
264
265defm SL : log_inst<0x12, 0x39, "sll", shl, s_ishf>;
266defm SRA : log_inst<0x12, 0x3c, "sra", sra, s_ishf>;
267defm SRL : log_inst<0x12, 0x34, "srl", srl, s_ishf>;
268defm UMULH : log_inst<0x13, 0x30, "umulh", mulhu, s_imul>;
269
270def CTLZ : OForm2<0x1C, 0x32, "CTLZ $RB,$RC",
271 [(set GPRC:$RC, (ctlz GPRC:$RB))], s_imisc>;
272def CTPOP : OForm2<0x1C, 0x30, "CTPOP $RB,$RC",
273 [(set GPRC:$RC, (ctpop GPRC:$RB))], s_imisc>;
274def CTTZ : OForm2<0x1C, 0x33, "CTTZ $RB,$RC",
275 [(set GPRC:$RC, (cttz GPRC:$RB))], s_imisc>;
276def EXTBL : OForm< 0x12, 0x06, "EXTBL $RA,$RB,$RC",
277 [(set GPRC:$RC, (and (srl GPRC:$RA, (shl GPRC:$RB, 3)), 255))], s_ishf>;
278def EXTWL : OForm< 0x12, 0x16, "EXTWL $RA,$RB,$RC",
279 [(set GPRC:$RC, (and (srl GPRC:$RA, (shl GPRC:$RB, 3)), 65535))], s_ishf>;
280def EXTLL : OForm< 0x12, 0x26, "EXTLL $RA,$RB,$RC",
281 [(set GPRC:$RC, (and (srl GPRC:$RA, (shl GPRC:$RB, 3)), 4294967295))], s_ishf>;
282def SEXTB : OForm2<0x1C, 0x00, "sextb $RB,$RC",
283 [(set GPRC:$RC, (sext_inreg GPRC:$RB, i8))], s_ishf>;
284def SEXTW : OForm2<0x1C, 0x01, "sextw $RB,$RC",
285 [(set GPRC:$RC, (sext_inreg GPRC:$RB, i16))], s_ishf>;
286
287//def EXTBLi : OFormL<0x12, 0x06, "EXTBL $RA,$L,$RC", []>; //Extract byte low
288//def EXTLH : OForm< 0x12, 0x6A, "EXTLH $RA,$RB,$RC", []>; //Extract longword high
289//def EXTLHi : OFormL<0x12, 0x6A, "EXTLH $RA,$L,$RC", []>; //Extract longword high
290//def EXTLLi : OFormL<0x12, 0x26, "EXTLL $RA,$L,$RC", []>; //Extract longword low
291//def EXTQH : OForm< 0x12, 0x7A, "EXTQH $RA,$RB,$RC", []>; //Extract quadword high
292//def EXTQHi : OFormL<0x12, 0x7A, "EXTQH $RA,$L,$RC", []>; //Extract quadword high
293//def EXTQ : OForm< 0x12, 0x36, "EXTQ $RA,$RB,$RC", []>; //Extract quadword low
294//def EXTQi : OFormL<0x12, 0x36, "EXTQ $RA,$L,$RC", []>; //Extract quadword low
295//def EXTWH : OForm< 0x12, 0x5A, "EXTWH $RA,$RB,$RC", []>; //Extract word high
296//def EXTWHi : OFormL<0x12, 0x5A, "EXTWH $RA,$L,$RC", []>; //Extract word high
297//def EXTWLi : OFormL<0x12, 0x16, "EXTWL $RA,$L,$RC", []>; //Extract word low
298
299//def INSBL : OForm< 0x12, 0x0B, "INSBL $RA,$RB,$RC", []>; //Insert byte low
300//def INSBLi : OFormL<0x12, 0x0B, "INSBL $RA,$L,$RC", []>; //Insert byte low
301//def INSLH : OForm< 0x12, 0x67, "INSLH $RA,$RB,$RC", []>; //Insert longword high
302//def INSLHi : OFormL<0x12, 0x67, "INSLH $RA,$L,$RC", []>; //Insert longword high
303//def INSLL : OForm< 0x12, 0x2B, "INSLL $RA,$RB,$RC", []>; //Insert longword low
304//def INSLLi : OFormL<0x12, 0x2B, "INSLL $RA,$L,$RC", []>; //Insert longword low
305//def INSQH : OForm< 0x12, 0x77, "INSQH $RA,$RB,$RC", []>; //Insert quadword high
306//def INSQHi : OFormL<0x12, 0x77, "INSQH $RA,$L,$RC", []>; //Insert quadword high
307//def INSQL : OForm< 0x12, 0x3B, "INSQL $RA,$RB,$RC", []>; //Insert quadword low
308//def INSQLi : OFormL<0x12, 0x3B, "INSQL $RA,$L,$RC", []>; //Insert quadword low
309//def INSWH : OForm< 0x12, 0x57, "INSWH $RA,$RB,$RC", []>; //Insert word high
310//def INSWHi : OFormL<0x12, 0x57, "INSWH $RA,$L,$RC", []>; //Insert word high
311//def INSWL : OForm< 0x12, 0x1B, "INSWL $RA,$RB,$RC", []>; //Insert word low
312//def INSWLi : OFormL<0x12, 0x1B, "INSWL $RA,$L,$RC", []>; //Insert word low
313
314//def MSKBL : OForm< 0x12, 0x02, "MSKBL $RA,$RB,$RC", []>; //Mask byte low
315//def MSKBLi : OFormL<0x12, 0x02, "MSKBL $RA,$L,$RC", []>; //Mask byte low
316//def MSKLH : OForm< 0x12, 0x62, "MSKLH $RA,$RB,$RC", []>; //Mask longword high
317//def MSKLHi : OFormL<0x12, 0x62, "MSKLH $RA,$L,$RC", []>; //Mask longword high
318//def MSKLL : OForm< 0x12, 0x22, "MSKLL $RA,$RB,$RC", []>; //Mask longword low
319//def MSKLLi : OFormL<0x12, 0x22, "MSKLL $RA,$L,$RC", []>; //Mask longword low
320//def MSKQH : OForm< 0x12, 0x72, "MSKQH $RA,$RB,$RC", []>; //Mask quadword high
321//def MSKQHi : OFormL<0x12, 0x72, "MSKQH $RA,$L,$RC", []>; //Mask quadword high
322//def MSKQL : OForm< 0x12, 0x32, "MSKQL $RA,$RB,$RC", []>; //Mask quadword low
323//def MSKQLi : OFormL<0x12, 0x32, "MSKQL $RA,$L,$RC", []>; //Mask quadword low
324//def MSKWH : OForm< 0x12, 0x52, "MSKWH $RA,$RB,$RC", []>; //Mask word high
325//def MSKWHi : OFormL<0x12, 0x52, "MSKWH $RA,$L,$RC", []>; //Mask word high
326//def MSKWL : OForm< 0x12, 0x12, "MSKWL $RA,$RB,$RC", []>; //Mask word low
327//def MSKWLi : OFormL<0x12, 0x12, "MSKWL $RA,$L,$RC", []>; //Mask word low
328
329def ZAPNOTi : OFormL<0x12, 0x31, "zapnot $RA,$L,$RC", [], s_ishf>;
330
331// Define the pattern that produces ZAPNOTi.
332def : Pat<(i64 (zappat GPRC:$RA):$imm),
333 (ZAPNOTi GPRC:$RA, (iZAPX GPRC:$imm))>;
334
335
336//Comparison, int
337//So this is a waste of what this instruction can do, but it still saves something
338def CMPBGE : OForm< 0x10, 0x0F, "cmpbge $RA,$RB,$RC",
339 [(set GPRC:$RC, (setuge (and GPRC:$RA, 255), (and GPRC:$RB, 255)))], s_ilog>;
340def CMPBGEi : OFormL<0x10, 0x0F, "cmpbge $RA,$L,$RC",
341 [(set GPRC:$RC, (setuge (and GPRC:$RA, 255), immUExt8:$L))], s_ilog>;
342def CMPEQ : OForm< 0x10, 0x2D, "cmpeq $RA,$RB,$RC",
343 [(set GPRC:$RC, (seteq GPRC:$RA, GPRC:$RB))], s_iadd>;
344def CMPEQi : OFormL<0x10, 0x2D, "cmpeq $RA,$L,$RC",
345 [(set GPRC:$RC, (seteq GPRC:$RA, immUExt8:$L))], s_iadd>;
346def CMPLE : OForm< 0x10, 0x6D, "cmple $RA,$RB,$RC",
347 [(set GPRC:$RC, (setle GPRC:$RA, GPRC:$RB))], s_iadd>;
348def CMPLEi : OFormL<0x10, 0x6D, "cmple $RA,$L,$RC",
349 [(set GPRC:$RC, (setle GPRC:$RA, immUExt8:$L))], s_iadd>;
350def CMPLT : OForm< 0x10, 0x4D, "cmplt $RA,$RB,$RC",
351 [(set GPRC:$RC, (setlt GPRC:$RA, GPRC:$RB))], s_iadd>;
352def CMPLTi : OFormL<0x10, 0x4D, "cmplt $RA,$L,$RC",
353 [(set GPRC:$RC, (setlt GPRC:$RA, immUExt8:$L))], s_iadd>;
354def CMPULE : OForm< 0x10, 0x3D, "cmpule $RA,$RB,$RC",
355 [(set GPRC:$RC, (setule GPRC:$RA, GPRC:$RB))], s_iadd>;
356def CMPULEi : OFormL<0x10, 0x3D, "cmpule $RA,$L,$RC",
357 [(set GPRC:$RC, (setule GPRC:$RA, immUExt8:$L))], s_iadd>;
358def CMPULT : OForm< 0x10, 0x1D, "cmpult $RA,$RB,$RC",
359 [(set GPRC:$RC, (setult GPRC:$RA, GPRC:$RB))], s_iadd>;
360def CMPULTi : OFormL<0x10, 0x1D, "cmpult $RA,$L,$RC",
361 [(set GPRC:$RC, (setult GPRC:$RA, immUExt8:$L))], s_iadd>;
362
363//Patterns for unsupported int comparisons
364def : Pat<(setueq GPRC:$X, GPRC:$Y), (CMPEQ GPRC:$X, GPRC:$Y)>;
365def : Pat<(setueq GPRC:$X, immUExt8:$Y), (CMPEQi GPRC:$X, immUExt8:$Y)>;
366
367def : Pat<(setugt GPRC:$X, GPRC:$Y), (CMPULT GPRC:$Y, GPRC:$X)>;
368def : Pat<(setugt immUExt8:$X, GPRC:$Y), (CMPULTi GPRC:$Y, immUExt8:$X)>;
369
370def : Pat<(setuge GPRC:$X, GPRC:$Y), (CMPULE GPRC:$Y, GPRC:$X)>;
371def : Pat<(setuge immUExt8:$X, GPRC:$Y), (CMPULEi GPRC:$Y, immUExt8:$X)>;
372
373def : Pat<(setgt GPRC:$X, GPRC:$Y), (CMPLT GPRC:$Y, GPRC:$X)>;
374def : Pat<(setgt immUExt8:$X, GPRC:$Y), (CMPLTi GPRC:$Y, immUExt8:$X)>;
375
376def : Pat<(setge GPRC:$X, GPRC:$Y), (CMPLE GPRC:$Y, GPRC:$X)>;
377def : Pat<(setge immUExt8:$X, GPRC:$Y), (CMPLEi GPRC:$Y, immUExt8:$X)>;
378
379def : Pat<(setne GPRC:$X, GPRC:$Y), (CMPEQi (CMPEQ GPRC:$X, GPRC:$Y), 0)>;
380def : Pat<(setne GPRC:$X, immUExt8:$Y), (CMPEQi (CMPEQi GPRC:$X, immUExt8:$Y), 0)>;
381
382def : Pat<(setune GPRC:$X, GPRC:$Y), (CMPEQi (CMPEQ GPRC:$X, GPRC:$Y), 0)>;
383def : Pat<(setune GPRC:$X, immUExt8:$Y), (CMPEQi (CMPEQ GPRC:$X, immUExt8:$Y), 0)>;
384
385
Evan Cheng37e7c752007-07-21 00:34:19 +0000386let isReturn = 1, isTerminator = 1, Ra = 31, Rb = 26, disp = 1, Uses = [R26] in {
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000387 def RETDAG : MbrForm< 0x1A, 0x02, (ops), "ret $$31,($$26),1", s_jsr>; //Return from subroutine
388 def RETDAGp : MbrpForm< 0x1A, 0x02, (ops), "ret $$31,($$26),1", [(retflag)], s_jsr>; //Return from subroutine
389}
390
Owen Andersonf8053082007-11-12 07:39:39 +0000391let isBranch = 1, isTerminator = 1, isBarrier = 1, isIndirectBranch = 1, Ra = 31, disp = 0 in
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000392def JMP : MbrpForm< 0x1A, 0x00, (ops GPRC:$RS), "jmp $$31,($RS),0",
393 [(brind GPRC:$RS)], s_jsr>; //Jump
394
Evan Cheng37e7c752007-07-21 00:34:19 +0000395let isCall = 1, Ra = 26,
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000396 Defs = [R0, R1, R2, R3, R4, R5, R6, R7, R8, R16, R17, R18, R19,
397 R20, R21, R22, R23, R24, R25, R26, R27, R28, R29,
398 F0, F1,
399 F10, F11, F12, F13, F14, F15, F16, F17, F18, F19,
400 F20, F21, F22, F23, F24, F25, F26, F27, F28, F29, F30], Uses = [R29] in {
401 def BSR : BFormD<0x34, "bsr $$26,$$$DISP..ng", [], s_jsr>; //Branch to subroutine
402}
Evan Cheng37e7c752007-07-21 00:34:19 +0000403let isCall = 1, Ra = 26, Rb = 27, disp = 0,
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000404 Defs = [R0, R1, R2, R3, R4, R5, R6, R7, R8, R16, R17, R18, R19,
405 R20, R21, R22, R23, R24, R25, R26, R27, R28, R29,
406 F0, F1,
407 F10, F11, F12, F13, F14, F15, F16, F17, F18, F19,
408 F20, F21, F22, F23, F24, F25, F26, F27, F28, F29, F30], Uses = [R27, R29] in {
409 def JSR : MbrForm< 0x1A, 0x01, (ops ), "jsr $$26,($$27),0", s_jsr>; //Jump to subroutine
410}
411
Evan Cheng37e7c752007-07-21 00:34:19 +0000412let isCall = 1, Ra = 23, Rb = 27, disp = 0,
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000413 Defs = [R23, R24, R25, R27, R28], Uses = [R24, R25, R27] in
414 def JSRs : MbrForm< 0x1A, 0x01, (ops ), "jsr $$23,($$27),0", s_jsr>; //Jump to div or rem
415
416
417def JSR_COROUTINE : MbrForm< 0x1A, 0x03, (ops GPRC:$RD, GPRC:$RS, s14imm:$DISP), "jsr_coroutine $RD,($RS),$DISP", s_jsr>; //Jump to subroutine return
418
419
Evan Chengb783fa32007-07-19 01:14:50 +0000420let OutOperandList = (ops GPRC:$RA), InOperandList = (ops s64imm:$DISP, GPRC:$RB) in {
Chris Lattneref8d6082008-01-06 06:44:58 +0000421def LDQ : MForm<0x29, 1, "ldq $RA,$DISP($RB)",
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000422 [(set GPRC:$RA, (load (add GPRC:$RB, immSExt16:$DISP)))], s_ild>;
Chris Lattneref8d6082008-01-06 06:44:58 +0000423def LDQr : MForm<0x29, 1, "ldq $RA,$DISP($RB)\t\t!gprellow",
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000424 [(set GPRC:$RA, (load (Alpha_gprello tglobaladdr:$DISP, GPRC:$RB)))], s_ild>;
Chris Lattneref8d6082008-01-06 06:44:58 +0000425def LDL : MForm<0x28, 1, "ldl $RA,$DISP($RB)",
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000426 [(set GPRC:$RA, (sextloadi32 (add GPRC:$RB, immSExt16:$DISP)))], s_ild>;
Chris Lattneref8d6082008-01-06 06:44:58 +0000427def LDLr : MForm<0x28, 1, "ldl $RA,$DISP($RB)\t\t!gprellow",
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000428 [(set GPRC:$RA, (sextloadi32 (Alpha_gprello tglobaladdr:$DISP, GPRC:$RB)))], s_ild>;
Chris Lattneref8d6082008-01-06 06:44:58 +0000429def LDBU : MForm<0x0A, 1, "ldbu $RA,$DISP($RB)",
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000430 [(set GPRC:$RA, (zextloadi8 (add GPRC:$RB, immSExt16:$DISP)))], s_ild>;
Chris Lattneref8d6082008-01-06 06:44:58 +0000431def LDBUr : MForm<0x0A, 1, "ldbu $RA,$DISP($RB)\t\t!gprellow",
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000432 [(set GPRC:$RA, (zextloadi8 (Alpha_gprello tglobaladdr:$DISP, GPRC:$RB)))], s_ild>;
Chris Lattneref8d6082008-01-06 06:44:58 +0000433def LDWU : MForm<0x0C, 1, "ldwu $RA,$DISP($RB)",
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000434 [(set GPRC:$RA, (zextloadi16 (add GPRC:$RB, immSExt16:$DISP)))], s_ild>;
Chris Lattneref8d6082008-01-06 06:44:58 +0000435def LDWUr : MForm<0x0C, 1, "ldwu $RA,$DISP($RB)\t\t!gprellow",
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000436 [(set GPRC:$RA, (zextloadi16 (Alpha_gprello tglobaladdr:$DISP, GPRC:$RB)))], s_ild>;
Evan Chengb783fa32007-07-19 01:14:50 +0000437}
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000438
439
Evan Chengb783fa32007-07-19 01:14:50 +0000440let OutOperandList = (ops), InOperandList = (ops GPRC:$RA, s64imm:$DISP, GPRC:$RB) in {
Chris Lattneref8d6082008-01-06 06:44:58 +0000441def STB : MForm<0x0E, 0, "stb $RA,$DISP($RB)",
Bill Wendling6c02cd22008-02-27 06:33:05 +0000442 [(truncstorei8 GPRC:$RA, (add GPRC:$RB, immSExt16:$DISP))], s_ist>;
Chris Lattneref8d6082008-01-06 06:44:58 +0000443def STBr : MForm<0x0E, 0, "stb $RA,$DISP($RB)\t\t!gprellow",
Bill Wendling6c02cd22008-02-27 06:33:05 +0000444 [(truncstorei8 GPRC:$RA, (Alpha_gprello tglobaladdr:$DISP, GPRC:$RB))], s_ist>;
Chris Lattneref8d6082008-01-06 06:44:58 +0000445def STW : MForm<0x0D, 0, "stw $RA,$DISP($RB)",
Bill Wendling6c02cd22008-02-27 06:33:05 +0000446 [(truncstorei16 GPRC:$RA, (add GPRC:$RB, immSExt16:$DISP))], s_ist>;
Chris Lattneref8d6082008-01-06 06:44:58 +0000447def STWr : MForm<0x0D, 0, "stw $RA,$DISP($RB)\t\t!gprellow",
Bill Wendling6c02cd22008-02-27 06:33:05 +0000448 [(truncstorei16 GPRC:$RA, (Alpha_gprello tglobaladdr:$DISP, GPRC:$RB))], s_ist>;
Chris Lattneref8d6082008-01-06 06:44:58 +0000449def STL : MForm<0x2C, 0, "stl $RA,$DISP($RB)",
Bill Wendling6c02cd22008-02-27 06:33:05 +0000450 [(truncstorei32 GPRC:$RA, (add GPRC:$RB, immSExt16:$DISP))], s_ist>;
Chris Lattneref8d6082008-01-06 06:44:58 +0000451def STLr : MForm<0x2C, 0, "stl $RA,$DISP($RB)\t\t!gprellow",
Bill Wendling6c02cd22008-02-27 06:33:05 +0000452 [(truncstorei32 GPRC:$RA, (Alpha_gprello tglobaladdr:$DISP, GPRC:$RB))], s_ist>;
Chris Lattneref8d6082008-01-06 06:44:58 +0000453def STQ : MForm<0x2D, 0, "stq $RA,$DISP($RB)",
Bill Wendling6c02cd22008-02-27 06:33:05 +0000454 [(store GPRC:$RA, (add GPRC:$RB, immSExt16:$DISP))], s_ist>;
Chris Lattneref8d6082008-01-06 06:44:58 +0000455def STQr : MForm<0x2D, 0, "stq $RA,$DISP($RB)\t\t!gprellow",
Bill Wendling6c02cd22008-02-27 06:33:05 +0000456 [(store GPRC:$RA, (Alpha_gprello tglobaladdr:$DISP, GPRC:$RB))], s_ist>;
Evan Chengb783fa32007-07-19 01:14:50 +0000457}
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000458
459//Load address
Evan Chengb783fa32007-07-19 01:14:50 +0000460let OutOperandList = (ops GPRC:$RA), InOperandList = (ops s64imm:$DISP, GPRC:$RB) in {
Chris Lattneref8d6082008-01-06 06:44:58 +0000461def LDA : MForm<0x08, 0, "lda $RA,$DISP($RB)",
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000462 [(set GPRC:$RA, (add GPRC:$RB, immSExt16:$DISP))], s_lda>;
Chris Lattneref8d6082008-01-06 06:44:58 +0000463def LDAr : MForm<0x08, 0, "lda $RA,$DISP($RB)\t\t!gprellow",
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000464 [(set GPRC:$RA, (Alpha_gprello tglobaladdr:$DISP, GPRC:$RB))], s_lda>; //Load address
Chris Lattneref8d6082008-01-06 06:44:58 +0000465def LDAH : MForm<0x09, 0, "ldah $RA,$DISP($RB)",
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000466 [], s_lda>; //Load address high
Chris Lattneref8d6082008-01-06 06:44:58 +0000467def LDAHr : MForm<0x09, 0, "ldah $RA,$DISP($RB)\t\t!gprelhigh",
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000468 [(set GPRC:$RA, (Alpha_gprelhi tglobaladdr:$DISP, GPRC:$RB))], s_lda>; //Load address high
469}
470
Evan Chengb783fa32007-07-19 01:14:50 +0000471let OutOperandList = (ops), InOperandList = (ops F4RC:$RA, s64imm:$DISP, GPRC:$RB) in {
Chris Lattneref8d6082008-01-06 06:44:58 +0000472def STS : MForm<0x26, 0, "sts $RA,$DISP($RB)",
Bill Wendling6c02cd22008-02-27 06:33:05 +0000473 [(store F4RC:$RA, (add GPRC:$RB, immSExt16:$DISP))], s_fst>;
Chris Lattneref8d6082008-01-06 06:44:58 +0000474def STSr : MForm<0x26, 0, "sts $RA,$DISP($RB)\t\t!gprellow",
Bill Wendling6c02cd22008-02-27 06:33:05 +0000475 [(store F4RC:$RA, (Alpha_gprello tglobaladdr:$DISP, GPRC:$RB))], s_fst>;
Evan Chengb783fa32007-07-19 01:14:50 +0000476}
477let OutOperandList = (ops F4RC:$RA), InOperandList = (ops s64imm:$DISP, GPRC:$RB) in {
Chris Lattneref8d6082008-01-06 06:44:58 +0000478def LDS : MForm<0x22, 1, "lds $RA,$DISP($RB)",
Bill Wendling6c02cd22008-02-27 06:33:05 +0000479 [(set F4RC:$RA, (load (add GPRC:$RB, immSExt16:$DISP)))], s_fld>;
Chris Lattneref8d6082008-01-06 06:44:58 +0000480def LDSr : MForm<0x22, 1, "lds $RA,$DISP($RB)\t\t!gprellow",
Bill Wendling6c02cd22008-02-27 06:33:05 +0000481 [(set F4RC:$RA, (load (Alpha_gprello tglobaladdr:$DISP, GPRC:$RB)))], s_fld>;
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000482}
Evan Chengb783fa32007-07-19 01:14:50 +0000483let OutOperandList = (ops), InOperandList = (ops F8RC:$RA, s64imm:$DISP, GPRC:$RB) in {
Chris Lattneref8d6082008-01-06 06:44:58 +0000484def STT : MForm<0x27, 0, "stt $RA,$DISP($RB)",
Bill Wendling6c02cd22008-02-27 06:33:05 +0000485 [(store F8RC:$RA, (add GPRC:$RB, immSExt16:$DISP))], s_fst>;
Chris Lattneref8d6082008-01-06 06:44:58 +0000486def STTr : MForm<0x27, 0, "stt $RA,$DISP($RB)\t\t!gprellow",
Bill Wendling6c02cd22008-02-27 06:33:05 +0000487 [(store F8RC:$RA, (Alpha_gprello tglobaladdr:$DISP, GPRC:$RB))], s_fst>;
Evan Chengb783fa32007-07-19 01:14:50 +0000488}
489let OutOperandList = (ops F8RC:$RA), InOperandList = (ops s64imm:$DISP, GPRC:$RB) in {
Chris Lattneref8d6082008-01-06 06:44:58 +0000490def LDT : MForm<0x23, 1, "ldt $RA,$DISP($RB)",
Bill Wendling6c02cd22008-02-27 06:33:05 +0000491 [(set F8RC:$RA, (load (add GPRC:$RB, immSExt16:$DISP)))], s_fld>;
Chris Lattneref8d6082008-01-06 06:44:58 +0000492def LDTr : MForm<0x23, 1, "ldt $RA,$DISP($RB)\t\t!gprellow",
Bill Wendling6c02cd22008-02-27 06:33:05 +0000493 [(set F8RC:$RA, (load (Alpha_gprello tglobaladdr:$DISP, GPRC:$RB)))], s_fld>;
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000494}
495
496
497//constpool rels
498def : Pat<(i64 (load (Alpha_gprello tconstpool:$DISP, GPRC:$RB))),
499 (LDQr tconstpool:$DISP, GPRC:$RB)>;
500def : Pat<(i64 (sextloadi32 (Alpha_gprello tconstpool:$DISP, GPRC:$RB))),
501 (LDLr tconstpool:$DISP, GPRC:$RB)>;
502def : Pat<(i64 (zextloadi8 (Alpha_gprello tconstpool:$DISP, GPRC:$RB))),
503 (LDBUr tconstpool:$DISP, GPRC:$RB)>;
504def : Pat<(i64 (zextloadi16 (Alpha_gprello tconstpool:$DISP, GPRC:$RB))),
505 (LDWUr tconstpool:$DISP, GPRC:$RB)>;
506def : Pat<(i64 (Alpha_gprello tconstpool:$DISP, GPRC:$RB)),
507 (LDAr tconstpool:$DISP, GPRC:$RB)>;
508def : Pat<(i64 (Alpha_gprelhi tconstpool:$DISP, GPRC:$RB)),
509 (LDAHr tconstpool:$DISP, GPRC:$RB)>;
510def : Pat<(f32 (load (Alpha_gprello tconstpool:$DISP, GPRC:$RB))),
511 (LDSr tconstpool:$DISP, GPRC:$RB)>;
512def : Pat<(f64 (load (Alpha_gprello tconstpool:$DISP, GPRC:$RB))),
513 (LDTr tconstpool:$DISP, GPRC:$RB)>;
514
515//jumptable rels
516def : Pat<(i64 (Alpha_gprelhi tjumptable:$DISP, GPRC:$RB)),
517 (LDAHr tjumptable:$DISP, GPRC:$RB)>;
518def : Pat<(i64 (Alpha_gprello tjumptable:$DISP, GPRC:$RB)),
519 (LDAr tjumptable:$DISP, GPRC:$RB)>;
520
521
522//misc ext patterns
523def : Pat<(i64 (extloadi8 (add GPRC:$RB, immSExt16:$DISP))),
524 (LDBU immSExt16:$DISP, GPRC:$RB)>;
525def : Pat<(i64 (extloadi16 (add GPRC:$RB, immSExt16:$DISP))),
526 (LDWU immSExt16:$DISP, GPRC:$RB)>;
527def : Pat<(i64 (extloadi32 (add GPRC:$RB, immSExt16:$DISP))),
528 (LDL immSExt16:$DISP, GPRC:$RB)>;
529
530//0 disp patterns
531def : Pat<(i64 (load GPRC:$addr)),
532 (LDQ 0, GPRC:$addr)>;
533def : Pat<(f64 (load GPRC:$addr)),
534 (LDT 0, GPRC:$addr)>;
535def : Pat<(f32 (load GPRC:$addr)),
536 (LDS 0, GPRC:$addr)>;
537def : Pat<(i64 (sextloadi32 GPRC:$addr)),
538 (LDL 0, GPRC:$addr)>;
539def : Pat<(i64 (zextloadi16 GPRC:$addr)),
540 (LDWU 0, GPRC:$addr)>;
541def : Pat<(i64 (zextloadi8 GPRC:$addr)),
542 (LDBU 0, GPRC:$addr)>;
543def : Pat<(i64 (extloadi8 GPRC:$addr)),
544 (LDBU 0, GPRC:$addr)>;
545def : Pat<(i64 (extloadi16 GPRC:$addr)),
546 (LDWU 0, GPRC:$addr)>;
547def : Pat<(i64 (extloadi32 GPRC:$addr)),
548 (LDL 0, GPRC:$addr)>;
549
550def : Pat<(store GPRC:$DATA, GPRC:$addr),
551 (STQ GPRC:$DATA, 0, GPRC:$addr)>;
552def : Pat<(store F8RC:$DATA, GPRC:$addr),
553 (STT F8RC:$DATA, 0, GPRC:$addr)>;
554def : Pat<(store F4RC:$DATA, GPRC:$addr),
555 (STS F4RC:$DATA, 0, GPRC:$addr)>;
556def : Pat<(truncstorei32 GPRC:$DATA, GPRC:$addr),
557 (STL GPRC:$DATA, 0, GPRC:$addr)>;
558def : Pat<(truncstorei16 GPRC:$DATA, GPRC:$addr),
559 (STW GPRC:$DATA, 0, GPRC:$addr)>;
560def : Pat<(truncstorei8 GPRC:$DATA, GPRC:$addr),
561 (STB GPRC:$DATA, 0, GPRC:$addr)>;
562
563
564//load address, rellocated gpdist form
Evan Chengb783fa32007-07-19 01:14:50 +0000565let OutOperandList = (ops GPRC:$RA), InOperandList = (ops s16imm:$DISP, GPRC:$RB, s16imm:$NUM) in {
Chris Lattneref8d6082008-01-06 06:44:58 +0000566def LDAg : MForm<0x08, 1, "lda $RA,0($RB)\t\t!gpdisp!$NUM", [], s_lda>; //Load address
567def LDAHg : MForm<0x09, 1, "ldah $RA,0($RB)\t\t!gpdisp!$NUM", [], s_lda>; //Load address
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000568}
569
570//Load quad, rellocated literal form
Evan Chengb783fa32007-07-19 01:14:50 +0000571let OutOperandList = (ops GPRC:$RA), InOperandList = (ops s64imm:$DISP, GPRC:$RB) in
Chris Lattneref8d6082008-01-06 06:44:58 +0000572def LDQl : MForm<0x29, 1, "ldq $RA,$DISP($RB)\t\t!literal",
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000573 [(set GPRC:$RA, (Alpha_rellit tglobaladdr:$DISP, GPRC:$RB))], s_ild>;
574def : Pat<(Alpha_rellit texternalsym:$ext, GPRC:$RB),
575 (LDQl texternalsym:$ext, GPRC:$RB)>;
576
Andrew Lenharthe44f3902008-02-21 06:45:13 +0000577let OutOperandList = (outs GPRC:$RR),
578 InOperandList = (ins GPRC:$RA, s64imm:$DISP, GPRC:$RB),
579 Constraints = "$RA = $RR",
580 DisableEncoding = "$RR" in {
581def STQ_C : MForm<0x2F, 0, "stq_l $RA,$DISP($RB)", [], s_ist>;
582def STL_C : MForm<0x2E, 0, "stl_l $RA,$DISP($RB)", [], s_ist>;
583}
584let OutOperandList = (ops GPRC:$RA), InOperandList = (ops s64imm:$DISP, GPRC:$RB) in {
585def LDQ_L : MForm<0x2B, 1, "ldq_l $RA,$DISP($RB)", [], s_ild>;
586def LDL_L : MForm<0x2A, 1, "ldl_l $RA,$DISP($RB)", [], s_ild>;
587}
588
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000589def RPCC : MfcForm<0x18, 0xC000, "rpcc $RA", s_rpcc>; //Read process cycle counter
Andrew Lenharth785610d2008-02-16 01:24:58 +0000590def MB : MfcPForm<0x18, 0x4000, "mb", s_imisc>; //memory barrier
591def WMB : MfcPForm<0x18, 0x4400, "wmb", s_imisc>; //write memory barrier
592
593def : Pat<(membarrier (i64 imm:$ll), (i64 imm:$ls), (i64 imm:$sl), (i64 1), (i64 imm:$dev)),
594 (WMB)>;
595def : Pat<(membarrier (i64 imm:$ll), (i64 imm:$ls), (i64 imm:$sl), (i64 imm:$ss), (i64 imm:$dev)),
596 (MB)>;
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000597
598//Basic Floating point ops
599
600//Floats
601
Evan Chengb783fa32007-07-19 01:14:50 +0000602let OutOperandList = (ops F4RC:$RC), InOperandList = (ops F4RC:$RB), Fa = 31 in
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000603def SQRTS : FPForm<0x14, 0x58B, "sqrts/su $RB,$RC",
604 [(set F4RC:$RC, (fsqrt F4RC:$RB))], s_fsqrts>;
605
Evan Chengb783fa32007-07-19 01:14:50 +0000606let OutOperandList = (ops F4RC:$RC), InOperandList = (ops F4RC:$RA, F4RC:$RB) in {
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000607def ADDS : FPForm<0x16, 0x580, "adds/su $RA,$RB,$RC",
608 [(set F4RC:$RC, (fadd F4RC:$RA, F4RC:$RB))], s_fadd>;
609def SUBS : FPForm<0x16, 0x581, "subs/su $RA,$RB,$RC",
610 [(set F4RC:$RC, (fsub F4RC:$RA, F4RC:$RB))], s_fadd>;
611def DIVS : FPForm<0x16, 0x583, "divs/su $RA,$RB,$RC",
612 [(set F4RC:$RC, (fdiv F4RC:$RA, F4RC:$RB))], s_fdivs>;
613def MULS : FPForm<0x16, 0x582, "muls/su $RA,$RB,$RC",
614 [(set F4RC:$RC, (fmul F4RC:$RA, F4RC:$RB))], s_fmul>;
615
616def CPYSS : FPForm<0x17, 0x020, "cpys $RA,$RB,$RC",
617 [(set F4RC:$RC, (fcopysign F4RC:$RB, F4RC:$RA))], s_fadd>;
618def CPYSES : FPForm<0x17, 0x022, "cpyse $RA,$RB,$RC",[], s_fadd>; //Copy sign and exponent
619def CPYSNS : FPForm<0x17, 0x021, "cpysn $RA,$RB,$RC",
620 [(set F4RC:$RC, (fneg (fcopysign F4RC:$RB, F4RC:$RA)))], s_fadd>;
621}
622
623//Doubles
624
Evan Chengb783fa32007-07-19 01:14:50 +0000625let OutOperandList = (ops F8RC:$RC), InOperandList = (ops F8RC:$RB), Fa = 31 in
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000626def SQRTT : FPForm<0x14, 0x5AB, "sqrtt/su $RB,$RC",
627 [(set F8RC:$RC, (fsqrt F8RC:$RB))], s_fsqrtt>;
628
Evan Chengb783fa32007-07-19 01:14:50 +0000629let OutOperandList = (ops F8RC:$RC), InOperandList = (ops F8RC:$RA, F8RC:$RB) in {
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000630def ADDT : FPForm<0x16, 0x5A0, "addt/su $RA,$RB,$RC",
631 [(set F8RC:$RC, (fadd F8RC:$RA, F8RC:$RB))], s_fadd>;
632def SUBT : FPForm<0x16, 0x5A1, "subt/su $RA,$RB,$RC",
633 [(set F8RC:$RC, (fsub F8RC:$RA, F8RC:$RB))], s_fadd>;
634def DIVT : FPForm<0x16, 0x5A3, "divt/su $RA,$RB,$RC",
635 [(set F8RC:$RC, (fdiv F8RC:$RA, F8RC:$RB))], s_fdivt>;
636def MULT : FPForm<0x16, 0x5A2, "mult/su $RA,$RB,$RC",
637 [(set F8RC:$RC, (fmul F8RC:$RA, F8RC:$RB))], s_fmul>;
638
639def CPYST : FPForm<0x17, 0x020, "cpys $RA,$RB,$RC",
640 [(set F8RC:$RC, (fcopysign F8RC:$RB, F8RC:$RA))], s_fadd>;
641def CPYSET : FPForm<0x17, 0x022, "cpyse $RA,$RB,$RC",[], s_fadd>; //Copy sign and exponent
642def CPYSNT : FPForm<0x17, 0x021, "cpysn $RA,$RB,$RC",
643 [(set F8RC:$RC, (fneg (fcopysign F8RC:$RB, F8RC:$RA)))], s_fadd>;
644
645def CMPTEQ : FPForm<0x16, 0x5A5, "cmpteq/su $RA,$RB,$RC", [], s_fadd>;
646// [(set F8RC:$RC, (seteq F8RC:$RA, F8RC:$RB))]>;
647def CMPTLE : FPForm<0x16, 0x5A7, "cmptle/su $RA,$RB,$RC", [], s_fadd>;
648// [(set F8RC:$RC, (setle F8RC:$RA, F8RC:$RB))]>;
649def CMPTLT : FPForm<0x16, 0x5A6, "cmptlt/su $RA,$RB,$RC", [], s_fadd>;
650// [(set F8RC:$RC, (setlt F8RC:$RA, F8RC:$RB))]>;
651def CMPTUN : FPForm<0x16, 0x5A4, "cmptun/su $RA,$RB,$RC", [], s_fadd>;
652// [(set F8RC:$RC, (setuo F8RC:$RA, F8RC:$RB))]>;
653}
654
655//More CPYS forms:
Evan Chengb783fa32007-07-19 01:14:50 +0000656let OutOperandList = (ops F8RC:$RC), InOperandList = (ops F4RC:$RA, F8RC:$RB) in {
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000657def CPYSTs : FPForm<0x17, 0x020, "cpys $RA,$RB,$RC",
658 [(set F8RC:$RC, (fcopysign F8RC:$RB, F4RC:$RA))], s_fadd>;
659def CPYSNTs : FPForm<0x17, 0x021, "cpysn $RA,$RB,$RC",
660 [(set F8RC:$RC, (fneg (fcopysign F8RC:$RB, F4RC:$RA)))], s_fadd>;
661}
Evan Chengb783fa32007-07-19 01:14:50 +0000662let OutOperandList = (ops F4RC:$RC), InOperandList = (ops F8RC:$RA, F4RC:$RB) in {
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000663def CPYSSt : FPForm<0x17, 0x020, "cpys $RA,$RB,$RC",
664 [(set F4RC:$RC, (fcopysign F4RC:$RB, F8RC:$RA))], s_fadd>;
665def CPYSESt : FPForm<0x17, 0x022, "cpyse $RA,$RB,$RC",[], s_fadd>; //Copy sign and exponent
666def CPYSNSt : FPForm<0x17, 0x021, "cpysn $RA,$RB,$RC",
667 [(set F4RC:$RC, (fneg (fcopysign F4RC:$RB, F8RC:$RA)))], s_fadd>;
668}
669
670//conditional moves, floats
Evan Chengb783fa32007-07-19 01:14:50 +0000671let OutOperandList = (ops F4RC:$RDEST), InOperandList = (ops F4RC:$RFALSE, F4RC:$RTRUE, F8RC:$RCOND),
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000672 isTwoAddress = 1 in {
673def FCMOVEQS : FPForm<0x17, 0x02A, "fcmoveq $RCOND,$RTRUE,$RDEST",[], s_fcmov>; //FCMOVE if = zero
674def FCMOVGES : FPForm<0x17, 0x02D, "fcmovge $RCOND,$RTRUE,$RDEST",[], s_fcmov>; //FCMOVE if >= zero
675def FCMOVGTS : FPForm<0x17, 0x02F, "fcmovgt $RCOND,$RTRUE,$RDEST",[], s_fcmov>; //FCMOVE if > zero
676def FCMOVLES : FPForm<0x17, 0x02E, "fcmovle $RCOND,$RTRUE,$RDEST",[], s_fcmov>; //FCMOVE if <= zero
677def FCMOVLTS : FPForm<0x17, 0x02C, "fcmovlt $RCOND,$RTRUE,$RDEST",[], s_fcmov>; // FCMOVE if < zero
678def FCMOVNES : FPForm<0x17, 0x02B, "fcmovne $RCOND,$RTRUE,$RDEST",[], s_fcmov>; //FCMOVE if != zero
679}
680//conditional moves, doubles
Evan Chengb783fa32007-07-19 01:14:50 +0000681let OutOperandList = (ops F8RC:$RDEST), InOperandList = (ops F8RC:$RFALSE, F8RC:$RTRUE, F8RC:$RCOND),
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000682 isTwoAddress = 1 in {
683def FCMOVEQT : FPForm<0x17, 0x02A, "fcmoveq $RCOND,$RTRUE,$RDEST", [], s_fcmov>;
684def FCMOVGET : FPForm<0x17, 0x02D, "fcmovge $RCOND,$RTRUE,$RDEST", [], s_fcmov>;
685def FCMOVGTT : FPForm<0x17, 0x02F, "fcmovgt $RCOND,$RTRUE,$RDEST", [], s_fcmov>;
686def FCMOVLET : FPForm<0x17, 0x02E, "fcmovle $RCOND,$RTRUE,$RDEST", [], s_fcmov>;
687def FCMOVLTT : FPForm<0x17, 0x02C, "fcmovlt $RCOND,$RTRUE,$RDEST", [], s_fcmov>;
688def FCMOVNET : FPForm<0x17, 0x02B, "fcmovne $RCOND,$RTRUE,$RDEST", [], s_fcmov>;
689}
690
691//misc FP selects
692//Select double
693
694def : Pat<(select (seteq F8RC:$RA, F8RC:$RB), F8RC:$st, F8RC:$sf),
695 (FCMOVNET F8RC:$sf, F8RC:$st, (CMPTEQ F8RC:$RA, F8RC:$RB))>;
696def : Pat<(select (setoeq F8RC:$RA, F8RC:$RB), F8RC:$st, F8RC:$sf),
697 (FCMOVNET F8RC:$sf, F8RC:$st, (CMPTEQ F8RC:$RA, F8RC:$RB))>;
698def : Pat<(select (setueq F8RC:$RA, F8RC:$RB), F8RC:$st, F8RC:$sf),
699 (FCMOVNET F8RC:$sf, F8RC:$st, (CMPTEQ F8RC:$RA, F8RC:$RB))>;
700
701def : Pat<(select (setne F8RC:$RA, F8RC:$RB), F8RC:$st, F8RC:$sf),
702 (FCMOVEQT F8RC:$sf, F8RC:$st, (CMPTEQ F8RC:$RA, F8RC:$RB))>;
703def : Pat<(select (setone F8RC:$RA, F8RC:$RB), F8RC:$st, F8RC:$sf),
704 (FCMOVEQT F8RC:$sf, F8RC:$st, (CMPTEQ F8RC:$RA, F8RC:$RB))>;
705def : Pat<(select (setune F8RC:$RA, F8RC:$RB), F8RC:$st, F8RC:$sf),
706 (FCMOVEQT F8RC:$sf, F8RC:$st, (CMPTEQ F8RC:$RA, F8RC:$RB))>;
707
708def : Pat<(select (setgt F8RC:$RA, F8RC:$RB), F8RC:$st, F8RC:$sf),
709 (FCMOVNET F8RC:$sf, F8RC:$st, (CMPTLT F8RC:$RB, F8RC:$RA))>;
710def : Pat<(select (setogt F8RC:$RA, F8RC:$RB), F8RC:$st, F8RC:$sf),
711 (FCMOVNET F8RC:$sf, F8RC:$st, (CMPTLT F8RC:$RB, F8RC:$RA))>;
712def : Pat<(select (setugt F8RC:$RA, F8RC:$RB), F8RC:$st, F8RC:$sf),
713 (FCMOVNET F8RC:$sf, F8RC:$st, (CMPTLT F8RC:$RB, F8RC:$RA))>;
714
715def : Pat<(select (setge F8RC:$RA, F8RC:$RB), F8RC:$st, F8RC:$sf),
716 (FCMOVNET F8RC:$sf, F8RC:$st, (CMPTLE F8RC:$RB, F8RC:$RA))>;
717def : Pat<(select (setoge F8RC:$RA, F8RC:$RB), F8RC:$st, F8RC:$sf),
718 (FCMOVNET F8RC:$sf, F8RC:$st, (CMPTLE F8RC:$RB, F8RC:$RA))>;
719def : Pat<(select (setuge F8RC:$RA, F8RC:$RB), F8RC:$st, F8RC:$sf),
720 (FCMOVNET F8RC:$sf, F8RC:$st, (CMPTLE F8RC:$RB, F8RC:$RA))>;
721
722def : Pat<(select (setlt F8RC:$RA, F8RC:$RB), F8RC:$st, F8RC:$sf),
723 (FCMOVNET F8RC:$sf, F8RC:$st, (CMPTLT F8RC:$RA, F8RC:$RB))>;
724def : Pat<(select (setolt F8RC:$RA, F8RC:$RB), F8RC:$st, F8RC:$sf),
725 (FCMOVNET F8RC:$sf, F8RC:$st, (CMPTLT F8RC:$RA, F8RC:$RB))>;
726def : Pat<(select (setult F8RC:$RA, F8RC:$RB), F8RC:$st, F8RC:$sf),
727 (FCMOVNET F8RC:$sf, F8RC:$st, (CMPTLT F8RC:$RA, F8RC:$RB))>;
728
729def : Pat<(select (setle F8RC:$RA, F8RC:$RB), F8RC:$st, F8RC:$sf),
730 (FCMOVNET F8RC:$sf, F8RC:$st, (CMPTLE F8RC:$RA, F8RC:$RB))>;
731def : Pat<(select (setole F8RC:$RA, F8RC:$RB), F8RC:$st, F8RC:$sf),
732 (FCMOVNET F8RC:$sf, F8RC:$st, (CMPTLE F8RC:$RA, F8RC:$RB))>;
733def : Pat<(select (setule F8RC:$RA, F8RC:$RB), F8RC:$st, F8RC:$sf),
734 (FCMOVNET F8RC:$sf, F8RC:$st, (CMPTLE F8RC:$RA, F8RC:$RB))>;
735
736//Select single
737def : Pat<(select (seteq F8RC:$RA, F8RC:$RB), F4RC:$st, F4RC:$sf),
738 (FCMOVNES F4RC:$sf, F4RC:$st, (CMPTEQ F8RC:$RA, F8RC:$RB))>;
739def : Pat<(select (setoeq F8RC:$RA, F8RC:$RB), F4RC:$st, F4RC:$sf),
740 (FCMOVNES F4RC:$sf, F4RC:$st, (CMPTEQ F8RC:$RA, F8RC:$RB))>;
741def : Pat<(select (setueq F8RC:$RA, F8RC:$RB), F4RC:$st, F4RC:$sf),
742 (FCMOVNES F4RC:$sf, F4RC:$st, (CMPTEQ F8RC:$RA, F8RC:$RB))>;
743
744def : Pat<(select (setne F8RC:$RA, F8RC:$RB), F4RC:$st, F4RC:$sf),
745 (FCMOVEQS F4RC:$sf, F4RC:$st, (CMPTEQ F8RC:$RA, F8RC:$RB))>;
746def : Pat<(select (setone F8RC:$RA, F8RC:$RB), F4RC:$st, F4RC:$sf),
747 (FCMOVEQS F4RC:$sf, F4RC:$st, (CMPTEQ F8RC:$RA, F8RC:$RB))>;
748def : Pat<(select (setune F8RC:$RA, F8RC:$RB), F4RC:$st, F4RC:$sf),
749 (FCMOVEQS F4RC:$sf, F4RC:$st, (CMPTEQ F8RC:$RA, F8RC:$RB))>;
750
751def : Pat<(select (setgt F8RC:$RA, F8RC:$RB), F4RC:$st, F4RC:$sf),
752 (FCMOVNES F4RC:$sf, F4RC:$st, (CMPTLT F8RC:$RB, F8RC:$RA))>;
753def : Pat<(select (setogt F8RC:$RA, F8RC:$RB), F4RC:$st, F4RC:$sf),
754 (FCMOVNES F4RC:$sf, F4RC:$st, (CMPTLT F8RC:$RB, F8RC:$RA))>;
755def : Pat<(select (setugt F8RC:$RA, F8RC:$RB), F4RC:$st, F4RC:$sf),
756 (FCMOVNES F4RC:$sf, F4RC:$st, (CMPTLT F8RC:$RB, F8RC:$RA))>;
757
758def : Pat<(select (setge F8RC:$RA, F8RC:$RB), F4RC:$st, F4RC:$sf),
759 (FCMOVNES F4RC:$sf, F4RC:$st, (CMPTLE F8RC:$RB, F8RC:$RA))>;
760def : Pat<(select (setoge F8RC:$RA, F8RC:$RB), F4RC:$st, F4RC:$sf),
761 (FCMOVNES F4RC:$sf, F4RC:$st, (CMPTLE F8RC:$RB, F8RC:$RA))>;
762def : Pat<(select (setuge F8RC:$RA, F8RC:$RB), F4RC:$st, F4RC:$sf),
763 (FCMOVNES F4RC:$sf, F4RC:$st, (CMPTLE F8RC:$RB, F8RC:$RA))>;
764
765def : Pat<(select (setlt F8RC:$RA, F8RC:$RB), F4RC:$st, F4RC:$sf),
766 (FCMOVNES F4RC:$sf, F4RC:$st, (CMPTLT F8RC:$RA, F8RC:$RB))>;
767def : Pat<(select (setolt F8RC:$RA, F8RC:$RB), F4RC:$st, F4RC:$sf),
768 (FCMOVNES F4RC:$sf, F4RC:$st, (CMPTLT F8RC:$RA, F8RC:$RB))>;
769def : Pat<(select (setult F8RC:$RA, F8RC:$RB), F4RC:$st, F4RC:$sf),
770 (FCMOVNES F4RC:$sf, F4RC:$st, (CMPTLT F8RC:$RA, F8RC:$RB))>;
771
772def : Pat<(select (setle F8RC:$RA, F8RC:$RB), F4RC:$st, F4RC:$sf),
773 (FCMOVNES F4RC:$sf, F4RC:$st, (CMPTLE F8RC:$RA, F8RC:$RB))>;
774def : Pat<(select (setole F8RC:$RA, F8RC:$RB), F4RC:$st, F4RC:$sf),
775 (FCMOVNES F4RC:$sf, F4RC:$st, (CMPTLE F8RC:$RA, F8RC:$RB))>;
776def : Pat<(select (setule F8RC:$RA, F8RC:$RB), F4RC:$st, F4RC:$sf),
777 (FCMOVNES F4RC:$sf, F4RC:$st, (CMPTLE F8RC:$RA, F8RC:$RB))>;
778
779
780
Evan Chengb783fa32007-07-19 01:14:50 +0000781let OutOperandList = (ops GPRC:$RC), InOperandList = (ops F4RC:$RA), Fb = 31 in
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000782def FTOIS : FPForm<0x1C, 0x078, "ftois $RA,$RC",[], s_ftoi>; //Floating to integer move, S_floating
Evan Chengb783fa32007-07-19 01:14:50 +0000783let OutOperandList = (ops GPRC:$RC), InOperandList = (ops F8RC:$RA), Fb = 31 in
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000784def FTOIT : FPForm<0x1C, 0x070, "ftoit $RA,$RC",
785 [(set GPRC:$RC, (bitconvert F8RC:$RA))], s_ftoi>; //Floating to integer move
Evan Chengb783fa32007-07-19 01:14:50 +0000786let OutOperandList = (ops F4RC:$RC), InOperandList = (ops GPRC:$RA), Fb = 31 in
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000787def ITOFS : FPForm<0x14, 0x004, "itofs $RA,$RC",[], s_itof>; //Integer to floating move, S_floating
Evan Chengb783fa32007-07-19 01:14:50 +0000788let OutOperandList = (ops F8RC:$RC), InOperandList = (ops GPRC:$RA), Fb = 31 in
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000789def ITOFT : FPForm<0x14, 0x024, "itoft $RA,$RC",
790 [(set F8RC:$RC, (bitconvert GPRC:$RA))], s_itof>; //Integer to floating move
791
792
Evan Chengb783fa32007-07-19 01:14:50 +0000793let OutOperandList = (ops F4RC:$RC), InOperandList = (ops F8RC:$RB), Fa = 31 in
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000794def CVTQS : FPForm<0x16, 0x7BC, "cvtqs/sui $RB,$RC",
795 [(set F4RC:$RC, (Alpha_cvtqs F8RC:$RB))], s_fadd>;
Evan Chengb783fa32007-07-19 01:14:50 +0000796let OutOperandList = (ops F8RC:$RC), InOperandList = (ops F8RC:$RB), Fa = 31 in
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000797def CVTQT : FPForm<0x16, 0x7BE, "cvtqt/sui $RB,$RC",
798 [(set F8RC:$RC, (Alpha_cvtqt F8RC:$RB))], s_fadd>;
Evan Chengb783fa32007-07-19 01:14:50 +0000799let OutOperandList = (ops F8RC:$RC), InOperandList = (ops F8RC:$RB), Fa = 31 in
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000800def CVTTQ : FPForm<0x16, 0x52F, "cvttq/svc $RB,$RC",
801 [(set F8RC:$RC, (Alpha_cvttq F8RC:$RB))], s_fadd>;
Evan Chengb783fa32007-07-19 01:14:50 +0000802let OutOperandList = (ops F8RC:$RC), InOperandList = (ops F4RC:$RB), Fa = 31 in
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000803def CVTST : FPForm<0x16, 0x6AC, "cvtst/s $RB,$RC",
804 [(set F8RC:$RC, (fextend F4RC:$RB))], s_fadd>;
Evan Chengb783fa32007-07-19 01:14:50 +0000805let OutOperandList = (ops F4RC:$RC), InOperandList = (ops F8RC:$RB), Fa = 31 in
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000806def CVTTS : FPForm<0x16, 0x7AC, "cvtts/sui $RB,$RC",
807 [(set F4RC:$RC, (fround F8RC:$RB))], s_fadd>;
808
809
810/////////////////////////////////////////////////////////
811//Branching
812/////////////////////////////////////////////////////////
813class br_icc<bits<6> opc, string asmstr>
814 : BFormN<opc, (ops u64imm:$opc, GPRC:$R, target:$dst),
815 !strconcat(asmstr, " $R,$dst"), s_icbr>;
816class br_fcc<bits<6> opc, string asmstr>
817 : BFormN<opc, (ops u64imm:$opc, F8RC:$R, target:$dst),
818 !strconcat(asmstr, " $R,$dst"), s_fbr>;
819
Evan Cheng37e7c752007-07-21 00:34:19 +0000820let isBranch = 1, isTerminator = 1, hasCtrlDep = 1 in {
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000821let Ra = 31 in
822def BR : BFormD<0x30, "br $$31,$DISP", [(br bb:$DISP)], s_ubr>;
823
824def COND_BRANCH_I : BFormN<0, (ops u64imm:$opc, GPRC:$R, target:$dst),
825 "{:comment} COND_BRANCH imm:$opc, GPRC:$R, bb:$dst",
826 s_icbr>;
827def COND_BRANCH_F : BFormN<0, (ops u64imm:$opc, F8RC:$R, target:$dst),
828 "{:comment} COND_BRANCH imm:$opc, F8RC:$R, bb:$dst",
829 s_fbr>;
830//Branches, int
831def BEQ : br_icc<0x39, "beq">;
832def BGE : br_icc<0x3E, "bge">;
833def BGT : br_icc<0x3F, "bgt">;
834def BLBC : br_icc<0x38, "blbc">;
835def BLBS : br_icc<0x3C, "blbs">;
836def BLE : br_icc<0x3B, "ble">;
837def BLT : br_icc<0x3A, "blt">;
838def BNE : br_icc<0x3D, "bne">;
839
840//Branches, float
841def FBEQ : br_fcc<0x31, "fbeq">;
842def FBGE : br_fcc<0x36, "fbge">;
843def FBGT : br_fcc<0x37, "fbgt">;
844def FBLE : br_fcc<0x33, "fble">;
845def FBLT : br_fcc<0x32, "fblt">;
846def FBNE : br_fcc<0x36, "fbne">;
847}
848
849//An ugly trick to get the opcode as an imm I can use
850def immBRCond : SDNodeXForm<imm, [{
851 switch((uint64_t)N->getValue()) {
852 case 0: return getI64Imm(Alpha::BEQ);
853 case 1: return getI64Imm(Alpha::BNE);
854 case 2: return getI64Imm(Alpha::BGE);
855 case 3: return getI64Imm(Alpha::BGT);
856 case 4: return getI64Imm(Alpha::BLE);
857 case 5: return getI64Imm(Alpha::BLT);
858 case 6: return getI64Imm(Alpha::BLBS);
859 case 7: return getI64Imm(Alpha::BLBC);
860 case 20: return getI64Imm(Alpha::FBEQ);
861 case 21: return getI64Imm(Alpha::FBNE);
862 case 22: return getI64Imm(Alpha::FBGE);
863 case 23: return getI64Imm(Alpha::FBGT);
864 case 24: return getI64Imm(Alpha::FBLE);
865 case 25: return getI64Imm(Alpha::FBLT);
866 default: assert(0 && "Unknown branch type");
867 }
868}]>;
869
870//Int cond patterns
871def : Pat<(brcond (seteq GPRC:$RA, 0), bb:$DISP),
872 (COND_BRANCH_I (immBRCond 0), GPRC:$RA, bb:$DISP)>;
873def : Pat<(brcond (setge GPRC:$RA, 0), bb:$DISP),
874 (COND_BRANCH_I (immBRCond 2), GPRC:$RA, bb:$DISP)>;
875def : Pat<(brcond (setgt GPRC:$RA, 0), bb:$DISP),
876 (COND_BRANCH_I (immBRCond 3), GPRC:$RA, bb:$DISP)>;
877def : Pat<(brcond (and GPRC:$RA, 1), bb:$DISP),
878 (COND_BRANCH_I (immBRCond 6), GPRC:$RA, bb:$DISP)>;
879def : Pat<(brcond (setle GPRC:$RA, 0), bb:$DISP),
880 (COND_BRANCH_I (immBRCond 4), GPRC:$RA, bb:$DISP)>;
881def : Pat<(brcond (setlt GPRC:$RA, 0), bb:$DISP),
882 (COND_BRANCH_I (immBRCond 5), GPRC:$RA, bb:$DISP)>;
883def : Pat<(brcond (setne GPRC:$RA, 0), bb:$DISP),
884 (COND_BRANCH_I (immBRCond 1), GPRC:$RA, bb:$DISP)>;
885
886def : Pat<(brcond GPRC:$RA, bb:$DISP),
887 (COND_BRANCH_I (immBRCond 1), GPRC:$RA, bb:$DISP)>;
888def : Pat<(brcond (setne GPRC:$RA, GPRC:$RB), bb:$DISP),
889 (COND_BRANCH_I (immBRCond 0), (CMPEQ GPRC:$RA, GPRC:$RB), bb:$DISP)>;
890def : Pat<(brcond (setne GPRC:$RA, immUExt8:$L), bb:$DISP),
891 (COND_BRANCH_I (immBRCond 0), (CMPEQi GPRC:$RA, immUExt8:$L), bb:$DISP)>;
892
893//FP cond patterns
894def : Pat<(brcond (seteq F8RC:$RA, immFPZ), bb:$DISP),
895 (COND_BRANCH_F (immBRCond 20), F8RC:$RA, bb:$DISP)>;
896def : Pat<(brcond (setne F8RC:$RA, immFPZ), bb:$DISP),
897 (COND_BRANCH_F (immBRCond 21), F8RC:$RA, bb:$DISP)>;
898def : Pat<(brcond (setge F8RC:$RA, immFPZ), bb:$DISP),
899 (COND_BRANCH_F (immBRCond 22), F8RC:$RA, bb:$DISP)>;
900def : Pat<(brcond (setgt F8RC:$RA, immFPZ), bb:$DISP),
901 (COND_BRANCH_F (immBRCond 23), F8RC:$RA, bb:$DISP)>;
902def : Pat<(brcond (setle F8RC:$RA, immFPZ), bb:$DISP),
903 (COND_BRANCH_F (immBRCond 24), F8RC:$RA, bb:$DISP)>;
904def : Pat<(brcond (setlt F8RC:$RA, immFPZ), bb:$DISP),
905 (COND_BRANCH_F (immBRCond 25), F8RC:$RA, bb:$DISP)>;
906
907
908def : Pat<(brcond (seteq F8RC:$RA, F8RC:$RB), bb:$DISP),
909 (COND_BRANCH_F (immBRCond 21), (CMPTEQ F8RC:$RA, F8RC:$RB), bb:$DISP)>;
910def : Pat<(brcond (setoeq F8RC:$RA, F8RC:$RB), bb:$DISP),
911 (COND_BRANCH_F (immBRCond 21), (CMPTEQ F8RC:$RA, F8RC:$RB), bb:$DISP)>;
912def : Pat<(brcond (setueq F8RC:$RA, F8RC:$RB), bb:$DISP),
913 (COND_BRANCH_F (immBRCond 21), (CMPTEQ F8RC:$RA, F8RC:$RB), bb:$DISP)>;
914
915def : Pat<(brcond (setlt F8RC:$RA, F8RC:$RB), bb:$DISP),
916 (COND_BRANCH_F (immBRCond 21), (CMPTLT F8RC:$RA, F8RC:$RB), bb:$DISP)>;
917def : Pat<(brcond (setolt F8RC:$RA, F8RC:$RB), bb:$DISP),
918 (COND_BRANCH_F (immBRCond 21), (CMPTLT F8RC:$RA, F8RC:$RB), bb:$DISP)>;
919def : Pat<(brcond (setult F8RC:$RA, F8RC:$RB), bb:$DISP),
920 (COND_BRANCH_F (immBRCond 21), (CMPTLT F8RC:$RA, F8RC:$RB), bb:$DISP)>;
921
922def : Pat<(brcond (setle F8RC:$RA, F8RC:$RB), bb:$DISP),
923 (COND_BRANCH_F (immBRCond 21), (CMPTLE F8RC:$RA, F8RC:$RB), bb:$DISP)>;
924def : Pat<(brcond (setole F8RC:$RA, F8RC:$RB), bb:$DISP),
925 (COND_BRANCH_F (immBRCond 21), (CMPTLE F8RC:$RA, F8RC:$RB), bb:$DISP)>;
926def : Pat<(brcond (setule F8RC:$RA, F8RC:$RB), bb:$DISP),
927 (COND_BRANCH_F (immBRCond 21), (CMPTLE F8RC:$RA, F8RC:$RB), bb:$DISP)>;
928
929def : Pat<(brcond (setgt F8RC:$RA, F8RC:$RB), bb:$DISP),
930 (COND_BRANCH_F (immBRCond 21), (CMPTLT F8RC:$RB, F8RC:$RA), bb:$DISP)>;
931def : Pat<(brcond (setogt F8RC:$RA, F8RC:$RB), bb:$DISP),
932 (COND_BRANCH_F (immBRCond 21), (CMPTLT F8RC:$RB, F8RC:$RA), bb:$DISP)>;
933def : Pat<(brcond (setugt F8RC:$RA, F8RC:$RB), bb:$DISP),
934 (COND_BRANCH_F (immBRCond 21), (CMPTLT F8RC:$RB, F8RC:$RA), bb:$DISP)>;
935
936def : Pat<(brcond (setge F8RC:$RA, F8RC:$RB), bb:$DISP),
937 (COND_BRANCH_F (immBRCond 21), (CMPTLE F8RC:$RB, F8RC:$RA), bb:$DISP)>;
938def : Pat<(brcond (setoge F8RC:$RA, F8RC:$RB), bb:$DISP),
939 (COND_BRANCH_F (immBRCond 21), (CMPTLE F8RC:$RB, F8RC:$RA), bb:$DISP)>;
940def : Pat<(brcond (setuge F8RC:$RA, F8RC:$RB), bb:$DISP),
941 (COND_BRANCH_F (immBRCond 21), (CMPTLE F8RC:$RB, F8RC:$RA), bb:$DISP)>;
942
943def : Pat<(brcond (setne F8RC:$RA, F8RC:$RB), bb:$DISP),
944 (COND_BRANCH_F (immBRCond 20), (CMPTEQ F8RC:$RA, F8RC:$RB), bb:$DISP)>;
945def : Pat<(brcond (setone F8RC:$RA, F8RC:$RB), bb:$DISP),
946 (COND_BRANCH_F (immBRCond 20), (CMPTEQ F8RC:$RA, F8RC:$RB), bb:$DISP)>;
947def : Pat<(brcond (setune F8RC:$RA, F8RC:$RB), bb:$DISP),
948 (COND_BRANCH_F (immBRCond 20), (CMPTEQ F8RC:$RA, F8RC:$RB), bb:$DISP)>;
949
950
951def : Pat<(brcond (setoeq F8RC:$RA, immFPZ), bb:$DISP),
952 (COND_BRANCH_F (immBRCond 20), F8RC:$RA,bb:$DISP)>;
953def : Pat<(brcond (setueq F8RC:$RA, immFPZ), bb:$DISP),
954 (COND_BRANCH_F (immBRCond 20), F8RC:$RA,bb:$DISP)>;
955
956def : Pat<(brcond (setoge F8RC:$RA, immFPZ), bb:$DISP),
957 (COND_BRANCH_F (immBRCond 22), F8RC:$RA,bb:$DISP)>;
958def : Pat<(brcond (setuge F8RC:$RA, immFPZ), bb:$DISP),
959 (COND_BRANCH_F (immBRCond 22), F8RC:$RA,bb:$DISP)>;
960
961def : Pat<(brcond (setogt F8RC:$RA, immFPZ), bb:$DISP),
962 (COND_BRANCH_F (immBRCond 23), F8RC:$RA,bb:$DISP)>;
963def : Pat<(brcond (setugt F8RC:$RA, immFPZ), bb:$DISP),
964 (COND_BRANCH_F (immBRCond 23), F8RC:$RA,bb:$DISP)>;
965
966def : Pat<(brcond (setole F8RC:$RA, immFPZ), bb:$DISP),
967 (COND_BRANCH_F (immBRCond 24), F8RC:$RA,bb:$DISP)>;
968def : Pat<(brcond (setule F8RC:$RA, immFPZ), bb:$DISP),
969 (COND_BRANCH_F (immBRCond 24), F8RC:$RA,bb:$DISP)>;
970
971def : Pat<(brcond (setolt F8RC:$RA, immFPZ), bb:$DISP),
972 (COND_BRANCH_F (immBRCond 25), F8RC:$RA,bb:$DISP)>;
973def : Pat<(brcond (setult F8RC:$RA, immFPZ), bb:$DISP),
974 (COND_BRANCH_F (immBRCond 25), F8RC:$RA,bb:$DISP)>;
975
976def : Pat<(brcond (setone F8RC:$RA, immFPZ), bb:$DISP),
977 (COND_BRANCH_F (immBRCond 21), F8RC:$RA,bb:$DISP)>;
978def : Pat<(brcond (setune F8RC:$RA, immFPZ), bb:$DISP),
979 (COND_BRANCH_F (immBRCond 21), F8RC:$RA,bb:$DISP)>;
980
981//End Branches
982
983//S_floating : IEEE Single
984//T_floating : IEEE Double
985
986//Unused instructions
987//Mnemonic Format Opcode Description
988//CALL_PAL Pcd 00 Trap to PALcode
989//ECB Mfc 18.E800 Evict cache block
990//EXCB Mfc 18.0400 Exception barrier
991//FETCH Mfc 18.8000 Prefetch data
992//FETCH_M Mfc 18.A000 Prefetch data, modify intent
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000993//LDQ_U Mem 0B Load unaligned quadword
994//MB Mfc 18.4000 Memory barrier
Dan Gohmanf17a25c2007-07-18 16:29:46 +0000995//STQ_U Mem 0F Store unaligned quadword
996//TRAPB Mfc 18.0000 Trap barrier
997//WH64 Mfc 18.F800 Write hint  64 bytes
998//WMB Mfc 18.4400 Write memory barrier
999//MF_FPCR F-P 17.025 Move from FPCR
1000//MT_FPCR F-P 17.024 Move to FPCR
1001//There are in the Multimedia extentions, so let's not use them yet
1002//def MAXSB8 : OForm<0x1C, 0x3E, "MAXSB8 $RA,$RB,$RC">; //Vector signed byte maximum
1003//def MAXSW4 : OForm< 0x1C, 0x3F, "MAXSW4 $RA,$RB,$RC">; //Vector signed word maximum
1004//def MAXUB8 : OForm<0x1C, 0x3C, "MAXUB8 $RA,$RB,$RC">; //Vector unsigned byte maximum
1005//def MAXUW4 : OForm< 0x1C, 0x3D, "MAXUW4 $RA,$RB,$RC">; //Vector unsigned word maximum
1006//def MINSB8 : OForm< 0x1C, 0x38, "MINSB8 $RA,$RB,$RC">; //Vector signed byte minimum
1007//def MINSW4 : OForm< 0x1C, 0x39, "MINSW4 $RA,$RB,$RC">; //Vector signed word minimum
1008//def MINUB8 : OForm< 0x1C, 0x3A, "MINUB8 $RA,$RB,$RC">; //Vector unsigned byte minimum
1009//def MINUW4 : OForm< 0x1C, 0x3B, "MINUW4 $RA,$RB,$RC">; //Vector unsigned word minimum
1010//def PERR : OForm< 0x1C, 0x31, "PERR $RA,$RB,$RC">; //Pixel error
1011//def PKLB : OForm< 0x1C, 0x37, "PKLB $RA,$RB,$RC">; //Pack longwords to bytes
1012//def PKWB : OForm<0x1C, 0x36, "PKWB $RA,$RB,$RC">; //Pack words to bytes
1013//def UNPKBL : OForm< 0x1C, 0x35, "UNPKBL $RA,$RB,$RC">; //Unpack bytes to longwords
1014//def UNPKBW : OForm< 0x1C, 0x34, "UNPKBW $RA,$RB,$RC">; //Unpack bytes to words
1015//CVTLQ F-P 17.010 Convert longword to quadword
1016//CVTQL F-P 17.030 Convert quadword to longword
1017
1018
1019//Constant handling
1020
1021def immConst2Part : PatLeaf<(imm), [{
1022 //true if imm fits in a LDAH LDA pair
1023 int64_t val = (int64_t)N->getValue();
1024 return (val <= IMM_FULLHIGH && val >= IMM_FULLLOW);
1025}]>;
1026def immConst2PartInt : PatLeaf<(imm), [{
1027 //true if imm fits in a LDAH LDA pair with zeroext
1028 uint64_t uval = N->getValue();
1029 int32_t val32 = (int32_t)uval;
1030 return ((uval >> 32) == 0 && //empty upper bits
1031 val32 <= IMM_FULLHIGH);
1032// val32 >= IMM_FULLLOW + IMM_LOW * IMM_MULT); //Always True
1033}], SExt32>;
1034
1035def : Pat<(i64 immConst2Part:$imm),
1036 (LDA (LL16 immConst2Part:$imm), (LDAH (LH16 immConst2Part:$imm), R31))>;
1037
1038def : Pat<(i64 immSExt16:$imm),
1039 (LDA immSExt16:$imm, R31)>;
1040
1041def : Pat<(i64 immSExt16int:$imm),
1042 (ZAPNOTi (LDA (SExt16 immSExt16int:$imm), R31), 15)>;
1043def : Pat<(i64 immConst2PartInt:$imm),
1044 (ZAPNOTi (LDA (LL16 (SExt32 immConst2PartInt:$imm)),
1045 (LDAH (LH16 (SExt32 immConst2PartInt:$imm)), R31)), 15)>;
1046
1047
1048//TODO: I want to just define these like this!
1049//def : Pat<(i64 0),
1050// (R31)>;
1051//def : Pat<(f64 0.0),
1052// (F31)>;
1053//def : Pat<(f64 -0.0),
1054// (CPYSNT F31, F31)>;
1055//def : Pat<(f32 0.0),
1056// (F31)>;
1057//def : Pat<(f32 -0.0),
1058// (CPYSNS F31, F31)>;
1059
1060//Misc Patterns:
1061
1062def : Pat<(sext_inreg GPRC:$RB, i32),
1063 (ADDLi GPRC:$RB, 0)>;
1064
1065def : Pat<(fabs F8RC:$RB),
1066 (CPYST F31, F8RC:$RB)>;
1067def : Pat<(fabs F4RC:$RB),
1068 (CPYSS F31, F4RC:$RB)>;
1069def : Pat<(fneg F8RC:$RB),
1070 (CPYSNT F8RC:$RB, F8RC:$RB)>;
1071def : Pat<(fneg F4RC:$RB),
1072 (CPYSNS F4RC:$RB, F4RC:$RB)>;
1073
1074def : Pat<(fcopysign F4RC:$A, (fneg F4RC:$B)),
1075 (CPYSNS F4RC:$B, F4RC:$A)>;
1076def : Pat<(fcopysign F8RC:$A, (fneg F8RC:$B)),
1077 (CPYSNT F8RC:$B, F8RC:$A)>;
1078def : Pat<(fcopysign F4RC:$A, (fneg F8RC:$B)),
1079 (CPYSNSt F8RC:$B, F4RC:$A)>;
1080def : Pat<(fcopysign F8RC:$A, (fneg F4RC:$B)),
1081 (CPYSNTs F4RC:$B, F8RC:$A)>;
1082
1083//Yes, signed multiply high is ugly
1084def : Pat<(mulhs GPRC:$RA, GPRC:$RB),
1085 (SUBQr (UMULHr GPRC:$RA, GPRC:$RB), (ADDQr (CMOVGEr GPRC:$RB, R31, GPRC:$RA),
1086 (CMOVGEr GPRC:$RA, R31, GPRC:$RB)))>;
1087
1088//Stupid crazy arithmetic stuff:
1089let AddedComplexity = 1 in {
1090def : Pat<(mul GPRC:$RA, 5), (S4ADDQr GPRC:$RA, GPRC:$RA)>;
1091def : Pat<(mul GPRC:$RA, 9), (S8ADDQr GPRC:$RA, GPRC:$RA)>;
1092def : Pat<(mul GPRC:$RA, 3), (S4SUBQr GPRC:$RA, GPRC:$RA)>;
1093def : Pat<(mul GPRC:$RA, 7), (S8SUBQr GPRC:$RA, GPRC:$RA)>;
1094
1095//slight tree expansion if we are multiplying near to a power of 2
1096//n is above a power of 2
1097def : Pat<(mul GPRC:$RA, immRem1:$imm),
1098 (ADDQr (SLr GPRC:$RA, (nearP2X immRem1:$imm)), GPRC:$RA)>;
1099def : Pat<(mul GPRC:$RA, immRem2:$imm),
1100 (ADDQr (SLr GPRC:$RA, (nearP2X immRem2:$imm)), (ADDQr GPRC:$RA, GPRC:$RA))>;
1101def : Pat<(mul GPRC:$RA, immRem3:$imm),
1102 (ADDQr (SLr GPRC:$RA, (nearP2X immRem3:$imm)), (S4SUBQr GPRC:$RA, GPRC:$RA))>;
1103def : Pat<(mul GPRC:$RA, immRem4:$imm),
1104 (S4ADDQr GPRC:$RA, (SLr GPRC:$RA, (nearP2X immRem4:$imm)))>;
1105def : Pat<(mul GPRC:$RA, immRem5:$imm),
1106 (ADDQr (SLr GPRC:$RA, (nearP2X immRem5:$imm)), (S4ADDQr GPRC:$RA, GPRC:$RA))>;
1107def : Pat<(mul GPRC:$RA, immRemP2:$imm),
1108 (ADDQr (SLr GPRC:$RA, (nearP2X immRemP2:$imm)), (SLi GPRC:$RA, (nearP2RemX immRemP2:$imm)))>;
1109
1110//n is below a power of 2
Andrew Lenharthd0ac96e2007-11-27 18:31:30 +00001111//FIXME: figure out why something is truncating the imm to 32bits
1112// this will fix 2007-11-27-mulneg3
1113//def : Pat<(mul GPRC:$RA, immRem1n:$imm),
1114// (SUBQr (SLr GPRC:$RA, (nearP2X immRem1n:$imm)), GPRC:$RA)>;
1115//def : Pat<(mul GPRC:$RA, immRem2n:$imm),
1116// (SUBQr (SLr GPRC:$RA, (nearP2X immRem2n:$imm)), (ADDQr GPRC:$RA, GPRC:$RA))>;
1117//def : Pat<(mul GPRC:$RA, immRem3n:$imm),
1118// (SUBQr (SLr GPRC:$RA, (nearP2X immRem3n:$imm)), (S4SUBQr GPRC:$RA, GPRC:$RA))>;
1119//def : Pat<(mul GPRC:$RA, immRem4n:$imm),
1120// (SUBQr (SLr GPRC:$RA, (nearP2X immRem4n:$imm)), (SLi GPRC:$RA, 2))>;
1121//def : Pat<(mul GPRC:$RA, immRem5n:$imm),
1122// (SUBQr (SLr GPRC:$RA, (nearP2X immRem5n:$imm)), (S4ADDQr GPRC:$RA, GPRC:$RA))>;
1123//def : Pat<(mul GPRC:$RA, immRemP2n:$imm),
1124// (SUBQr (SLr GPRC:$RA, (nearP2X immRemP2n:$imm)), (SLi GPRC:$RA, (nearP2RemX immRemP2n:$imm)))>;
Dan Gohmanf17a25c2007-07-18 16:29:46 +00001125} //Added complexity