Home | History | Annotate | Download | only in Sparc
      1 //===-- SparcInstrAliases.td - Instruction Aliases for Sparc Target -------===//
      2 //
      3 //                     The LLVM Compiler Infrastructure
      4 //
      5 // This file is distributed under the University of Illinois Open Source
      6 // License. See LICENSE.TXT for details.
      7 //
      8 //===----------------------------------------------------------------------===//
      9 //
     10 // This file contains instruction aliases for Sparc.
     11 //===----------------------------------------------------------------------===//
     12 
     13 // Instruction aliases for conditional moves.
     14 
     15 // mov<cond> <ccreg> rs2, rd
     16 multiclass intcond_mov_alias<string cond, int condVal, string ccreg,
     17                           Instruction movrr, Instruction movri,
     18                           Instruction fmovs, Instruction fmovd> {
     19 
     20   // mov<cond> (%icc|%xcc), rs2, rd
     21   def : InstAlias<!strconcat(!strconcat(!strconcat("mov", cond), ccreg),
     22                              ", $rs2, $rd"),
     23                   (movrr IntRegs:$rd, IntRegs:$rs2, condVal)>;
     24 
     25   // mov<cond> (%icc|%xcc), simm11, rd
     26   def : InstAlias<!strconcat(!strconcat(!strconcat("mov", cond), ccreg),
     27                              ", $simm11, $rd"),
     28                   (movri IntRegs:$rd, i32imm:$simm11, condVal)>;
     29 
     30   // fmovs<cond> (%icc|%xcc), $rs2, $rd
     31   def : InstAlias<!strconcat(!strconcat(!strconcat("fmovs", cond), ccreg),
     32                              ", $rs2, $rd"),
     33                   (fmovs FPRegs:$rd, FPRegs:$rs2, condVal)>;
     34 
     35   // fmovd<cond> (%icc|%xcc), $rs2, $rd
     36   def : InstAlias<!strconcat(!strconcat(!strconcat("fmovd", cond), ccreg),
     37                              ", $rs2, $rd"),
     38                   (fmovd DFPRegs:$rd, DFPRegs:$rs2, condVal)>;
     39 }
     40 
     41 // mov<cond> <ccreg> rs2, rd
     42 multiclass fpcond_mov_alias<string cond, int condVal,
     43                            Instruction movrr, Instruction movri,
     44                            Instruction fmovs, Instruction fmovd> {
     45 
     46   // mov<cond> %fcc[0-3], rs2, rd
     47   def : InstAlias<!strconcat(!strconcat("mov", cond), " $cc, $rs2, $rd"),
     48                   (movrr IntRegs:$rd, FCCRegs:$cc, IntRegs:$rs2, condVal)>;
     49 
     50   // mov<cond> %fcc[0-3], simm11, rd
     51   def : InstAlias<!strconcat(!strconcat("mov", cond), " $cc, $simm11, $rd"),
     52                   (movri IntRegs:$rd, FCCRegs:$cc, i32imm:$simm11, condVal)>;
     53 
     54   // fmovs<cond> %fcc[0-3], $rs2, $rd
     55   def : InstAlias<!strconcat(!strconcat("fmovs", cond), " $cc, $rs2, $rd"),
     56                   (fmovs FPRegs:$rd, FCCRegs:$cc, FPRegs:$rs2, condVal)>;
     57 
     58   // fmovd<cond> %fcc[0-3], $rs2, $rd
     59   def : InstAlias<!strconcat(!strconcat("fmovd", cond), " $cc, $rs2, $rd"),
     60                   (fmovd DFPRegs:$rd, FCCRegs:$cc, DFPRegs:$rs2, condVal)>;
     61 }
     62 
     63 // Instruction aliases for integer conditional branches and moves.
     64 multiclass int_cond_alias<string cond, int condVal> {
     65 
     66   // b<cond> $imm
     67   def : InstAlias<!strconcat(!strconcat("b", cond), " $imm"),
     68                   (BCOND brtarget:$imm, condVal)>;
     69 
     70   // b<cond>,a $imm
     71   def : InstAlias<!strconcat(!strconcat("b", cond), ",a $imm"),
     72                   (BCONDA brtarget:$imm, condVal)>;
     73 
     74   // b<cond> %icc, $imm
     75   def : InstAlias<!strconcat(!strconcat("b", cond), " %icc, $imm"),
     76                   (BPICC brtarget:$imm, condVal)>, Requires<[HasV9]>;
     77 
     78   // b<cond>,pt %icc, $imm
     79   def : InstAlias<!strconcat(!strconcat("b", cond), ",pt %icc, $imm"),
     80                   (BPICC brtarget:$imm, condVal)>, Requires<[HasV9]>;
     81 
     82   // b<cond>,a %icc, $imm
     83   def : InstAlias<!strconcat(!strconcat("b", cond), ",a %icc, $imm"),
     84                   (BPICCA brtarget:$imm, condVal)>, Requires<[HasV9]>;
     85 
     86   // b<cond>,a,pt %icc, $imm
     87   def : InstAlias<!strconcat(!strconcat("b", cond), ",a,pt %icc, $imm"),
     88                   (BPICCA brtarget:$imm, condVal)>, Requires<[HasV9]>;
     89 
     90   // b<cond>,pn %icc, $imm
     91   def : InstAlias<!strconcat(!strconcat("b", cond), ",pn %icc, $imm"),
     92                   (BPICCNT brtarget:$imm, condVal)>, Requires<[HasV9]>;
     93 
     94   // b<cond>,a,pn %icc, $imm
     95   def : InstAlias<!strconcat(!strconcat("b", cond), ",a,pn %icc, $imm"),
     96                   (BPICCANT brtarget:$imm, condVal)>, Requires<[HasV9]>;
     97 
     98   // b<cond> %xcc, $imm
     99   def : InstAlias<!strconcat(!strconcat("b", cond), " %xcc, $imm"),
    100                   (BPXCC brtarget:$imm, condVal)>, Requires<[Is64Bit]>;
    101 
    102   // b<cond>,pt %xcc, $imm
    103   def : InstAlias<!strconcat(!strconcat("b", cond), ",pt %xcc, $imm"),
    104                   (BPXCC brtarget:$imm, condVal)>, Requires<[Is64Bit]>;
    105 
    106   // b<cond>,a %xcc, $imm
    107   def : InstAlias<!strconcat(!strconcat("b", cond), ",a %xcc, $imm"),
    108                   (BPXCCA brtarget:$imm, condVal)>, Requires<[Is64Bit]>;
    109 
    110   // b<cond>,a,pt %xcc, $imm
    111   def : InstAlias<!strconcat(!strconcat("b", cond), ",a,pt %xcc, $imm"),
    112                   (BPXCCA brtarget:$imm, condVal)>, Requires<[Is64Bit]>;
    113 
    114   // b<cond>,pn %xcc, $imm
    115   def : InstAlias<!strconcat(!strconcat("b", cond), ",pn %xcc, $imm"),
    116                   (BPXCCNT brtarget:$imm, condVal)>, Requires<[Is64Bit]>;
    117 
    118   // b<cond>,a,pn %xcc, $imm
    119   def : InstAlias<!strconcat(!strconcat("b", cond), ",a,pn %xcc, $imm"),
    120                   (BPXCCANT brtarget:$imm, condVal)>, Requires<[Is64Bit]>;
    121 
    122 
    123   defm : intcond_mov_alias<cond, condVal, " %icc",
    124                             MOVICCrr, MOVICCri,
    125                             FMOVS_ICC, FMOVD_ICC>, Requires<[HasV9]>;
    126 
    127   defm : intcond_mov_alias<cond, condVal, " %xcc",
    128                             MOVXCCrr, MOVXCCri,
    129                             FMOVS_XCC, FMOVD_XCC>, Requires<[Is64Bit]>;
    130 
    131   // fmovq<cond> (%icc|%xcc), $rs2, $rd
    132   def : InstAlias<!strconcat(!strconcat("fmovq", cond), " %icc, $rs2, $rd"),
    133                   (FMOVQ_ICC QFPRegs:$rd, QFPRegs:$rs2, condVal)>,
    134                   Requires<[HasV9, HasHardQuad]>;
    135   def : InstAlias<!strconcat(!strconcat("fmovq", cond), " %xcc, $rs2, $rd"),
    136                   (FMOVQ_XCC QFPRegs:$rd, QFPRegs:$rs2, condVal)>,
    137                   Requires<[Is64Bit, HasHardQuad]>;
    138 
    139   // t<cond> %icc,  rs => t<cond> %icc, G0 + rs
    140   def : InstAlias<!strconcat(!strconcat("t", cond), " %icc, $rs2"),
    141                   (TICCrr G0, IntRegs:$rs2, condVal)>,
    142                   Requires<[HasV9]>;
    143   // t<cond> %icc, rs1 + rs2
    144   def : InstAlias<!strconcat(!strconcat("t", cond), " %icc, $rs1 + $rs2"),
    145                   (TICCrr IntRegs:$rs1, IntRegs:$rs2, condVal)>,
    146                   Requires<[HasV9]>;
    147 
    148 
    149   // t<cond> %xcc, rs => t<cond> %xcc, G0 + rs
    150   def : InstAlias<!strconcat(!strconcat("t", cond), " %xcc, $rs2"),
    151                   (TXCCrr G0, IntRegs:$rs2, condVal)>,
    152                   Requires<[HasV9]>;
    153   // t<cond> %xcc, rs1 + rs2
    154   def : InstAlias<!strconcat(!strconcat("t", cond), " %xcc, $rs1 + $rs2"),
    155                   (TXCCrr IntRegs:$rs1, IntRegs:$rs2, condVal)>,
    156                   Requires<[HasV9]>;
    157 
    158 
    159   // t<cond> rs=> t<cond> %icc,  G0 + rs2
    160   //def : InstAlias<!strconcat(!strconcat("t", cond), " $rs2"),
    161   //                (TICCrr G0, IntRegs:$rs2, condVal)>,
    162   //                Requires<[HasV9]>;
    163 
    164   // t<cond> rs1 + rs2 => t<cond> %icc, rs1 + rs2
    165   //def : InstAlias<!strconcat(!strconcat("t", cond), " $rs1 + $rs2"),
    166   //                (TICCrr IntRegs:$rs1, IntRegs:$rs2, condVal)>,
    167   //                Requires<[HasV9]>;
    168 
    169   // t<cond> %icc, imm => t<cond> %icc, G0 + imm
    170   def : InstAlias<!strconcat(!strconcat("t", cond), " %icc, $imm"),
    171                   (TICCri G0, i32imm:$imm, condVal)>,
    172                   Requires<[HasV9]>;
    173   // t<cond> %icc, rs1 + imm
    174   def : InstAlias<!strconcat(!strconcat("t", cond), " %icc, $rs1 + $imm"),
    175                   (TICCri IntRegs:$rs1, i32imm:$imm, condVal)>,
    176                   Requires<[HasV9]>;
    177   // t<cond> %xcc, imm => t<cond> %xcc, G0 + imm
    178   def : InstAlias<!strconcat(!strconcat("t", cond), " %xcc, $imm"),
    179                   (TXCCri G0, i32imm:$imm, condVal)>,
    180                   Requires<[HasV9]>;
    181   // t<cond> %xcc, rs1 + imm
    182   def : InstAlias<!strconcat(!strconcat("t", cond), " %xcc, $rs1 + $imm"),
    183                   (TXCCri IntRegs:$rs1, i32imm:$imm, condVal)>,
    184                   Requires<[HasV9]>;
    185 
    186   // t<cond> imm => t<cond> G0 + imm
    187   def : InstAlias<!strconcat(!strconcat("t", cond), " $imm"),
    188                   (TRAPri G0, i32imm:$imm, condVal)>;
    189 
    190   // t<cond> rs1 + imm => t<cond> rs1 + imm
    191   def : InstAlias<!strconcat(!strconcat("t", cond), " $rs1 + $imm"),
    192                   (TRAPri IntRegs:$rs1, i32imm:$imm, condVal)>;
    193 
    194   // t<cond> rs1 => t<cond> G0 + rs1
    195   def : InstAlias<!strconcat(!strconcat("t", cond), " $rs1"),
    196                   (TRAPrr G0, IntRegs:$rs1, condVal)>;
    197 
    198   // t<cond> rs1 + rs2
    199   def : InstAlias<!strconcat(!strconcat("t", cond), " $rs1 + $rs2"),
    200                   (TRAPrr IntRegs:$rs1, IntRegs:$rs2, condVal)>;
    201 }
    202 
    203 
    204 // Instruction aliases for floating point conditional branches and moves.
    205 multiclass fp_cond_alias<string cond, int condVal> {
    206 
    207   // fb<cond> $imm
    208   def : InstAlias<!strconcat(!strconcat("fb", cond), " $imm"),
    209                   (FBCOND brtarget:$imm, condVal), 0>;
    210 
    211   // fb<cond>,a $imm
    212   def : InstAlias<!strconcat(!strconcat("fb", cond), ",a $imm"),
    213                   (FBCONDA brtarget:$imm, condVal), 0>;
    214 
    215   // fb<cond> %fcc0, $imm
    216   def : InstAlias<!strconcat(!strconcat("fb", cond), " $cc, $imm"),
    217                   (BPFCC brtarget:$imm, condVal, FCCRegs:$cc)>,
    218                   Requires<[HasV9]>;
    219 
    220   // fb<cond>,pt %fcc0, $imm
    221   def : InstAlias<!strconcat(!strconcat("fb", cond), ",pt $cc, $imm"),
    222                   (BPFCC brtarget:$imm, condVal, FCCRegs:$cc)>,
    223                   Requires<[HasV9]>;
    224 
    225   // fb<cond>,a %fcc0, $imm
    226   def : InstAlias<!strconcat(!strconcat("fb", cond), ",a $cc, $imm"),
    227                   (BPFCCA brtarget:$imm, condVal, FCCRegs:$cc)>,
    228                   Requires<[HasV9]>;
    229 
    230   // fb<cond>,a,pt %fcc0, $imm
    231   def : InstAlias<!strconcat(!strconcat("fb", cond), ",a,pt $cc, $imm"),
    232                   (BPFCCA brtarget:$imm, condVal, FCCRegs:$cc)>,
    233                    Requires<[HasV9]>;
    234 
    235   // fb<cond>,pn %fcc0, $imm
    236   def : InstAlias<!strconcat(!strconcat("fb", cond), ",pn $cc, $imm"),
    237                   (BPFCCNT brtarget:$imm, condVal, FCCRegs:$cc)>,
    238                    Requires<[HasV9]>;
    239 
    240   // fb<cond>,a,pn %fcc0, $imm
    241   def : InstAlias<!strconcat(!strconcat("fb", cond), ",a,pn $cc, $imm"),
    242                   (BPFCCANT brtarget:$imm, condVal, FCCRegs:$cc)>,
    243                   Requires<[HasV9]>;
    244 
    245   defm : fpcond_mov_alias<cond, condVal,
    246                           V9MOVFCCrr, V9MOVFCCri,
    247                           V9FMOVS_FCC, V9FMOVD_FCC>, Requires<[HasV9]>;
    248 
    249   // fmovq<cond> %fcc0, $rs2, $rd
    250   def : InstAlias<!strconcat(!strconcat("fmovq", cond), " $cc, $rs2, $rd"),
    251                   (V9FMOVQ_FCC QFPRegs:$rd, FCCRegs:$cc, QFPRegs:$rs2,
    252                                                           condVal)>,
    253                   Requires<[HasV9, HasHardQuad]>;
    254 }
    255 
    256 
    257 // Instruction aliases for co-processor conditional branches.
    258 multiclass cp_cond_alias<string cond, int condVal> {
    259 
    260   // cb<cond> $imm
    261   def : InstAlias<!strconcat(!strconcat("cb", cond), " $imm"),
    262                   (CBCOND brtarget:$imm, condVal), 0>;
    263 
    264   // cb<cond>,a $imm
    265   def : InstAlias<!strconcat(!strconcat("cb", cond), ",a $imm"),
    266                   (CBCONDA brtarget:$imm, condVal), 0>;
    267 }
    268 
    269 defm : int_cond_alias<"a",    0b1000>;
    270 defm : int_cond_alias<"n",    0b0000>;
    271 defm : int_cond_alias<"ne",   0b1001>;
    272 defm : int_cond_alias<"e",    0b0001>;
    273 defm : int_cond_alias<"g",    0b1010>;
    274 defm : int_cond_alias<"le",   0b0010>;
    275 defm : int_cond_alias<"ge",   0b1011>;
    276 defm : int_cond_alias<"l",    0b0011>;
    277 defm : int_cond_alias<"gu",   0b1100>;
    278 defm : int_cond_alias<"leu",  0b0100>;
    279 defm : int_cond_alias<"cc",   0b1101>;
    280 defm : int_cond_alias<"cs",   0b0101>;
    281 defm : int_cond_alias<"pos",  0b1110>;
    282 defm : int_cond_alias<"neg",  0b0110>;
    283 defm : int_cond_alias<"vc",   0b1111>;
    284 defm : int_cond_alias<"vs",   0b0111>;
    285 let EmitPriority = 0 in 
    286 {
    287   defm : int_cond_alias<"",     0b1000>; // same as a; gnu asm, not in manual
    288   defm : int_cond_alias<"nz",   0b1001>; // same as ne
    289   defm : int_cond_alias<"eq",   0b0001>; // same as e
    290   defm : int_cond_alias<"z",    0b0001>; // same as e
    291   defm : int_cond_alias<"geu",  0b1101>; // same as cc
    292   defm : int_cond_alias<"lu",   0b0101>; // same as cs
    293 }
    294 defm : fp_cond_alias<"a",     0b1000>;
    295 defm : fp_cond_alias<"n",     0b0000>;
    296 defm : fp_cond_alias<"u",     0b0111>;
    297 defm : fp_cond_alias<"g",     0b0110>;
    298 defm : fp_cond_alias<"ug",    0b0101>;
    299 defm : fp_cond_alias<"l",     0b0100>;
    300 defm : fp_cond_alias<"ul",    0b0011>;
    301 defm : fp_cond_alias<"lg",    0b0010>;
    302 defm : fp_cond_alias<"ne",    0b0001>;
    303 defm : fp_cond_alias<"e",     0b1001>;
    304 defm : fp_cond_alias<"ue",    0b1010>;
    305 defm : fp_cond_alias<"ge",    0b1011>;
    306 defm : fp_cond_alias<"uge",   0b1100>;
    307 defm : fp_cond_alias<"le",    0b1101>;
    308 defm : fp_cond_alias<"ule",   0b1110>;
    309 defm : fp_cond_alias<"o",     0b1111>;
    310 let EmitPriority = 0 in 
    311 {
    312   defm : fp_cond_alias<"",      0b1000>; // same as a; gnu asm, not in manual
    313   defm : fp_cond_alias<"nz",    0b0001>; // same as ne
    314   defm : fp_cond_alias<"z",     0b1001>; // same as e
    315 }
    316 
    317 defm : cp_cond_alias<"a",     0b1000>;
    318 defm : cp_cond_alias<"n",     0b0000>;
    319 defm : cp_cond_alias<"3",     0b0111>;
    320 defm : cp_cond_alias<"2",     0b0110>;
    321 defm : cp_cond_alias<"23",    0b0101>;
    322 defm : cp_cond_alias<"1",     0b0100>;
    323 defm : cp_cond_alias<"13",    0b0011>;
    324 defm : cp_cond_alias<"12",    0b0010>;
    325 defm : cp_cond_alias<"123",   0b0001>;
    326 defm : cp_cond_alias<"0",     0b1001>;
    327 defm : cp_cond_alias<"03",    0b1010>;
    328 defm : cp_cond_alias<"02",    0b1011>;
    329 defm : cp_cond_alias<"023",   0b1100>;
    330 defm : cp_cond_alias<"01",    0b1101>;
    331 defm : cp_cond_alias<"013",   0b1110>;
    332 defm : cp_cond_alias<"012",   0b1111>;
    333 let EmitPriority = 0 in defm : cp_cond_alias<"",      0b1000>; // same as a; gnu asm, not in manual
    334 
    335 // Section A.3 Synthetic Instructions
    336 
    337 // Most are marked as Emit=0, so that they are not used for disassembly. This is
    338 // an aesthetic issue, but the chosen policy is to typically prefer using the
    339 // non-alias form, except for the most obvious and clarifying aliases: cmp, jmp,
    340 // call, tst, ret, retl.
    341 
    342 // Note: cmp is handled in SparcInstrInfo.
    343 //       jmp/call/ret/retl have special case handling for output in
    344 //       SparcInstPrinter.cpp
    345 
    346 // jmp addr -> jmpl addr, %g0
    347 def : InstAlias<"jmp $addr", (JMPLrr G0, MEMrr:$addr), 0>;
    348 def : InstAlias<"jmp $addr", (JMPLri G0, MEMri:$addr), 0>;
    349 
    350 // call addr -> jmpl addr, %o7
    351 def : InstAlias<"call $addr", (JMPLrr O7, MEMrr:$addr), 0>;
    352 def : InstAlias<"call $addr", (JMPLri O7, MEMri:$addr), 0>;
    353 
    354 // tst reg -> orcc %g0, reg, %g0
    355 def : InstAlias<"tst $rs2", (ORCCrr G0, IntRegs:$rs2, G0)>;
    356 
    357 // ret -> jmpl %i7+8, %g0 (aka RET 8)
    358 def : InstAlias<"ret", (RET 8)>;
    359 
    360 // retl -> jmpl %o7+8, %g0 (aka RETL 8)
    361 def : InstAlias<"retl", (RETL 8)>;
    362 
    363 // restore -> restore %g0, %g0, %g0
    364 def : InstAlias<"restore", (RESTORErr G0, G0, G0)>;
    365 
    366 // save -> restore %g0, %g0, %g0
    367 def : InstAlias<"save", (SAVErr G0, G0, G0)>;
    368 
    369 // set value, rd
    370 // (turns into a sequence of sethi+or, depending on the value)
    371 // def : InstAlias<"set $val, $rd", (ORri IntRegs:$rd, (SETHIi (HI22 imm:$val)), (LO10 imm:$val))>;
    372 def SET : AsmPseudoInst<(outs IntRegs:$rd), (ins i32imm:$val), "set $val, $rd">;
    373 
    374 // not rd -> xnor rd, %g0, rd
    375 def : InstAlias<"not $rd", (XNORrr IntRegs:$rd, IntRegs:$rd, G0), 0>;
    376 
    377 // not reg, rd -> xnor reg, %g0, rd
    378 def : InstAlias<"not $rs1, $rd", (XNORrr IntRegs:$rd, IntRegs:$rs1, G0), 0>;
    379 
    380 // neg rd -> sub %g0, rd, rd
    381 def : InstAlias<"neg $rd", (SUBrr IntRegs:$rd, G0, IntRegs:$rd), 0>;
    382 
    383 // neg reg, rd -> sub %g0, reg, rd
    384 def : InstAlias<"neg $rs2, $rd", (SUBrr IntRegs:$rd, G0, IntRegs:$rs2), 0>;
    385 
    386 // inc rd -> add rd, 1, rd
    387 def : InstAlias<"inc $rd", (ADDri IntRegs:$rd, IntRegs:$rd, 1), 0>;
    388 
    389 // inc simm13, rd -> add rd, simm13, rd
    390 def : InstAlias<"inc $simm13, $rd", (ADDri IntRegs:$rd, IntRegs:$rd, i32imm:$simm13), 0>;
    391 
    392 // inccc rd -> addcc rd, 1, rd
    393 def : InstAlias<"inccc $rd", (ADDCCri IntRegs:$rd, IntRegs:$rd, 1), 0>;
    394 
    395 // inccc simm13, rd -> addcc rd, simm13, rd
    396 def : InstAlias<"inccc $simm13, $rd", (ADDCCri IntRegs:$rd, IntRegs:$rd, i32imm:$simm13), 0>;
    397 
    398 // dec rd -> sub rd, 1, rd
    399 def : InstAlias<"dec $rd", (SUBri IntRegs:$rd, IntRegs:$rd, 1), 0>;
    400 
    401 // dec simm13, rd -> sub rd, simm13, rd
    402 def : InstAlias<"dec $simm13, $rd", (SUBri IntRegs:$rd, IntRegs:$rd, i32imm:$simm13), 0>;
    403 
    404 // deccc rd -> subcc rd, 1, rd
    405 def : InstAlias<"deccc $rd", (SUBCCri IntRegs:$rd, IntRegs:$rd, 1), 0>;
    406 
    407 // deccc simm13, rd -> subcc rd, simm13, rd
    408 def : InstAlias<"deccc $simm13, $rd", (SUBCCri IntRegs:$rd, IntRegs:$rd, i32imm:$simm13), 0>;
    409 
    410 // btst reg_or_imm, reg -> andcc reg,reg_or_imm,%g0
    411 def : InstAlias<"btst $rs2, $rs1", (ANDCCrr G0, IntRegs:$rs1, IntRegs:$rs2), 0>;
    412 def : InstAlias<"btst $simm13, $rs1", (ANDCCri G0, IntRegs:$rs1, i32imm:$simm13), 0>;
    413 
    414 // bset reg_or_imm, rd -> or rd,reg_or_imm,rd
    415 def : InstAlias<"bset $rs2, $rd", (ORrr IntRegs:$rd, IntRegs:$rd, IntRegs:$rs2), 0>;
    416 def : InstAlias<"bset $simm13, $rd", (ORri IntRegs:$rd, IntRegs:$rd, i32imm:$simm13), 0>;
    417 
    418 // bclr reg_or_imm, rd -> andn rd,reg_or_imm,rd
    419 def : InstAlias<"bclr $rs2, $rd", (ANDNrr IntRegs:$rd, IntRegs:$rd, IntRegs:$rs2), 0>;
    420 def : InstAlias<"bclr $simm13, $rd", (ANDNri IntRegs:$rd, IntRegs:$rd, i32imm:$simm13), 0>;
    421 
    422 // btog reg_or_imm, rd -> xor rd,reg_or_imm,rd
    423 def : InstAlias<"btog $rs2, $rd", (XORrr IntRegs:$rd, IntRegs:$rd, IntRegs:$rs2), 0>;
    424 def : InstAlias<"btog $simm13, $rd", (XORri IntRegs:$rd, IntRegs:$rd, i32imm:$simm13), 0>;
    425 
    426 
    427 // clr rd -> or %g0, %g0, rd
    428 def : InstAlias<"clr $rd", (ORrr IntRegs:$rd, G0, G0), 0>;
    429 
    430 // clr{b,h,} [addr] -> st{b,h,} %g0, [addr]
    431 def : InstAlias<"clrb [$addr]", (STBrr MEMrr:$addr, G0), 0>;
    432 def : InstAlias<"clrb [$addr]", (STBri MEMri:$addr, G0), 0>;
    433 def : InstAlias<"clrh [$addr]", (STHrr MEMrr:$addr, G0), 0>;
    434 def : InstAlias<"clrh [$addr]", (STHri MEMri:$addr, G0), 0>;
    435 def : InstAlias<"clr [$addr]", (STrr MEMrr:$addr, G0), 0>;
    436 def : InstAlias<"clr [$addr]", (STri MEMri:$addr, G0), 0>;
    437 
    438 
    439 // mov reg_or_imm, rd -> or %g0, reg_or_imm, rd
    440 def : InstAlias<"mov $rs2, $rd", (ORrr IntRegs:$rd, G0, IntRegs:$rs2)>;
    441 def : InstAlias<"mov $simm13, $rd", (ORri IntRegs:$rd, G0, i32imm:$simm13)>;
    442 
    443 // mov specialreg, rd -> rd specialreg, rd
    444 def : InstAlias<"mov $asr, $rd", (RDASR IntRegs:$rd, ASRRegs:$asr), 0>;
    445 def : InstAlias<"mov %psr, $rd", (RDPSR IntRegs:$rd), 0>;
    446 def : InstAlias<"mov %wim, $rd", (RDWIM IntRegs:$rd), 0>;
    447 def : InstAlias<"mov %tbr, $rd", (RDTBR IntRegs:$rd), 0>;
    448 
    449 // mov reg_or_imm, specialreg -> wr %g0, reg_or_imm, specialreg
    450 def : InstAlias<"mov $rs2, $asr", (WRASRrr ASRRegs:$asr, G0, IntRegs:$rs2), 0>;
    451 def : InstAlias<"mov $simm13, $asr", (WRASRri ASRRegs:$asr, G0, i32imm:$simm13), 0>;
    452 def : InstAlias<"mov $rs2, %psr", (WRPSRrr G0, IntRegs:$rs2), 0>;
    453 def : InstAlias<"mov $simm13, %psr", (WRPSRri G0, i32imm:$simm13), 0>;
    454 def : InstAlias<"mov $rs2, %wim", (WRWIMrr G0, IntRegs:$rs2), 0>;
    455 def : InstAlias<"mov $simm13, %wim", (WRWIMri G0, i32imm:$simm13), 0>;
    456 def : InstAlias<"mov $rs2, %tbr", (WRTBRrr G0, IntRegs:$rs2), 0>;
    457 def : InstAlias<"mov $simm13, %tbr", (WRTBRri G0, i32imm:$simm13), 0>;
    458 
    459 // End of Section A.3
    460 
    461 // wr reg_or_imm, specialreg -> wr %g0, reg_or_imm, specialreg
    462 // (aka: omit the first arg when it's g0. This is not in the manual, but is
    463 // supported by gnu and solaris as)
    464 def : InstAlias<"wr $rs2, $asr", (WRASRrr ASRRegs:$asr, G0, IntRegs:$rs2), 0>;
    465 def : InstAlias<"wr $simm13, $asr", (WRASRri ASRRegs:$asr, G0, i32imm:$simm13), 0>;
    466 def : InstAlias<"wr $rs2, %psr", (WRPSRrr G0, IntRegs:$rs2), 0>;
    467 def : InstAlias<"wr $simm13, %psr", (WRPSRri G0, i32imm:$simm13), 0>;
    468 def : InstAlias<"wr $rs2, %wim", (WRWIMrr G0, IntRegs:$rs2), 0>;
    469 def : InstAlias<"wr $simm13, %wim", (WRWIMri G0, i32imm:$simm13), 0>;
    470 def : InstAlias<"wr $rs2, %tbr", (WRTBRrr G0, IntRegs:$rs2), 0>;
    471 def : InstAlias<"wr $simm13, %tbr", (WRTBRri G0, i32imm:$simm13), 0>;
    472 
    473 
    474 // flush -> flush %g0
    475 def : InstAlias<"flush", (FLUSH), 0>;
    476 
    477 def : MnemonicAlias<"iflush", "flush">;
    478 
    479 def : MnemonicAlias<"stub", "stb">;
    480 def : MnemonicAlias<"stsb", "stb">;
    481 
    482 def : MnemonicAlias<"stuba", "stba">;
    483 def : MnemonicAlias<"stsba", "stba">;
    484 
    485 def : MnemonicAlias<"stuh", "sth">;
    486 def : MnemonicAlias<"stsh", "sth">;
    487 
    488 def : MnemonicAlias<"stuha", "stha">;
    489 def : MnemonicAlias<"stsha", "stha">;
    490 
    491 def : MnemonicAlias<"lduw", "ld">, Requires<[HasV9]>;
    492 def : MnemonicAlias<"lduwa", "lda">, Requires<[HasV9]>;
    493 
    494 def : MnemonicAlias<"return", "rett">, Requires<[HasV9]>;
    495 
    496 def : MnemonicAlias<"addc", "addx">, Requires<[HasV9]>;
    497 def : MnemonicAlias<"addccc", "addxcc">, Requires<[HasV9]>;
    498 
    499 def : MnemonicAlias<"subc", "subx">, Requires<[HasV9]>;
    500 def : MnemonicAlias<"subccc", "subxcc">, Requires<[HasV9]>;
    501 
    502 
    503 def : InstAlias<"fcmps $rs1, $rs2", (V9FCMPS FCC0, FPRegs:$rs1, FPRegs:$rs2)>;
    504 def : InstAlias<"fcmpd $rs1, $rs2", (V9FCMPD FCC0, DFPRegs:$rs1, DFPRegs:$rs2)>;
    505 def : InstAlias<"fcmpq $rs1, $rs2", (V9FCMPQ FCC0, QFPRegs:$rs1, QFPRegs:$rs2)>,
    506                 Requires<[HasHardQuad]>;
    507 
    508 def : InstAlias<"fcmpes $rs1, $rs2", (V9FCMPES FCC0, FPRegs:$rs1, FPRegs:$rs2)>;
    509 def : InstAlias<"fcmped $rs1, $rs2", (V9FCMPED FCC0, DFPRegs:$rs1,
    510                                                      DFPRegs:$rs2)>;
    511 def : InstAlias<"fcmpeq $rs1, $rs2", (V9FCMPEQ FCC0, QFPRegs:$rs1,
    512                                                      QFPRegs:$rs2)>,
    513                 Requires<[HasHardQuad]>;
    514 
    515 // signx rd -> sra rd, %g0, rd
    516 def : InstAlias<"signx $rd", (SRArr IntRegs:$rd, IntRegs:$rd, G0), 0>, Requires<[HasV9]>;
    517 
    518 // signx reg, rd -> sra reg, %g0, rd
    519 def : InstAlias<"signx $rs1, $rd", (SRArr IntRegs:$rd, IntRegs:$rs1, G0), 0>, Requires<[HasV9]>;
    520