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