Home | History | Annotate | Download | only in MSP430
      1 //===-- MSP430InstrInfo.td - MSP430 Instruction defs -------*- tablegen -*-===//
      2 //
      3 //                     The LLVM Compiler Infrastructure
      4 //
      5 // This file is distributed under the University of Illinois Open Source 
      6 // License. See LICENSE.TXT for details.
      7 //
      8 //===----------------------------------------------------------------------===//
      9 //
     10 // This file describes the MSP430 instructions in TableGen format.
     11 //
     12 //===----------------------------------------------------------------------===//
     13 
     14 include "MSP430InstrFormats.td"
     15 
     16 //===----------------------------------------------------------------------===//
     17 // Type Constraints.
     18 //===----------------------------------------------------------------------===//
     19 class SDTCisI8<int OpNum> : SDTCisVT<OpNum, i8>;
     20 class SDTCisI16<int OpNum> : SDTCisVT<OpNum, i16>;
     21 
     22 //===----------------------------------------------------------------------===//
     23 // Type Profiles.
     24 //===----------------------------------------------------------------------===//
     25 def SDT_MSP430Call         : SDTypeProfile<0, -1, [SDTCisVT<0, iPTR>]>;
     26 def SDT_MSP430CallSeqStart : SDCallSeqStart<[SDTCisVT<0, i16>]>;
     27 def SDT_MSP430CallSeqEnd   : SDCallSeqEnd<[SDTCisVT<0, i16>, SDTCisVT<1, i16>]>;
     28 def SDT_MSP430Wrapper      : SDTypeProfile<1, 1, [SDTCisSameAs<0, 1>,
     29                                                   SDTCisPtrTy<0>]>;
     30 def SDT_MSP430Cmp          : SDTypeProfile<0, 2, [SDTCisSameAs<0, 1>]>;
     31 def SDT_MSP430BrCC         : SDTypeProfile<0, 2, [SDTCisVT<0, OtherVT>,
     32                                                   SDTCisVT<1, i8>]>;
     33 def SDT_MSP430SelectCC     : SDTypeProfile<1, 3, [SDTCisSameAs<0, 1>,
     34                                                   SDTCisSameAs<1, 2>, 
     35                                                   SDTCisVT<3, i8>]>;
     36 def SDT_MSP430Shift        : SDTypeProfile<1, 2, [SDTCisSameAs<0, 1>,
     37                                                   SDTCisI8<2>]>;
     38 
     39 //===----------------------------------------------------------------------===//
     40 // MSP430 Specific Node Definitions.
     41 //===----------------------------------------------------------------------===//
     42 def MSP430retflag  : SDNode<"MSP430ISD::RET_FLAG", SDTNone,
     43                        [SDNPHasChain, SDNPOptInGlue, SDNPVariadic]>;
     44 def MSP430retiflag : SDNode<"MSP430ISD::RETI_FLAG", SDTNone,
     45                        [SDNPHasChain, SDNPOptInGlue, SDNPVariadic]>;
     46 
     47 def MSP430rra     : SDNode<"MSP430ISD::RRA", SDTIntUnaryOp, []>;
     48 def MSP430rla     : SDNode<"MSP430ISD::RLA", SDTIntUnaryOp, []>;
     49 def MSP430rrc     : SDNode<"MSP430ISD::RRC", SDTIntUnaryOp, []>;
     50 
     51 def MSP430call    : SDNode<"MSP430ISD::CALL", SDT_MSP430Call,
     52                      [SDNPHasChain, SDNPOutGlue, SDNPOptInGlue, SDNPVariadic]>;
     53 def MSP430callseq_start :
     54                  SDNode<"ISD::CALLSEQ_START", SDT_MSP430CallSeqStart,
     55                         [SDNPHasChain, SDNPOutGlue]>;
     56 def MSP430callseq_end :
     57                  SDNode<"ISD::CALLSEQ_END",   SDT_MSP430CallSeqEnd,
     58                         [SDNPHasChain, SDNPOptInGlue, SDNPOutGlue]>;
     59 def MSP430Wrapper : SDNode<"MSP430ISD::Wrapper", SDT_MSP430Wrapper>;
     60 def MSP430cmp     : SDNode<"MSP430ISD::CMP", SDT_MSP430Cmp, [SDNPOutGlue]>;
     61 def MSP430brcc    : SDNode<"MSP430ISD::BR_CC", SDT_MSP430BrCC,
     62                             [SDNPHasChain, SDNPInGlue]>;
     63 def MSP430selectcc: SDNode<"MSP430ISD::SELECT_CC", SDT_MSP430SelectCC,
     64                             [SDNPInGlue]>;
     65 def MSP430shl     : SDNode<"MSP430ISD::SHL", SDT_MSP430Shift, []>;
     66 def MSP430sra     : SDNode<"MSP430ISD::SRA", SDT_MSP430Shift, []>;
     67 def MSP430srl     : SDNode<"MSP430ISD::SRL", SDT_MSP430Shift, []>;
     68 
     69 //===----------------------------------------------------------------------===//
     70 // MSP430 Operand Definitions.
     71 //===----------------------------------------------------------------------===//
     72 
     73 // Address operands
     74 def memsrc : Operand<i16> {
     75   let PrintMethod = "printSrcMemOperand";
     76   let MIOperandInfo = (ops GR16, i16imm);
     77 }
     78 
     79 def memdst : Operand<i16> {
     80   let PrintMethod = "printSrcMemOperand";
     81   let MIOperandInfo = (ops GR16, i16imm);
     82 }
     83 
     84 // Short jump targets have OtherVT type and are printed as pcrel imm values.
     85 def jmptarget : Operand<OtherVT> {
     86   let PrintMethod = "printPCRelImmOperand";
     87 }
     88 
     89 // Operand for printing out a condition code.
     90 def cc : Operand<i8> {
     91   let PrintMethod = "printCCOperand";
     92 }
     93 
     94 //===----------------------------------------------------------------------===//
     95 // MSP430 Complex Pattern Definitions.
     96 //===----------------------------------------------------------------------===//
     97 
     98 def addr : ComplexPattern<iPTR, 2, "SelectAddr", [], []>;
     99 
    100 //===----------------------------------------------------------------------===//
    101 // Pattern Fragments
    102 def zextloadi16i8 : PatFrag<(ops node:$ptr), (i16 (zextloadi8 node:$ptr))>;
    103 def  extloadi16i8 : PatFrag<(ops node:$ptr), (i16 ( extloadi8 node:$ptr))>;
    104 def and_su : PatFrag<(ops node:$lhs, node:$rhs), (and node:$lhs, node:$rhs), [{
    105   return N->hasOneUse();
    106 }]>;
    107 //===----------------------------------------------------------------------===//
    108 // Instruction list..
    109 
    110 // ADJCALLSTACKDOWN/UP implicitly use/def SP because they may be expanded into
    111 // a stack adjustment and the codegen must know that they may modify the stack
    112 // pointer before prolog-epilog rewriting occurs.
    113 // Pessimistically assume ADJCALLSTACKDOWN / ADJCALLSTACKUP will become
    114 // sub / add which can clobber SRW.
    115 let Defs = [SPW, SRW], Uses = [SPW] in {
    116 def ADJCALLSTACKDOWN : Pseudo<(outs), (ins i16imm:$amt),
    117                               "#ADJCALLSTACKDOWN",
    118                               [(MSP430callseq_start timm:$amt)]>;
    119 def ADJCALLSTACKUP   : Pseudo<(outs), (ins i16imm:$amt1, i16imm:$amt2),
    120                               "#ADJCALLSTACKUP",
    121                               [(MSP430callseq_end timm:$amt1, timm:$amt2)]>;
    122 }
    123 
    124 let usesCustomInserter = 1 in {
    125   def Select8  : Pseudo<(outs GR8:$dst), (ins GR8:$src, GR8:$src2, i8imm:$cc),
    126                         "# Select8 PSEUDO",
    127                         [(set GR8:$dst,
    128                           (MSP430selectcc GR8:$src, GR8:$src2, imm:$cc))]>;
    129   def Select16 : Pseudo<(outs GR16:$dst), (ins GR16:$src, GR16:$src2, i8imm:$cc),
    130                         "# Select16 PSEUDO",
    131                         [(set GR16:$dst,
    132                           (MSP430selectcc GR16:$src, GR16:$src2, imm:$cc))]>;
    133   let Defs = [SRW] in {
    134   def Shl8     : Pseudo<(outs GR8:$dst), (ins GR8:$src, GR8:$cnt),
    135                         "# Shl8 PSEUDO",
    136                         [(set GR8:$dst, (MSP430shl GR8:$src, GR8:$cnt))]>;
    137   def Shl16    : Pseudo<(outs GR16:$dst), (ins GR16:$src, GR8:$cnt),
    138                         "# Shl16 PSEUDO",
    139                         [(set GR16:$dst, (MSP430shl GR16:$src, GR8:$cnt))]>;
    140   def Sra8     : Pseudo<(outs GR8:$dst), (ins GR8:$src, GR8:$cnt),
    141                         "# Sra8 PSEUDO",
    142                         [(set GR8:$dst, (MSP430sra GR8:$src, GR8:$cnt))]>;
    143   def Sra16    : Pseudo<(outs GR16:$dst), (ins GR16:$src, GR8:$cnt),
    144                         "# Sra16 PSEUDO",
    145                         [(set GR16:$dst, (MSP430sra GR16:$src, GR8:$cnt))]>;
    146   def Srl8     : Pseudo<(outs GR8:$dst), (ins GR8:$src, GR8:$cnt),
    147                         "# Srl8 PSEUDO",
    148                         [(set GR8:$dst, (MSP430srl GR8:$src, GR8:$cnt))]>;
    149   def Srl16    : Pseudo<(outs GR16:$dst), (ins GR16:$src, GR8:$cnt),
    150                         "# Srl16 PSEUDO",
    151                         [(set GR16:$dst, (MSP430srl GR16:$src, GR8:$cnt))]>;
    152 
    153   }
    154 }
    155 
    156 let neverHasSideEffects = 1 in
    157 def NOP : Pseudo<(outs), (ins), "nop", []>;
    158 
    159 //===----------------------------------------------------------------------===//
    160 //  Control Flow Instructions...
    161 //
    162 
    163 // FIXME: Provide proper encoding!
    164 let isReturn = 1, isTerminator = 1, isBarrier = 1 in {
    165   def RET  : IForm16<0x0, DstReg, SrcPostInc, Size2Bytes,
    166                      (outs), (ins), "ret",  [(MSP430retflag)]>;
    167   def RETI : II16r<0x0, (outs), (ins), "reti", [(MSP430retiflag)]>;
    168 }
    169 
    170 let isBranch = 1, isTerminator = 1 in {
    171 
    172 // FIXME: expand opcode & cond field for branches!
    173 
    174 // Direct branch
    175 let isBarrier = 1 in {
    176   // Short branch
    177   def JMP : CJForm<0, 0, (outs), (ins jmptarget:$dst),
    178                    "jmp\t$dst",
    179                    [(br bb:$dst)]>;
    180   let isIndirectBranch = 1 in {
    181     // Long branches
    182     def Bi  : I16ri<0, (outs), (ins i16imm:$brdst),
    183                     "br\t$brdst",
    184                     [(brind tblockaddress:$brdst)]>;
    185     def Br  : I16rr<0, (outs), (ins GR16:$brdst),
    186                     "br\t$brdst",
    187                     [(brind GR16:$brdst)]>;
    188     def Bm  : I16rm<0, (outs), (ins memsrc:$brdst),
    189                     "br\t$brdst",
    190                     [(brind (load addr:$brdst))]>;
    191   }
    192 }
    193 
    194 // Conditional branches
    195 let Uses = [SRW] in
    196   def JCC : CJForm<0, 0,
    197                    (outs), (ins jmptarget:$dst, cc:$cc),
    198                    "j$cc\t$dst",
    199                    [(MSP430brcc bb:$dst, imm:$cc)]>;
    200 } // isBranch, isTerminator
    201 
    202 //===----------------------------------------------------------------------===//
    203 //  Call Instructions...
    204 //
    205 let isCall = 1 in
    206   // All calls clobber the non-callee saved registers. SPW is marked as
    207   // a use to prevent stack-pointer assignments that appear immediately
    208   // before calls from potentially appearing dead. Uses for argument
    209   // registers are added manually.
    210   let Defs = [R12W, R13W, R14W, R15W, SRW],
    211       Uses = [SPW] in {
    212     def CALLi     : II16i<0x0,
    213                           (outs), (ins i16imm:$dst),
    214                           "call\t$dst", [(MSP430call imm:$dst)]>;
    215     def CALLr     : II16r<0x0,
    216                           (outs), (ins GR16:$dst),
    217                           "call\t$dst", [(MSP430call GR16:$dst)]>;
    218     def CALLm     : II16m<0x0,
    219                           (outs), (ins memsrc:$dst),
    220                           "call\t${dst:mem}", [(MSP430call (load addr:$dst))]>;
    221   }
    222 
    223 
    224 //===----------------------------------------------------------------------===//
    225 //  Miscellaneous Instructions...
    226 //
    227 let Defs = [SPW], Uses = [SPW], neverHasSideEffects=1 in {
    228 let mayLoad = 1 in
    229 def POP16r   : IForm16<0x0, DstReg, SrcPostInc, Size2Bytes,
    230                        (outs GR16:$reg), (ins), "pop.w\t$reg", []>;
    231 
    232 let mayStore = 1 in
    233 def PUSH16r  : II16r<0x0,
    234                      (outs), (ins GR16:$reg), "push.w\t$reg",[]>;
    235 }
    236 
    237 //===----------------------------------------------------------------------===//
    238 // Move Instructions
    239 
    240 // FIXME: Provide proper encoding!
    241 let neverHasSideEffects = 1 in {
    242 def MOV8rr  : I8rr<0x0,
    243                    (outs GR8:$dst), (ins GR8:$src),
    244                    "mov.b\t{$src, $dst}",
    245                    []>;
    246 def MOV16rr : I16rr<0x0,
    247                     (outs GR16:$dst), (ins GR16:$src),
    248                     "mov.w\t{$src, $dst}",
    249                     []>;
    250 }
    251 
    252 // FIXME: Provide proper encoding!
    253 let isReMaterializable = 1, isAsCheapAsAMove = 1 in {
    254 def MOV8ri  : I8ri<0x0,
    255                    (outs GR8:$dst), (ins i8imm:$src),
    256                    "mov.b\t{$src, $dst}",
    257                    [(set GR8:$dst, imm:$src)]>;
    258 def MOV16ri : I16ri<0x0,
    259                     (outs GR16:$dst), (ins i16imm:$src),
    260                     "mov.w\t{$src, $dst}",
    261                     [(set GR16:$dst, imm:$src)]>;
    262 }
    263 
    264 let canFoldAsLoad = 1, isReMaterializable = 1 in {
    265 def MOV8rm  : I8rm<0x0,
    266                    (outs GR8:$dst), (ins memsrc:$src),
    267                    "mov.b\t{$src, $dst}",
    268                    [(set GR8:$dst, (load addr:$src))]>;
    269 def MOV16rm : I16rm<0x0,
    270                     (outs GR16:$dst), (ins memsrc:$src),
    271                     "mov.w\t{$src, $dst}",
    272                     [(set GR16:$dst, (load addr:$src))]>;
    273 }
    274 
    275 def MOVZX16rr8 : I8rr<0x0,
    276                       (outs GR16:$dst), (ins GR8:$src),
    277                       "mov.b\t{$src, $dst}",
    278                       [(set GR16:$dst, (zext GR8:$src))]>;
    279 def MOVZX16rm8 : I8rm<0x0,
    280                       (outs GR16:$dst), (ins memsrc:$src),
    281                       "mov.b\t{$src, $dst}",
    282                       [(set GR16:$dst, (zextloadi16i8 addr:$src))]>;
    283 
    284 let mayLoad = 1, hasExtraDefRegAllocReq = 1, Constraints = "$base = $base_wb" in {
    285 def MOV8rm_POST  : IForm8<0x0, DstReg, SrcPostInc, Size2Bytes,
    286                          (outs GR8:$dst, GR16:$base_wb), (ins GR16:$base),
    287                          "mov.b\t{@$base+, $dst}", []>;
    288 def MOV16rm_POST : IForm16<0x0, DstReg, SrcPostInc, Size2Bytes,
    289                            (outs GR16:$dst, GR16:$base_wb), (ins GR16:$base),
    290                            "mov.w\t{@$base+, $dst}", []>;
    291 }
    292 
    293 // Any instruction that defines a 8-bit result leaves the high half of the
    294 // register. Truncate can be lowered to EXTRACT_SUBREG, and CopyFromReg may
    295 // be copying from a truncate, but any other 8-bit operation will zero-extend
    296 // up to 16 bits.
    297 def def8 : PatLeaf<(i8 GR8:$src), [{
    298   return N->getOpcode() != ISD::TRUNCATE &&
    299          N->getOpcode() != TargetOpcode::EXTRACT_SUBREG &&
    300          N->getOpcode() != ISD::CopyFromReg;
    301 }]>;
    302 
    303 // In the case of a 8-bit def that is known to implicitly zero-extend,
    304 // we can use a SUBREG_TO_REG.
    305 def : Pat<(i16 (zext def8:$src)),
    306           (SUBREG_TO_REG (i16 0), GR8:$src, subreg_8bit)>;
    307 
    308 def MOV8mi  : I8mi<0x0,
    309                    (outs), (ins memdst:$dst, i8imm:$src),
    310                    "mov.b\t{$src, $dst}",
    311                    [(store (i8 imm:$src), addr:$dst)]>;
    312 def MOV16mi : I16mi<0x0,
    313                     (outs), (ins memdst:$dst, i16imm:$src),
    314                     "mov.w\t{$src, $dst}",
    315                     [(store (i16 imm:$src), addr:$dst)]>;
    316 
    317 def MOV8mr  : I8mr<0x0,
    318                    (outs), (ins memdst:$dst, GR8:$src),
    319                    "mov.b\t{$src, $dst}",
    320                    [(store GR8:$src, addr:$dst)]>;
    321 def MOV16mr : I16mr<0x0,
    322                     (outs), (ins memdst:$dst, GR16:$src),
    323                     "mov.w\t{$src, $dst}",
    324                     [(store GR16:$src, addr:$dst)]>;
    325 
    326 def MOV8mm  : I8mm<0x0,
    327                    (outs), (ins memdst:$dst, memsrc:$src),
    328                    "mov.b\t{$src, $dst}",
    329                    [(store (i8 (load addr:$src)), addr:$dst)]>;
    330 def MOV16mm : I16mm<0x0,
    331                     (outs), (ins memdst:$dst, memsrc:$src),
    332                     "mov.w\t{$src, $dst}",
    333                     [(store (i16 (load addr:$src)), addr:$dst)]>;
    334 
    335 //===----------------------------------------------------------------------===//
    336 // Arithmetic Instructions
    337 
    338 let Constraints = "$src = $dst" in {
    339 
    340 let Defs = [SRW] in {
    341 
    342 let isCommutable = 1 in { // X = ADD Y, Z  == X = ADD Z, Y
    343 
    344 def ADD8rr  : I8rr<0x0,
    345                    (outs GR8:$dst), (ins GR8:$src, GR8:$src2),
    346                    "add.b\t{$src2, $dst}",
    347                    [(set GR8:$dst, (add GR8:$src, GR8:$src2)),
    348                     (implicit SRW)]>;
    349 def ADD16rr : I16rr<0x0,
    350                     (outs GR16:$dst), (ins GR16:$src, GR16:$src2),
    351                     "add.w\t{$src2, $dst}",
    352                     [(set GR16:$dst, (add GR16:$src, GR16:$src2)),
    353                      (implicit SRW)]>;
    354 }
    355 
    356 def ADD8rm  : I8rm<0x0,
    357                    (outs GR8:$dst), (ins GR8:$src, memsrc:$src2),
    358                    "add.b\t{$src2, $dst}",
    359                    [(set GR8:$dst, (add GR8:$src, (load addr:$src2))),
    360                     (implicit SRW)]>;
    361 def ADD16rm : I16rm<0x0,
    362                     (outs GR16:$dst), (ins GR16:$src, memsrc:$src2),
    363                     "add.w\t{$src2, $dst}",
    364                     [(set GR16:$dst, (add GR16:$src, (load addr:$src2))),
    365                      (implicit SRW)]>;
    366 
    367 let mayLoad = 1, hasExtraDefRegAllocReq = 1, 
    368 Constraints = "$base = $base_wb, $src = $dst" in {
    369 def ADD8rm_POST : IForm8<0x0, DstReg, SrcPostInc, Size2Bytes,
    370                          (outs GR8:$dst, GR16:$base_wb),
    371                          (ins GR8:$src, GR16:$base),
    372                          "add.b\t{@$base+, $dst}", []>;
    373 def ADD16rm_POST : IForm16<0x0, DstReg, SrcPostInc, Size2Bytes,
    374                            (outs GR16:$dst, GR16:$base_wb),
    375                            (ins GR16:$src, GR16:$base),
    376                           "add.w\t{@$base+, $dst}", []>;
    377 }
    378 
    379 
    380 def ADD8ri  : I8ri<0x0,
    381                    (outs GR8:$dst), (ins GR8:$src, i8imm:$src2),
    382                    "add.b\t{$src2, $dst}",
    383                    [(set GR8:$dst, (add GR8:$src, imm:$src2)),
    384                     (implicit SRW)]>;
    385 def ADD16ri : I16ri<0x0,
    386                     (outs GR16:$dst), (ins GR16:$src, i16imm:$src2),
    387                     "add.w\t{$src2, $dst}",
    388                     [(set GR16:$dst, (add GR16:$src, imm:$src2)),
    389                      (implicit SRW)]>;
    390 
    391 let Constraints = "" in {
    392 def ADD8mr  : I8mr<0x0,
    393                    (outs), (ins memdst:$dst, GR8:$src),
    394                    "add.b\t{$src, $dst}",
    395                    [(store (add (load addr:$dst), GR8:$src), addr:$dst),
    396                     (implicit SRW)]>;
    397 def ADD16mr : I16mr<0x0,
    398                     (outs), (ins memdst:$dst, GR16:$src),
    399                     "add.w\t{$src, $dst}",
    400                     [(store (add (load addr:$dst), GR16:$src), addr:$dst),
    401                      (implicit SRW)]>;
    402 
    403 def ADD8mi  : I8mi<0x0,
    404                    (outs), (ins memdst:$dst, i8imm:$src),
    405                    "add.b\t{$src, $dst}",
    406                    [(store (add (load addr:$dst), (i8 imm:$src)), addr:$dst),
    407                     (implicit SRW)]>;
    408 def ADD16mi : I16mi<0x0,
    409                     (outs), (ins memdst:$dst, i16imm:$src),
    410                     "add.w\t{$src, $dst}",
    411                     [(store (add (load addr:$dst), (i16 imm:$src)), addr:$dst),
    412                      (implicit SRW)]>;
    413 
    414 def ADD8mm  : I8mm<0x0,
    415                    (outs), (ins memdst:$dst, memsrc:$src),
    416                    "add.b\t{$src, $dst}",
    417                    [(store (add (load addr:$dst), 
    418                                 (i8 (load addr:$src))), addr:$dst),
    419                     (implicit SRW)]>;
    420 def ADD16mm : I16mm<0x0,
    421                     (outs), (ins memdst:$dst, memsrc:$src),
    422                     "add.w\t{$src, $dst}",
    423                     [(store (add (load addr:$dst), 
    424                                   (i16 (load addr:$src))), addr:$dst),
    425                      (implicit SRW)]>;
    426 }
    427 
    428 let Uses = [SRW] in {
    429 
    430 let isCommutable = 1 in { // X = ADDC Y, Z  == X = ADDC Z, Y
    431 def ADC8rr  : I8rr<0x0,
    432                    (outs GR8:$dst), (ins GR8:$src, GR8:$src2),
    433                    "addc.b\t{$src2, $dst}",
    434                    [(set GR8:$dst, (adde GR8:$src, GR8:$src2)),
    435                     (implicit SRW)]>;
    436 def ADC16rr : I16rr<0x0,
    437                     (outs GR16:$dst), (ins GR16:$src, GR16:$src2),
    438                     "addc.w\t{$src2, $dst}",
    439                     [(set GR16:$dst, (adde GR16:$src, GR16:$src2)),
    440                      (implicit SRW)]>;
    441 } // isCommutable
    442 
    443 def ADC8ri  : I8ri<0x0,
    444                    (outs GR8:$dst), (ins GR8:$src, i8imm:$src2),
    445                    "addc.b\t{$src2, $dst}",
    446                    [(set GR8:$dst, (adde GR8:$src, imm:$src2)),
    447                     (implicit SRW)]>;
    448 def ADC16ri : I16ri<0x0,
    449                     (outs GR16:$dst), (ins GR16:$src, i16imm:$src2),
    450                     "addc.w\t{$src2, $dst}",
    451                     [(set GR16:$dst, (adde GR16:$src, imm:$src2)),
    452                      (implicit SRW)]>;
    453 
    454 def ADC8rm  : I8rm<0x0,
    455                    (outs GR8:$dst), (ins GR8:$src, memsrc:$src2),
    456                    "addc.b\t{$src2, $dst}",
    457                    [(set GR8:$dst, (adde GR8:$src, (load addr:$src2))),
    458                     (implicit SRW)]>;
    459 def ADC16rm : I16rm<0x0,
    460                     (outs GR16:$dst), (ins GR16:$src, memsrc:$src2),
    461                     "addc.w\t{$src2, $dst}",
    462                     [(set GR16:$dst, (adde GR16:$src, (load addr:$src2))),
    463                      (implicit SRW)]>;
    464 
    465 let Constraints = "" in {
    466 def ADC8mr  : I8mr<0x0,
    467                    (outs), (ins memdst:$dst, GR8:$src),
    468                    "addc.b\t{$src, $dst}",
    469                    [(store (adde (load addr:$dst), GR8:$src), addr:$dst),
    470                     (implicit SRW)]>;
    471 def ADC16mr : I16mr<0x0,
    472                     (outs), (ins memdst:$dst, GR16:$src),
    473                     "addc.w\t{$src, $dst}",
    474                     [(store (adde (load addr:$dst), GR16:$src), addr:$dst),
    475                      (implicit SRW)]>;
    476 
    477 def ADC8mi  : I8mi<0x0,
    478                    (outs), (ins memdst:$dst, i8imm:$src),
    479                    "addc.b\t{$src, $dst}",
    480                    [(store (adde (load addr:$dst), (i8 imm:$src)), addr:$dst),
    481                     (implicit SRW)]>;
    482 def ADC16mi : I16mi<0x0,
    483                     (outs), (ins memdst:$dst, i16imm:$src),
    484                     "addc.w\t{$src, $dst}",
    485                     [(store (adde (load addr:$dst), (i16 imm:$src)), addr:$dst),
    486                      (implicit SRW)]>;
    487 
    488 def ADC8mm  : I8mm<0x0,
    489                    (outs), (ins memdst:$dst, memsrc:$src),
    490                    "addc.b\t{$src, $dst}",
    491                    [(store (adde (load addr:$dst), 
    492                                  (i8 (load addr:$src))), addr:$dst),
    493                     (implicit SRW)]>;
    494 def ADC16mm : I8mm<0x0,
    495                    (outs), (ins memdst:$dst, memsrc:$src),
    496                    "addc.w\t{$src, $dst}",
    497                    [(store (adde (load addr:$dst), 
    498                                  (i16 (load addr:$src))), addr:$dst),
    499                     (implicit SRW)]>;
    500 }
    501 
    502 } // Uses = [SRW]
    503 
    504 let isCommutable = 1 in { // X = AND Y, Z  == X = AND Z, Y
    505 def AND8rr  : I8rr<0x0,
    506                    (outs GR8:$dst), (ins GR8:$src, GR8:$src2),
    507                    "and.b\t{$src2, $dst}",
    508                    [(set GR8:$dst, (and GR8:$src, GR8:$src2)),
    509                     (implicit SRW)]>;
    510 def AND16rr : I16rr<0x0,
    511                     (outs GR16:$dst), (ins GR16:$src, GR16:$src2),
    512                     "and.w\t{$src2, $dst}",
    513                     [(set GR16:$dst, (and GR16:$src, GR16:$src2)),
    514                      (implicit SRW)]>;
    515 }
    516 
    517 def AND8ri  : I8ri<0x0,
    518                    (outs GR8:$dst), (ins GR8:$src, i8imm:$src2),
    519                    "and.b\t{$src2, $dst}",
    520                    [(set GR8:$dst, (and GR8:$src, imm:$src2)),
    521                     (implicit SRW)]>;
    522 def AND16ri : I16ri<0x0,
    523                     (outs GR16:$dst), (ins GR16:$src, i16imm:$src2),
    524                     "and.w\t{$src2, $dst}",
    525                     [(set GR16:$dst, (and GR16:$src, imm:$src2)),
    526                      (implicit SRW)]>;
    527 
    528 def AND8rm  : I8rm<0x0,
    529                    (outs GR8:$dst), (ins GR8:$src, memsrc:$src2),
    530                    "and.b\t{$src2, $dst}",
    531                    [(set GR8:$dst, (and GR8:$src, (load addr:$src2))),
    532                     (implicit SRW)]>;
    533 def AND16rm : I16rm<0x0,
    534                     (outs GR16:$dst), (ins GR16:$src, memsrc:$src2),
    535                     "and.w\t{$src2, $dst}",
    536                     [(set GR16:$dst, (and GR16:$src, (load addr:$src2))),
    537                      (implicit SRW)]>;
    538 
    539 let mayLoad = 1, hasExtraDefRegAllocReq = 1, 
    540 Constraints = "$base = $base_wb, $src = $dst" in {
    541 def AND8rm_POST : IForm8<0x0, DstReg, SrcPostInc, Size2Bytes,
    542                          (outs GR8:$dst, GR16:$base_wb),
    543                          (ins GR8:$src, GR16:$base),
    544                          "and.b\t{@$base+, $dst}", []>;
    545 def AND16rm_POST : IForm16<0x0, DstReg, SrcPostInc, Size2Bytes,
    546                            (outs GR16:$dst, GR16:$base_wb),
    547                            (ins GR16:$src, GR16:$base),
    548                            "and.w\t{@$base+, $dst}", []>;
    549 }
    550 
    551 let Constraints = "" in {
    552 def AND8mr  : I8mr<0x0,
    553                    (outs), (ins memdst:$dst, GR8:$src),
    554                    "and.b\t{$src, $dst}",
    555                    [(store (and (load addr:$dst), GR8:$src), addr:$dst),
    556                     (implicit SRW)]>;
    557 def AND16mr : I16mr<0x0,
    558                     (outs), (ins memdst:$dst, GR16:$src),
    559                     "and.w\t{$src, $dst}",
    560                     [(store (and (load addr:$dst), GR16:$src), addr:$dst),
    561                      (implicit SRW)]>;
    562 
    563 def AND8mi  : I8mi<0x0,
    564                    (outs), (ins memdst:$dst, i8imm:$src),
    565                    "and.b\t{$src, $dst}",
    566                    [(store (and (load addr:$dst), (i8 imm:$src)), addr:$dst),
    567                     (implicit SRW)]>;
    568 def AND16mi : I16mi<0x0,
    569                     (outs), (ins memdst:$dst, i16imm:$src),
    570                     "and.w\t{$src, $dst}",
    571                     [(store (and (load addr:$dst), (i16 imm:$src)), addr:$dst),
    572                      (implicit SRW)]>;
    573 
    574 def AND8mm  : I8mm<0x0,
    575                    (outs), (ins memdst:$dst, memsrc:$src),
    576                    "and.b\t{$src, $dst}",
    577                    [(store (and (load addr:$dst), 
    578                                 (i8 (load addr:$src))), addr:$dst),
    579                     (implicit SRW)]>;
    580 def AND16mm : I16mm<0x0,
    581                     (outs), (ins memdst:$dst, memsrc:$src),
    582                     "and.w\t{$src, $dst}",
    583                     [(store (and (load addr:$dst), 
    584                                  (i16 (load addr:$src))), addr:$dst),
    585                      (implicit SRW)]>;
    586 }
    587 
    588 let isCommutable = 1 in { // X = OR Y, Z  == X = OR Z, Y
    589 def OR8rr  : I8rr<0x0,
    590                   (outs GR8:$dst), (ins GR8:$src, GR8:$src2),
    591                   "bis.b\t{$src2, $dst}",
    592                   [(set GR8:$dst, (or GR8:$src, GR8:$src2))]>;
    593 def OR16rr : I16rr<0x0,
    594                    (outs GR16:$dst), (ins GR16:$src, GR16:$src2),
    595                    "bis.w\t{$src2, $dst}",
    596                    [(set GR16:$dst, (or GR16:$src, GR16:$src2))]>;
    597 }
    598 
    599 def OR8ri  : I8ri<0x0,
    600                   (outs GR8:$dst), (ins GR8:$src, i8imm:$src2),
    601                   "bis.b\t{$src2, $dst}",
    602                   [(set GR8:$dst, (or GR8:$src, imm:$src2))]>;
    603 def OR16ri : I16ri<0x0,
    604                    (outs GR16:$dst), (ins GR16:$src, i16imm:$src2),
    605                    "bis.w\t{$src2, $dst}",
    606                    [(set GR16:$dst, (or GR16:$src, imm:$src2))]>;
    607 
    608 def OR8rm  : I8rm<0x0,
    609                   (outs GR8:$dst), (ins GR8:$src, memsrc:$src2),
    610                   "bis.b\t{$src2, $dst}",
    611                   [(set GR8:$dst, (or GR8:$src, (load addr:$src2)))]>;
    612 def OR16rm : I16rm<0x0,
    613                    (outs GR16:$dst), (ins GR16:$src, memsrc:$src2),
    614                    "bis.w\t{$src2, $dst}",
    615                    [(set GR16:$dst, (or GR16:$src, (load addr:$src2)))]>;
    616 
    617 let mayLoad = 1, hasExtraDefRegAllocReq = 1, 
    618 Constraints = "$base = $base_wb, $src = $dst" in {
    619 def OR8rm_POST : IForm8<0x0, DstReg, SrcPostInc, Size2Bytes,
    620                         (outs GR8:$dst, GR16:$base_wb),
    621                         (ins GR8:$src, GR16:$base),
    622                         "bis.b\t{@$base+, $dst}", []>;
    623 def OR16rm_POST : IForm16<0x0, DstReg, SrcPostInc, Size2Bytes,
    624                           (outs GR16:$dst, GR16:$base_wb),
    625                           (ins GR16:$src, GR16:$base),
    626                           "bis.w\t{@$base+, $dst}", []>;
    627 }
    628 
    629 let Constraints = "" in {
    630 def OR8mr  : I8mr<0x0,
    631                   (outs), (ins memdst:$dst, GR8:$src),
    632                   "bis.b\t{$src, $dst}",
    633                   [(store (or (load addr:$dst), GR8:$src), addr:$dst)]>;
    634 def OR16mr : I16mr<0x0,
    635                    (outs), (ins memdst:$dst, GR16:$src),
    636                    "bis.w\t{$src, $dst}",
    637                    [(store (or (load addr:$dst), GR16:$src), addr:$dst)]>;
    638 
    639 def OR8mi  : I8mi<0x0, 
    640                   (outs), (ins memdst:$dst, i8imm:$src),
    641                   "bis.b\t{$src, $dst}",
    642                   [(store (or (load addr:$dst), (i8 imm:$src)), addr:$dst)]>;
    643 def OR16mi : I16mi<0x0,
    644                    (outs), (ins memdst:$dst, i16imm:$src),
    645                    "bis.w\t{$src, $dst}",
    646                    [(store (or (load addr:$dst), (i16 imm:$src)), addr:$dst)]>;
    647 
    648 def OR8mm  : I8mm<0x0,
    649                   (outs), (ins memdst:$dst, memsrc:$src),
    650                   "bis.b\t{$src, $dst}",
    651                   [(store (or (i8 (load addr:$dst)),
    652                               (i8 (load addr:$src))), addr:$dst)]>;
    653 def OR16mm : I16mm<0x0,
    654                    (outs), (ins memdst:$dst, memsrc:$src),
    655                    "bis.w\t{$src, $dst}",
    656                    [(store (or (i16 (load addr:$dst)),
    657                                (i16 (load addr:$src))), addr:$dst)]>;
    658 }
    659 
    660 // bic does not modify condition codes
    661 def BIC8rr :  I8rr<0x0,
    662                    (outs GR8:$dst), (ins GR8:$src, GR8:$src2),
    663                    "bic.b\t{$src2, $dst}",
    664                    [(set GR8:$dst, (and GR8:$src, (not GR8:$src2)))]>;
    665 def BIC16rr : I16rr<0x0,
    666                     (outs GR16:$dst), (ins GR16:$src, GR16:$src2),
    667                     "bic.w\t{$src2, $dst}",
    668                     [(set GR16:$dst, (and GR16:$src, (not GR16:$src2)))]>;
    669 
    670 def BIC8rm :  I8rm<0x0,
    671                    (outs GR8:$dst), (ins GR8:$src, memsrc:$src2),
    672                    "bic.b\t{$src2, $dst}",
    673                     [(set GR8:$dst, (and GR8:$src, (not (i8 (load addr:$src2)))))]>;
    674 def BIC16rm : I16rm<0x0,
    675                     (outs GR16:$dst), (ins GR16:$src, memsrc:$src2),
    676                     "bic.w\t{$src2, $dst}",
    677                     [(set GR16:$dst, (and GR16:$src, (not (i16 (load addr:$src2)))))]>;
    678 
    679 let Constraints = "" in {
    680 def BIC8mr :  I8mr<0x0,
    681                    (outs), (ins memdst:$dst, GR8:$src),
    682                    "bic.b\t{$src, $dst}",
    683                    [(store (and (load addr:$dst), (not GR8:$src)), addr:$dst)]>;
    684 def BIC16mr : I16mr<0x0,
    685                     (outs), (ins memdst:$dst, GR16:$src),
    686                     "bic.w\t{$src, $dst}",
    687                     [(store (and (load addr:$dst), (not GR16:$src)), addr:$dst)]>;
    688 
    689 def BIC8mm :  I8mm<0x0,
    690                    (outs), (ins memdst:$dst, memsrc:$src),
    691                    "bic.b\t{$src, $dst}",
    692                    [(store (and (load addr:$dst),
    693                                 (not (i8 (load addr:$src)))), addr:$dst)]>;
    694 def BIC16mm : I16mm<0x0,
    695                     (outs), (ins memdst:$dst, memsrc:$src),
    696                     "bic.w\t{$src, $dst}",
    697                     [(store (and (load addr:$dst),
    698                                  (not (i16 (load addr:$src)))), addr:$dst)]>;
    699 }
    700 
    701 let isCommutable = 1 in { // X = XOR Y, Z  == X = XOR Z, Y
    702 def XOR8rr  : I8rr<0x0,
    703                    (outs GR8:$dst), (ins GR8:$src, GR8:$src2),
    704                    "xor.b\t{$src2, $dst}",
    705                    [(set GR8:$dst, (xor GR8:$src, GR8:$src2)),
    706                     (implicit SRW)]>;
    707 def XOR16rr : I16rr<0x0,
    708                     (outs GR16:$dst), (ins GR16:$src, GR16:$src2),
    709                     "xor.w\t{$src2, $dst}",
    710                     [(set GR16:$dst, (xor GR16:$src, GR16:$src2)),
    711                      (implicit SRW)]>;
    712 }
    713 
    714 def XOR8ri  : I8ri<0x0,
    715                    (outs GR8:$dst), (ins GR8:$src, i8imm:$src2),
    716                    "xor.b\t{$src2, $dst}",
    717                    [(set GR8:$dst, (xor GR8:$src, imm:$src2)),
    718                     (implicit SRW)]>;
    719 def XOR16ri : I16ri<0x0,
    720                     (outs GR16:$dst), (ins GR16:$src, i16imm:$src2),
    721                     "xor.w\t{$src2, $dst}",
    722                     [(set GR16:$dst, (xor GR16:$src, imm:$src2)),
    723                      (implicit SRW)]>;
    724 
    725 def XOR8rm  : I8rm<0x0,
    726                    (outs GR8:$dst), (ins GR8:$src, memsrc:$src2),
    727                    "xor.b\t{$src2, $dst}",
    728                    [(set GR8:$dst, (xor GR8:$src, (load addr:$src2))),
    729                     (implicit SRW)]>;
    730 def XOR16rm : I16rm<0x0,
    731                     (outs GR16:$dst), (ins GR16:$src, memsrc:$src2),
    732                     "xor.w\t{$src2, $dst}",
    733                     [(set GR16:$dst, (xor GR16:$src, (load addr:$src2))),
    734                      (implicit SRW)]>;
    735 
    736 let mayLoad = 1, hasExtraDefRegAllocReq = 1, 
    737 Constraints = "$base = $base_wb, $src = $dst" in {
    738 def XOR8rm_POST : IForm8<0x0, DstReg, SrcPostInc, Size2Bytes,
    739                          (outs GR8:$dst, GR16:$base_wb),
    740                          (ins GR8:$src, GR16:$base),
    741                          "xor.b\t{@$base+, $dst}", []>;
    742 def XOR16rm_POST : IForm16<0x0, DstReg, SrcPostInc, Size2Bytes,
    743                            (outs GR16:$dst, GR16:$base_wb),
    744                            (ins GR16:$src, GR16:$base),
    745                            "xor.w\t{@$base+, $dst}", []>;
    746 }
    747 
    748 let Constraints = "" in {
    749 def XOR8mr  : I8mr<0x0,
    750                    (outs), (ins memdst:$dst, GR8:$src),
    751                    "xor.b\t{$src, $dst}",
    752                    [(store (xor (load addr:$dst), GR8:$src), addr:$dst),
    753                     (implicit SRW)]>;
    754 def XOR16mr : I16mr<0x0,
    755                     (outs), (ins memdst:$dst, GR16:$src),
    756                     "xor.w\t{$src, $dst}",
    757                     [(store (xor (load addr:$dst), GR16:$src), addr:$dst),
    758                      (implicit SRW)]>;
    759 
    760 def XOR8mi  : I8mi<0x0,
    761                    (outs), (ins memdst:$dst, i8imm:$src),
    762                    "xor.b\t{$src, $dst}",
    763                    [(store (xor (load addr:$dst), (i8 imm:$src)), addr:$dst),
    764                     (implicit SRW)]>;
    765 def XOR16mi : I16mi<0x0,
    766                     (outs), (ins memdst:$dst, i16imm:$src),
    767                     "xor.w\t{$src, $dst}",
    768                     [(store (xor (load addr:$dst), (i16 imm:$src)), addr:$dst),
    769                      (implicit SRW)]>;
    770 
    771 def XOR8mm  : I8mm<0x0,
    772                    (outs), (ins memdst:$dst, memsrc:$src),
    773                    "xor.b\t{$src, $dst}",
    774                    [(store (xor (load addr:$dst), (i8 (load addr:$src))), addr:$dst),
    775                     (implicit SRW)]>;
    776 def XOR16mm : I16mm<0x0,
    777                     (outs), (ins memdst:$dst, memsrc:$src),
    778                     "xor.w\t{$src, $dst}",
    779                     [(store (xor (load addr:$dst), (i16 (load addr:$src))), addr:$dst),
    780                      (implicit SRW)]>;
    781 }
    782 
    783 
    784 def SUB8rr  : I8rr<0x0,
    785                    (outs GR8:$dst), (ins GR8:$src, GR8:$src2),
    786                    "sub.b\t{$src2, $dst}",
    787                    [(set GR8:$dst, (sub GR8:$src, GR8:$src2)),
    788                     (implicit SRW)]>;
    789 def SUB16rr : I16rr<0x0,
    790                     (outs GR16:$dst), (ins GR16:$src, GR16:$src2),
    791                     "sub.w\t{$src2, $dst}",
    792                     [(set GR16:$dst, (sub GR16:$src, GR16:$src2)),
    793                      (implicit SRW)]>;
    794 
    795 def SUB8ri  : I8ri<0x0,
    796                    (outs GR8:$dst), (ins GR8:$src, i8imm:$src2),
    797                    "sub.b\t{$src2, $dst}",
    798                    [(set GR8:$dst, (sub GR8:$src, imm:$src2)),
    799                     (implicit SRW)]>;
    800 def SUB16ri : I16ri<0x0,
    801                     (outs GR16:$dst), (ins GR16:$src, i16imm:$src2),
    802                     "sub.w\t{$src2, $dst}",
    803                     [(set GR16:$dst, (sub GR16:$src, imm:$src2)),
    804                      (implicit SRW)]>;
    805 
    806 def SUB8rm  : I8rm<0x0,
    807                    (outs GR8:$dst), (ins GR8:$src, memsrc:$src2),
    808                    "sub.b\t{$src2, $dst}",
    809                    [(set GR8:$dst, (sub GR8:$src, (load addr:$src2))),
    810                     (implicit SRW)]>;
    811 def SUB16rm : I16rm<0x0,
    812                     (outs GR16:$dst), (ins GR16:$src, memsrc:$src2),
    813                     "sub.w\t{$src2, $dst}",
    814                     [(set GR16:$dst, (sub GR16:$src, (load addr:$src2))),
    815                      (implicit SRW)]>;
    816 
    817 let mayLoad = 1, hasExtraDefRegAllocReq = 1, 
    818 Constraints = "$base = $base_wb, $src = $dst" in {
    819 def SUB8rm_POST : IForm8<0x0, DstReg, SrcPostInc, Size2Bytes,
    820                          (outs GR8:$dst, GR16:$base_wb),
    821                          (ins GR8:$src, GR16:$base),
    822                          "sub.b\t{@$base+, $dst}", []>;
    823 def SUB16rm_POST : IForm16<0x0, DstReg, SrcPostInc, Size2Bytes,
    824                           (outs GR16:$dst, GR16:$base_wb),
    825                           (ins GR16:$src, GR16:$base),
    826                           "sub.w\t{@$base+, $dst}", []>;
    827 }
    828 
    829 let Constraints = "" in {
    830 def SUB8mr  : I8mr<0x0,
    831                    (outs), (ins memdst:$dst, GR8:$src),
    832                    "sub.b\t{$src, $dst}",
    833                    [(store (sub (load addr:$dst), GR8:$src), addr:$dst),
    834                     (implicit SRW)]>;
    835 def SUB16mr : I16mr<0x0,
    836                     (outs), (ins memdst:$dst, GR16:$src),
    837                     "sub.w\t{$src, $dst}",
    838                     [(store (sub (load addr:$dst), GR16:$src), addr:$dst),
    839                      (implicit SRW)]>;
    840 
    841 def SUB8mi  : I8mi<0x0,
    842                    (outs), (ins memdst:$dst, i8imm:$src),
    843                    "sub.b\t{$src, $dst}",
    844                    [(store (sub (load addr:$dst), (i8 imm:$src)), addr:$dst),
    845                     (implicit SRW)]>;
    846 def SUB16mi : I16mi<0x0,
    847                     (outs), (ins memdst:$dst, i16imm:$src),
    848                     "sub.w\t{$src, $dst}",
    849                     [(store (sub (load addr:$dst), (i16 imm:$src)), addr:$dst),
    850                      (implicit SRW)]>;
    851 
    852 def SUB8mm  : I8mm<0x0,
    853                    (outs), (ins memdst:$dst, memsrc:$src),
    854                    "sub.b\t{$src, $dst}",
    855                    [(store (sub (load addr:$dst), 
    856                                 (i8 (load addr:$src))), addr:$dst),
    857                     (implicit SRW)]>;
    858 def SUB16mm : I16mm<0x0,
    859                     (outs), (ins memdst:$dst, memsrc:$src),
    860                     "sub.w\t{$src, $dst}",
    861                     [(store (sub (load addr:$dst), 
    862                                  (i16 (load addr:$src))), addr:$dst),
    863                      (implicit SRW)]>;
    864 }
    865 
    866 let Uses = [SRW] in {
    867 def SBC8rr  : I8rr<0x0,
    868                    (outs GR8:$dst), (ins GR8:$src, GR8:$src2),
    869                    "subc.b\t{$src2, $dst}",
    870                    [(set GR8:$dst, (sube GR8:$src, GR8:$src2)),
    871                     (implicit SRW)]>;
    872 def SBC16rr : I16rr<0x0,
    873                     (outs GR16:$dst), (ins GR16:$src, GR16:$src2),
    874                     "subc.w\t{$src2, $dst}",
    875                     [(set GR16:$dst, (sube GR16:$src, GR16:$src2)),
    876                      (implicit SRW)]>;
    877 
    878 def SBC8ri  : I8ri<0x0,
    879                    (outs GR8:$dst), (ins GR8:$src, i8imm:$src2),
    880                    "subc.b\t{$src2, $dst}",
    881                    [(set GR8:$dst, (sube GR8:$src, imm:$src2)),
    882                     (implicit SRW)]>;
    883 def SBC16ri : I16ri<0x0,
    884                     (outs GR16:$dst), (ins GR16:$src, i16imm:$src2),
    885                     "subc.w\t{$src2, $dst}",
    886                     [(set GR16:$dst, (sube GR16:$src, imm:$src2)),
    887                      (implicit SRW)]>;
    888 
    889 def SBC8rm  : I8rm<0x0,
    890                    (outs GR8:$dst), (ins GR8:$src, memsrc:$src2),
    891                    "subc.b\t{$src2, $dst}",
    892                    [(set GR8:$dst, (sube GR8:$src, (load addr:$src2))),
    893                     (implicit SRW)]>;
    894 def SBC16rm : I16rm<0x0,
    895                     (outs GR16:$dst), (ins GR16:$src, memsrc:$src2),
    896                     "subc.w\t{$src2, $dst}",
    897                     [(set GR16:$dst, (sube GR16:$src, (load addr:$src2))),
    898                      (implicit SRW)]>;
    899 
    900 let Constraints = "" in {
    901 def SBC8mr  : I8mr<0x0,
    902                    (outs), (ins memdst:$dst, GR8:$src),
    903                    "subc.b\t{$src, $dst}",
    904                   [(store (sube (load addr:$dst), GR8:$src), addr:$dst),
    905                    (implicit SRW)]>;
    906 def SBC16mr : I16mr<0x0,
    907                     (outs), (ins memdst:$dst, GR16:$src),
    908                     "subc.w\t{$src, $dst}",
    909                     [(store (sube (load addr:$dst), GR16:$src), addr:$dst),
    910                      (implicit SRW)]>;
    911 
    912 def SBC8mi  : I8mi<0x0,
    913                    (outs), (ins memdst:$dst, i8imm:$src),
    914                    "subc.b\t{$src, $dst}",
    915                    [(store (sube (load addr:$dst), (i8 imm:$src)), addr:$dst),
    916                     (implicit SRW)]>;
    917 def SBC16mi : I16mi<0x0,
    918                     (outs), (ins memdst:$dst, i16imm:$src),
    919                     "subc.w\t{$src, $dst}",
    920                     [(store (sube (load addr:$dst), (i16 imm:$src)), addr:$dst),
    921                      (implicit SRW)]>;
    922 
    923 def SBC8mm  : I8mm<0x0,
    924                    (outs), (ins memdst:$dst, memsrc:$src),
    925                    "subc.b\t{$src, $dst}",
    926                    [(store (sube (load addr:$dst),
    927                                  (i8 (load addr:$src))), addr:$dst),
    928                     (implicit SRW)]>;
    929 def SBC16mm : I16mm<0x0,
    930                     (outs), (ins memdst:$dst, memsrc:$src),
    931                     "subc.w\t{$src, $dst}",
    932                     [(store (sube (load addr:$dst),
    933                             (i16 (load addr:$src))), addr:$dst),
    934                      (implicit SRW)]>;
    935 }
    936 
    937 } // Uses = [SRW]
    938 
    939 // FIXME: memory variant!
    940 def SAR8r1  : II8r<0x0,
    941                    (outs GR8:$dst), (ins GR8:$src),
    942                    "rra.b\t$dst",
    943                    [(set GR8:$dst, (MSP430rra GR8:$src)),
    944                     (implicit SRW)]>;
    945 def SAR16r1 : II16r<0x0,
    946                     (outs GR16:$dst), (ins GR16:$src),
    947                     "rra.w\t$dst",
    948                     [(set GR16:$dst, (MSP430rra GR16:$src)),
    949                      (implicit SRW)]>;
    950 
    951 def SHL8r1  : I8rr<0x0,
    952                    (outs GR8:$dst), (ins GR8:$src),
    953                    "rla.b\t$dst",
    954                    [(set GR8:$dst, (MSP430rla GR8:$src)),
    955                     (implicit SRW)]>;
    956 def SHL16r1 : I16rr<0x0,
    957                     (outs GR16:$dst), (ins GR16:$src),
    958                     "rla.w\t$dst",
    959                     [(set GR16:$dst, (MSP430rla GR16:$src)),
    960                      (implicit SRW)]>;
    961 
    962 def SAR8r1c  : Pseudo<(outs GR8:$dst), (ins GR8:$src),
    963                       "clrc\n\t"
    964                       "rrc.b\t$dst",
    965                       [(set GR8:$dst, (MSP430rrc GR8:$src)),
    966                        (implicit SRW)]>;
    967 def SAR16r1c : Pseudo<(outs GR16:$dst), (ins GR16:$src),
    968                       "clrc\n\t"
    969                       "rrc.w\t$dst",
    970                       [(set GR16:$dst, (MSP430rrc GR16:$src)),
    971                        (implicit SRW)]>;
    972 
    973 // FIXME: Memory sext's ?
    974 def SEXT16r : II16r<0x0,
    975                     (outs GR16:$dst), (ins GR16:$src),
    976                     "sxt\t$dst",
    977                     [(set GR16:$dst, (sext_inreg GR16:$src, i8)),
    978                      (implicit SRW)]>;
    979 
    980 } // Defs = [SRW]
    981 
    982 def ZEXT16r : I8rr<0x0,
    983                    (outs GR16:$dst), (ins GR16:$src),
    984                    "mov.b\t{$src, $dst}",
    985                    [(set GR16:$dst, (zext (trunc GR16:$src)))]>;
    986 
    987 // FIXME: Memory bitswaps?
    988 def SWPB16r : II16r<0x0,
    989                     (outs GR16:$dst), (ins GR16:$src),
    990                     "swpb\t$dst",
    991                     [(set GR16:$dst, (bswap GR16:$src))]>;
    992 
    993 } // Constraints = "$src = $dst"
    994 
    995 // Integer comparisons
    996 let Defs = [SRW] in {
    997 def CMP8rr  : I8rr<0x0,
    998                    (outs), (ins GR8:$src, GR8:$src2),
    999                    "cmp.b\t{$src2, $src}",
   1000                    [(MSP430cmp GR8:$src, GR8:$src2), (implicit SRW)]>;
   1001 def CMP16rr : I16rr<0x0,
   1002                     (outs), (ins GR16:$src, GR16:$src2),
   1003                     "cmp.w\t{$src2, $src}",
   1004                     [(MSP430cmp GR16:$src, GR16:$src2), (implicit SRW)]>;
   1005 
   1006 def CMP8ri  : I8ri<0x0,
   1007                    (outs), (ins GR8:$src, i8imm:$src2),
   1008                    "cmp.b\t{$src2, $src}",
   1009                    [(MSP430cmp GR8:$src, imm:$src2), (implicit SRW)]>;
   1010 def CMP16ri : I16ri<0x0,
   1011                     (outs), (ins GR16:$src, i16imm:$src2),
   1012                     "cmp.w\t{$src2, $src}",
   1013                     [(MSP430cmp GR16:$src, imm:$src2), (implicit SRW)]>;
   1014 
   1015 def CMP8mi  : I8mi<0x0,
   1016                    (outs), (ins memsrc:$src, i8imm:$src2),
   1017                    "cmp.b\t{$src2, $src}",
   1018                    [(MSP430cmp (load addr:$src),
   1019                                (i8 imm:$src2)), (implicit SRW)]>;
   1020 def CMP16mi : I16mi<0x0,
   1021                     (outs), (ins memsrc:$src, i16imm:$src2),
   1022                     "cmp.w\t{$src2, $src}",
   1023                      [(MSP430cmp (load addr:$src),
   1024                                  (i16 imm:$src2)), (implicit SRW)]>;
   1025 
   1026 def CMP8rm  : I8rm<0x0,
   1027                    (outs), (ins GR8:$src, memsrc:$src2),
   1028                    "cmp.b\t{$src2, $src}",
   1029                    [(MSP430cmp GR8:$src, (load addr:$src2)), 
   1030                     (implicit SRW)]>;
   1031 def CMP16rm : I16rm<0x0,
   1032                     (outs), (ins GR16:$src, memsrc:$src2),
   1033                     "cmp.w\t{$src2, $src}",
   1034                     [(MSP430cmp GR16:$src, (load addr:$src2)),
   1035                      (implicit SRW)]>;
   1036 
   1037 def CMP8mr  : I8mr<0x0,
   1038                    (outs), (ins memsrc:$src, GR8:$src2),
   1039                    "cmp.b\t{$src2, $src}",
   1040                    [(MSP430cmp (load addr:$src), GR8:$src2),
   1041                     (implicit SRW)]>;
   1042 def CMP16mr : I16mr<0x0,
   1043                     (outs), (ins memsrc:$src, GR16:$src2),
   1044                     "cmp.w\t{$src2, $src}",
   1045                     [(MSP430cmp (load addr:$src), GR16:$src2), 
   1046                      (implicit SRW)]>;
   1047 
   1048 
   1049 // BIT TESTS, just sets condition codes
   1050 // Note that the C condition is set differently than when using CMP.
   1051 let isCommutable = 1 in {
   1052 def BIT8rr  : I8rr<0x0,
   1053                    (outs), (ins GR8:$src, GR8:$src2),
   1054                    "bit.b\t{$src2, $src}",
   1055                    [(MSP430cmp (and_su GR8:$src, GR8:$src2), 0),
   1056                     (implicit SRW)]>;
   1057 def BIT16rr : I16rr<0x0,
   1058                     (outs), (ins GR16:$src, GR16:$src2),
   1059                     "bit.w\t{$src2, $src}",
   1060                     [(MSP430cmp (and_su GR16:$src, GR16:$src2), 0),
   1061                      (implicit SRW)]>;
   1062 }
   1063 def BIT8ri  : I8ri<0x0,
   1064                    (outs), (ins GR8:$src, i8imm:$src2),
   1065                    "bit.b\t{$src2, $src}",
   1066                    [(MSP430cmp (and_su GR8:$src, imm:$src2), 0),
   1067                     (implicit SRW)]>;
   1068 def BIT16ri : I16ri<0x0,
   1069                     (outs), (ins GR16:$src, i16imm:$src2),
   1070                     "bit.w\t{$src2, $src}",
   1071                     [(MSP430cmp (and_su GR16:$src, imm:$src2), 0),
   1072                      (implicit SRW)]>;
   1073 
   1074 def BIT8rm  : I8rm<0x0,
   1075                    (outs), (ins GR8:$src, memdst:$src2),
   1076                    "bit.b\t{$src2, $src}",
   1077                    [(MSP430cmp (and_su GR8:$src,  (load addr:$src2)), 0),
   1078                     (implicit SRW)]>;
   1079 def BIT16rm : I16rm<0x0,
   1080                     (outs), (ins GR16:$src, memdst:$src2),
   1081                     "bit.w\t{$src2, $src}",
   1082                     [(MSP430cmp (and_su GR16:$src,  (load addr:$src2)), 0),
   1083                      (implicit SRW)]>;
   1084 
   1085 def BIT8mr  : I8mr<0x0,
   1086                   (outs), (ins memsrc:$src, GR8:$src2),
   1087                   "bit.b\t{$src2, $src}",
   1088                   [(MSP430cmp (and_su (load addr:$src), GR8:$src2), 0),
   1089                    (implicit SRW)]>;
   1090 def BIT16mr : I16mr<0x0,
   1091                     (outs), (ins memsrc:$src, GR16:$src2),
   1092                     "bit.w\t{$src2, $src}",
   1093                     [(MSP430cmp (and_su (load addr:$src), GR16:$src2), 0),
   1094                      (implicit SRW)]>;
   1095 
   1096 def BIT8mi  : I8mi<0x0,
   1097                    (outs), (ins memsrc:$src, i8imm:$src2),
   1098                    "bit.b\t{$src2, $src}",
   1099                    [(MSP430cmp (and_su (load addr:$src), (i8 imm:$src2)), 0),
   1100                     (implicit SRW)]>;
   1101 def BIT16mi : I16mi<0x0,
   1102                     (outs), (ins memsrc:$src, i16imm:$src2),
   1103                     "bit.w\t{$src2, $src}",
   1104                     [(MSP430cmp (and_su (load addr:$src), (i16 imm:$src2)), 0),
   1105                      (implicit SRW)]>;
   1106 
   1107 def BIT8mm  : I8mm<0x0,
   1108                    (outs), (ins memsrc:$src, memsrc:$src2),
   1109                    "bit.b\t{$src2, $src}",
   1110                    [(MSP430cmp (and_su (i8 (load addr:$src)),
   1111                                        (load addr:$src2)),
   1112                                  0),
   1113                       (implicit SRW)]>;
   1114 def BIT16mm : I16mm<0x0,
   1115                     (outs), (ins memsrc:$src, memsrc:$src2),
   1116                     "bit.w\t{$src2, $src}",
   1117                     [(MSP430cmp (and_su (i16 (load addr:$src)),
   1118                                         (load addr:$src2)),
   1119                                  0),
   1120                      (implicit SRW)]>;
   1121 } // Defs = [SRW]
   1122 
   1123 //===----------------------------------------------------------------------===//
   1124 // Non-Instruction Patterns
   1125 
   1126 // extload
   1127 def : Pat<(extloadi16i8 addr:$src), (MOVZX16rm8 addr:$src)>;
   1128 
   1129 // anyext
   1130 def : Pat<(i16 (anyext GR8:$src)),
   1131           (SUBREG_TO_REG (i16 0), GR8:$src, subreg_8bit)>;
   1132 
   1133 // truncs
   1134 def : Pat<(i8 (trunc GR16:$src)),
   1135           (EXTRACT_SUBREG GR16:$src, subreg_8bit)>;
   1136 
   1137 // GlobalAddress, ExternalSymbol
   1138 def : Pat<(i16 (MSP430Wrapper tglobaladdr:$dst)), (MOV16ri tglobaladdr:$dst)>;
   1139 def : Pat<(i16 (MSP430Wrapper texternalsym:$dst)), (MOV16ri texternalsym:$dst)>;
   1140 def : Pat<(i16 (MSP430Wrapper tblockaddress:$dst)), (MOV16ri tblockaddress:$dst)>;
   1141 
   1142 def : Pat<(add GR16:$src, (MSP430Wrapper tglobaladdr :$src2)),
   1143           (ADD16ri GR16:$src, tglobaladdr:$src2)>;
   1144 def : Pat<(add GR16:$src, (MSP430Wrapper texternalsym:$src2)),
   1145           (ADD16ri GR16:$src, texternalsym:$src2)>;
   1146 def : Pat<(add GR16:$src, (MSP430Wrapper tblockaddress:$src2)),
   1147           (ADD16ri GR16:$src, tblockaddress:$src2)>;
   1148 
   1149 def : Pat<(store (i16 (MSP430Wrapper tglobaladdr:$src)), addr:$dst),
   1150           (MOV16mi addr:$dst, tglobaladdr:$src)>;
   1151 def : Pat<(store (i16 (MSP430Wrapper texternalsym:$src)), addr:$dst),
   1152           (MOV16mi addr:$dst, texternalsym:$src)>;
   1153 def : Pat<(store (i16 (MSP430Wrapper tblockaddress:$src)), addr:$dst),
   1154           (MOV16mi addr:$dst, tblockaddress:$src)>;
   1155 
   1156 // calls
   1157 def : Pat<(MSP430call (i16 tglobaladdr:$dst)),
   1158           (CALLi tglobaladdr:$dst)>;
   1159 def : Pat<(MSP430call (i16 texternalsym:$dst)),
   1160           (CALLi texternalsym:$dst)>;
   1161 
   1162 // add and sub always produce carry
   1163 def : Pat<(addc GR16:$src, GR16:$src2),
   1164           (ADD16rr GR16:$src, GR16:$src2)>;
   1165 def : Pat<(addc GR16:$src, (load addr:$src2)),
   1166           (ADD16rm GR16:$src, addr:$src2)>;
   1167 def : Pat<(addc GR16:$src, imm:$src2),
   1168           (ADD16ri GR16:$src, imm:$src2)>;
   1169 def : Pat<(store (addc (load addr:$dst), GR16:$src), addr:$dst),
   1170           (ADD16mr addr:$dst, GR16:$src)>;
   1171 def : Pat<(store (addc (load addr:$dst), (i16 (load addr:$src))), addr:$dst),
   1172           (ADD16mm addr:$dst, addr:$src)>;
   1173 
   1174 def : Pat<(addc GR8:$src, GR8:$src2),
   1175           (ADD8rr GR8:$src, GR8:$src2)>;
   1176 def : Pat<(addc GR8:$src, (load addr:$src2)),
   1177           (ADD8rm GR8:$src, addr:$src2)>;
   1178 def : Pat<(addc GR8:$src, imm:$src2),
   1179           (ADD8ri GR8:$src, imm:$src2)>;
   1180 def : Pat<(store (addc (load addr:$dst), GR8:$src), addr:$dst),
   1181           (ADD8mr addr:$dst, GR8:$src)>;
   1182 def : Pat<(store (addc (load addr:$dst), (i8 (load addr:$src))), addr:$dst),
   1183           (ADD8mm addr:$dst, addr:$src)>;
   1184 
   1185 def : Pat<(subc GR16:$src, GR16:$src2),
   1186           (SUB16rr GR16:$src, GR16:$src2)>;
   1187 def : Pat<(subc GR16:$src, (load addr:$src2)),
   1188           (SUB16rm GR16:$src, addr:$src2)>;
   1189 def : Pat<(subc GR16:$src, imm:$src2),
   1190           (SUB16ri GR16:$src, imm:$src2)>;
   1191 def : Pat<(store (subc (load addr:$dst), GR16:$src), addr:$dst),
   1192           (SUB16mr addr:$dst, GR16:$src)>;
   1193 def : Pat<(store (subc (load addr:$dst), (i16 (load addr:$src))), addr:$dst),
   1194           (SUB16mm addr:$dst, addr:$src)>;
   1195 
   1196 def : Pat<(subc GR8:$src, GR8:$src2),
   1197           (SUB8rr GR8:$src, GR8:$src2)>;
   1198 def : Pat<(subc GR8:$src, (load addr:$src2)),
   1199           (SUB8rm GR8:$src, addr:$src2)>;
   1200 def : Pat<(subc GR8:$src, imm:$src2),
   1201           (SUB8ri GR8:$src, imm:$src2)>;
   1202 def : Pat<(store (subc (load addr:$dst), GR8:$src), addr:$dst),
   1203           (SUB8mr addr:$dst, GR8:$src)>;
   1204 def : Pat<(store (subc (load addr:$dst), (i8 (load addr:$src))), addr:$dst),
   1205           (SUB8mm addr:$dst, addr:$src)>;
   1206 
   1207 // peephole patterns
   1208 def : Pat<(and GR16:$src, 255), (ZEXT16r GR16:$src)>;
   1209 def : Pat<(MSP430cmp (trunc (and_su GR16:$src, GR16:$src2)), 0),
   1210           (BIT8rr (EXTRACT_SUBREG GR16:$src, subreg_8bit),
   1211                   (EXTRACT_SUBREG GR16:$src2, subreg_8bit))>;
   1212