Emit more efficient 64-bit operations when the RHS is a constant, and one
[oota-llvm.git] / lib / Target / X86 / X86ISelSimple.cpp
index 369b203e61462f9ded65991c6dba81810a1b87f2..1d4b7c97e227895118184a5b3d7817cdcf802145 100644 (file)
@@ -107,6 +107,7 @@ namespace {
     /// LowerUnknownIntrinsicFunctionCalls - This performs a prepass over the
     /// function, lowering any calls to unknown intrinsic functions into the
     /// equivalent LLVM code.
+    ///
     void LowerUnknownIntrinsicFunctionCalls(Function &F);
 
     /// LoadArgumentsToVirtualRegs - Load all of the arguments to this function
@@ -173,6 +174,8 @@ namespace {
     unsigned EmitComparison(unsigned OpNum, Value *Op0, Value *Op1,
                             MachineBasicBlock *MBB,
                             MachineBasicBlock::iterator MBBI);
+    void visitSelectInst(SelectInst &SI);
+    
     
     // Memory Instructions
     void visitLoadInst(LoadInst &I);
@@ -198,8 +201,14 @@ namespace {
     ///
     void promote32(unsigned targetReg, const ValueRecord &VR);
 
-    // getGEPIndex - This is used to fold GEP instructions into X86 addressing
-    // expressions.
+    /// getAddressingMode - Get the addressing mode to use to address the
+    /// specified value.  The returned value should be used with addFullAddress.
+    void getAddressingMode(Value *Addr, unsigned &BaseReg, unsigned &Scale,
+                           unsigned &IndexReg, unsigned &Disp);
+
+
+    /// getGEPIndex - This is used to fold GEP instructions into X86 addressing
+    /// expressions.
     void getGEPIndex(MachineBasicBlock *MBB, MachineBasicBlock::iterator IP,
                      std::vector<Value*> &GEPOps,
                      std::vector<const Type*> &GEPTypes, unsigned &BaseReg,
@@ -221,11 +230,13 @@ namespace {
 
     /// emitCastOperation - Common code shared between visitCastInst and
     /// constant expression cast support.
+    ///
     void emitCastOperation(MachineBasicBlock *BB,MachineBasicBlock::iterator IP,
                            Value *Src, const Type *DestTy, unsigned TargetReg);
 
     /// emitSimpleBinaryOperation - Common code shared between visitSimpleBinary
     /// and constant expression support.
+    ///
     void emitSimpleBinaryOperation(MachineBasicBlock *BB,
                                    MachineBasicBlock::iterator IP,
                                    Value *Op0, Value *Op1,
@@ -238,6 +249,7 @@ namespace {
 
     /// emitSetCCOperation - Common code shared between visitSetCondInst and
     /// constant expression support.
+    ///
     void emitSetCCOperation(MachineBasicBlock *BB,
                             MachineBasicBlock::iterator IP,
                             Value *Op0, Value *Op1, unsigned Opcode,
@@ -245,11 +257,18 @@ namespace {
 
     /// emitShiftOperation - Common code shared between visitShiftInst and
     /// constant expression support.
+    ///
     void emitShiftOperation(MachineBasicBlock *MBB,
                             MachineBasicBlock::iterator IP,
                             Value *Op, Value *ShiftAmount, bool isLeftShift,
                             const Type *ResultTy, unsigned DestReg);
       
+    /// emitSelectOperation - Common code shared between visitSelectInst and the
+    /// constant expression support.
+    void emitSelectOperation(MachineBasicBlock *MBB,
+                             MachineBasicBlock::iterator IP,
+                             Value *Cond, Value *TrueVal, Value *FalseVal,
+                             unsigned DestReg);
 
     /// copyConstantToRegister - Output the instructions required to put the
     /// specified constant into the specified register.
@@ -415,6 +434,11 @@ void ISel::copyConstantToRegister(MachineBasicBlock *MBB,
                          CE->getOpcode() == Instruction::Shl, CE->getType(), R);
       return;
 
+    case Instruction::Select:
+      emitSelectOperation(MBB, IP, CE->getOperand(0), CE->getOperand(1),
+                          CE->getOperand(2), R);
+      return;
+
     default:
       std::cerr << "Offending expr: " << C << "\n";
       assert(0 && "Constant expression not yet handled!\n");
@@ -586,17 +610,24 @@ void ISel::SelectPHINodes() {
           // If this is a constant or GlobalValue, we may have to insert code
           // into the basic block to compute it into a virtual register.
           if (isa<Constant>(Val) || isa<GlobalValue>(Val)) {
-            // Because we don't want to clobber any values which might be in
-            // physical registers with the computation of this constant (which
-            // might be arbitrarily complex if it is a constant expression),
-            // just insert the computation at the top of the basic block.
-            MachineBasicBlock::iterator PI = PredMBB->begin();
-
-            // Skip over any PHI nodes though!
-            while (PI != PredMBB->end() && PI->getOpcode() == X86::PHI)
-              ++PI;
-
-            ValReg = getReg(Val, PredMBB, PI);
+            if (isa<ConstantExpr>(Val)) {
+              // Because we don't want to clobber any values which might be in
+              // physical registers with the computation of this constant (which
+              // might be arbitrarily complex if it is a constant expression),
+              // just insert the computation at the top of the basic block.
+              MachineBasicBlock::iterator PI = PredMBB->begin();
+              
+              // Skip over any PHI nodes though!
+              while (PI != PredMBB->end() && PI->getOpcode() == X86::PHI)
+                ++PI;
+              
+              ValReg = getReg(Val, PredMBB, PI);
+            } else {
+              // Simple constants get emitted at the end of the basic block,
+              // before any terminator instructions.  We "know" that the code to
+              // move a constant into a register will never clobber any flags.
+              ValReg = getReg(Val, PredMBB, PredMBB->getFirstTerminator());
+            }
           } else {
             ValReg = getReg(Val);
           }
@@ -712,19 +743,20 @@ void ISel::InsertFPRegKills() {
 }
 
 
-// canFoldSetCCIntoBranch - Return the setcc instruction if we can fold it into
-// the conditional branch instruction which is the only user of the cc
-// instruction.  This is the case if the conditional branch is the only user of
-// the setcc, and if the setcc is in the same basic block as the conditional
-// branch.  We also don't handle long arguments below, so we reject them here as
-// well.
+// canFoldSetCCIntoBranchOrSelect - Return the setcc instruction if we can fold
+// it into the conditional branch or select instruction which is the only user
+// of the cc instruction.  This is the case if the conditional branch is the
+// only user of the setcc, and if the setcc is in the same basic block as the
+// conditional branch.  We also don't handle long arguments below, so we reject
+// them here as well.
 //
-static SetCondInst *canFoldSetCCIntoBranch(Value *V) {
+static SetCondInst *canFoldSetCCIntoBranchOrSelect(Value *V) {
   if (SetCondInst *SCI = dyn_cast<SetCondInst>(V))
-    if (SCI->hasOneUse() && isa<BranchInst>(SCI->use_back()) &&
-        SCI->getParent() == cast<BranchInst>(SCI->use_back())->getParent()) {
-      const Type *Ty = SCI->getOperand(0)->getType();
-      if (Ty != Type::LongTy && Ty != Type::ULongTy)
+    if (SCI->hasOneUse()) {
+      Instruction *User = cast<Instruction>(SCI->use_back());
+      if ((isa<BranchInst>(User) || isa<SelectInst>(User)) &&
+          SCI->getParent() == User->getParent() &&
+          getClassB(SCI->getOperand(0)->getType()) != cLong)
         return SCI;
     }
   return 0;
@@ -872,12 +904,12 @@ unsigned ISel::EmitComparison(unsigned OpNum, Value *Op0, Value *Op1,
   return OpNum;
 }
 
-
 /// SetCC instructions - Here we just emit boilerplate code to set a byte-sized
 /// register, then move it to wherever the result should be. 
 ///
 void ISel::visitSetCondInst(SetCondInst &I) {
-  if (canFoldSetCCIntoBranch(&I)) return;  // Fold this into a branch...
+  if (canFoldSetCCIntoBranchOrSelect(&I))
+    return;  // Fold this into a branch or select.
 
   unsigned DestReg = getReg(I);
   MachineBasicBlock::iterator MII = BB->end();
@@ -887,6 +919,7 @@ void ISel::visitSetCondInst(SetCondInst &I) {
 
 /// emitSetCCOperation - Common code shared between visitSetCondInst and
 /// constant expression support.
+///
 void ISel::emitSetCCOperation(MachineBasicBlock *MBB,
                               MachineBasicBlock::iterator IP,
                               Value *Op0, Value *Op1, unsigned Opcode,
@@ -908,18 +941,193 @@ void ISel::emitSetCCOperation(MachineBasicBlock *MBB,
   }
 }
 
+void ISel::visitSelectInst(SelectInst &SI) {
+  unsigned DestReg = getReg(SI);
+  MachineBasicBlock::iterator MII = BB->end();
+  emitSelectOperation(BB, MII, SI.getCondition(), SI.getTrueValue(),
+                      SI.getFalseValue(), DestReg);
+}
+/// emitSelect - Common code shared between visitSelectInst and the constant
+/// expression support.
+void ISel::emitSelectOperation(MachineBasicBlock *MBB,
+                               MachineBasicBlock::iterator IP,
+                               Value *Cond, Value *TrueVal, Value *FalseVal,
+                               unsigned DestReg) {
+  unsigned SelectClass = getClassB(TrueVal->getType());
+  
+  // We don't support 8-bit conditional moves.  If we have incoming constants,
+  // transform them into 16-bit constants to avoid having a run-time conversion.
+  if (SelectClass == cByte) {
+    if (Constant *T = dyn_cast<Constant>(TrueVal))
+      TrueVal = ConstantExpr::getCast(T, Type::ShortTy);
+    if (Constant *F = dyn_cast<Constant>(FalseVal))
+      FalseVal = ConstantExpr::getCast(F, Type::ShortTy);
+  }
+
+  
+  unsigned Opcode;
+  if (SetCondInst *SCI = canFoldSetCCIntoBranchOrSelect(Cond)) {
+    // We successfully folded the setcc into the select instruction.
+    
+    unsigned OpNum = getSetCCNumber(SCI->getOpcode());
+    OpNum = EmitComparison(OpNum, SCI->getOperand(0), SCI->getOperand(1), MBB,
+                           IP);
+
+    const Type *CompTy = SCI->getOperand(0)->getType();
+    bool isSigned = CompTy->isSigned() && getClassB(CompTy) != cFP;
+  
+    // LLVM  -> X86 signed  X86 unsigned
+    // -----    ----------  ------------
+    // seteq -> cmovNE      cmovNE
+    // setne -> cmovE       cmovE
+    // setlt -> cmovGE      cmovAE
+    // setge -> cmovL       cmovB
+    // setgt -> cmovLE      cmovBE
+    // setle -> cmovG       cmovA
+    // ----
+    //          cmovNS              // Used by comparison with 0 optimization
+    //          cmovS
+    
+    switch (SelectClass) {
+    default: assert(0 && "Unknown value class!");
+    case cFP: {
+      // Annoyingly, we don't have a full set of floating point conditional
+      // moves.  :(
+      static const unsigned OpcodeTab[2][8] = {
+        { X86::FCMOVNE, X86::FCMOVE, X86::FCMOVAE, X86::FCMOVB,
+          X86::FCMOVBE, X86::FCMOVA, 0, 0 },
+        { X86::FCMOVNE, X86::FCMOVE, 0, 0, 0, 0, 0, 0 },
+      };
+      Opcode = OpcodeTab[isSigned][OpNum];
+
+      // If opcode == 0, we hit a case that we don't support.  Output a setcc
+      // and compare the result against zero.
+      if (Opcode == 0) {
+        unsigned CompClass = getClassB(CompTy);
+        unsigned CondReg;
+        if (CompClass != cLong || OpNum < 2) {
+          CondReg = makeAnotherReg(Type::BoolTy);
+          // Handle normal comparisons with a setcc instruction...
+          BuildMI(*MBB, IP, SetCCOpcodeTab[isSigned][OpNum], 0, CondReg);
+        } else {
+          // Long comparisons end up in the BL register.
+          CondReg = X86::BL;
+        }
+        
+        BuildMI(*MBB, IP, X86::TEST8rr, 2).addReg(CondReg).addReg(CondReg);
+        Opcode = X86::FCMOVE;
+      }
+      break;
+    }
+    case cByte:
+    case cShort: {
+      static const unsigned OpcodeTab[2][8] = {
+        { X86::CMOVNE16rr, X86::CMOVE16rr, X86::CMOVAE16rr, X86::CMOVB16rr,
+          X86::CMOVBE16rr, X86::CMOVA16rr, 0, 0 },
+        { X86::CMOVNE16rr, X86::CMOVE16rr, X86::CMOVGE16rr, X86::CMOVL16rr,
+          X86::CMOVLE16rr, X86::CMOVG16rr, X86::CMOVNS16rr, X86::CMOVS16rr },
+      };
+      Opcode = OpcodeTab[isSigned][OpNum];
+      break;
+    }
+    case cInt:
+    case cLong: {
+      static const unsigned OpcodeTab[2][8] = {
+        { X86::CMOVNE32rr, X86::CMOVE32rr, X86::CMOVAE32rr, X86::CMOVB32rr,
+          X86::CMOVBE32rr, X86::CMOVA32rr, 0, 0 },
+        { X86::CMOVNE32rr, X86::CMOVE32rr, X86::CMOVGE32rr, X86::CMOVL32rr,
+          X86::CMOVLE32rr, X86::CMOVG32rr, X86::CMOVNS32rr, X86::CMOVS32rr },
+      };
+      Opcode = OpcodeTab[isSigned][OpNum];
+      break;
+    }
+    }
+  } else {
+    // Get the value being branched on, and use it to set the condition codes.
+    unsigned CondReg = getReg(Cond, MBB, IP);
+    BuildMI(*MBB, IP, X86::TEST8rr, 2).addReg(CondReg).addReg(CondReg);
+    switch (SelectClass) {
+    default: assert(0 && "Unknown value class!");
+    case cFP:    Opcode = X86::FCMOVE; break;
+    case cByte:
+    case cShort: Opcode = X86::CMOVE16rr; break;
+    case cInt:
+    case cLong:  Opcode = X86::CMOVE32rr; break;
+    }
+  }
+
+  unsigned TrueReg  = getReg(TrueVal, MBB, IP);
+  unsigned FalseReg = getReg(FalseVal, MBB, IP);
+  unsigned RealDestReg = DestReg;
+
+
+  // Annoyingly enough, X86 doesn't HAVE 8-bit conditional moves.  Because of
+  // this, we have to promote the incoming values to 16 bits, perform a 16-bit
+  // cmove, then truncate the result.
+  if (SelectClass == cByte) {
+    DestReg = makeAnotherReg(Type::ShortTy);
+    if (getClassB(TrueVal->getType()) == cByte) {
+      // Promote the true value, by storing it into AL, and reading from AX.
+      BuildMI(*MBB, IP, X86::MOV8rr, 1, X86::AL).addReg(TrueReg);
+      BuildMI(*MBB, IP, X86::MOV8ri, 1, X86::AH).addImm(0);
+      TrueReg = makeAnotherReg(Type::ShortTy);
+      BuildMI(*MBB, IP, X86::MOV16rr, 1, TrueReg).addReg(X86::AX);
+    }
+    if (getClassB(FalseVal->getType()) == cByte) {
+      // Promote the true value, by storing it into CL, and reading from CX.
+      BuildMI(*MBB, IP, X86::MOV8rr, 1, X86::CL).addReg(FalseReg);
+      BuildMI(*MBB, IP, X86::MOV8ri, 1, X86::CH).addImm(0);
+      FalseReg = makeAnotherReg(Type::ShortTy);
+      BuildMI(*MBB, IP, X86::MOV16rr, 1, FalseReg).addReg(X86::CX);
+    }
+  }
+
+  BuildMI(*MBB, IP, Opcode, 2, DestReg).addReg(TrueReg).addReg(FalseReg);
+
+  switch (SelectClass) {
+  case cByte:
+    // We did the computation with 16-bit registers.  Truncate back to our
+    // result by copying into AX then copying out AL.
+    BuildMI(*MBB, IP, X86::MOV16rr, 1, X86::AX).addReg(DestReg);
+    BuildMI(*MBB, IP, X86::MOV8rr, 1, RealDestReg).addReg(X86::AL);
+    break;
+  case cLong:
+    // Move the upper half of the value as well.
+    BuildMI(*MBB, IP, Opcode, 2,DestReg+1).addReg(TrueReg+1).addReg(FalseReg+1);
+    break;
+  }
+}
 
 
 
 /// promote32 - Emit instructions to turn a narrow operand into a 32-bit-wide
 /// operand, in the specified target register.
+///
 void ISel::promote32(unsigned targetReg, const ValueRecord &VR) {
   bool isUnsigned = VR.Ty->isUnsigned();
 
+  Value *Val = VR.Val;
+  const Type *Ty = VR.Ty;
+  if (Val) {
+    if (Constant *C = dyn_cast<Constant>(Val)) {
+      Val = ConstantExpr::getCast(C, Type::IntTy);
+      Ty = Type::IntTy;
+    }
+
+    // If this is a simple constant, just emit a MOVri directly to avoid the
+    // copy.
+    if (ConstantInt *CI = dyn_cast<ConstantInt>(Val)) {
+      int TheVal = CI->getRawValue() & 0xFFFFFFFF;
+    BuildMI(BB, X86::MOV32ri, 1, targetReg).addImm(TheVal);
+      return;
+    }
+  }
+
   // Make sure we have the register number for this value...
-  unsigned Reg = VR.Val ? getReg(VR.Val) : VR.Reg;
+  unsigned Reg = Val ? getReg(Val) : VR.Reg;
 
-  switch (getClassB(VR.Ty)) {
+  switch (getClassB(Ty)) {
   case cByte:
     // Extend value into target register (8->32)
     if (isUnsigned)
@@ -961,27 +1169,30 @@ void ISel::visitReturnInst(ReturnInst &I) {
   }
 
   Value *RetVal = I.getOperand(0);
-  unsigned RetReg = getReg(RetVal);
   switch (getClassB(RetVal->getType())) {
   case cByte:   // integral return values: extend or move into EAX and return
   case cShort:
   case cInt:
-    promote32(X86::EAX, ValueRecord(RetReg, RetVal->getType()));
+    promote32(X86::EAX, ValueRecord(RetVal));
     // Declare that EAX is live on exit
     BuildMI(BB, X86::IMPLICIT_USE, 2).addReg(X86::EAX).addReg(X86::ESP);
     break;
-  case cFP:                   // Floats & Doubles: Return in ST(0)
+  case cFP: {                  // Floats & Doubles: Return in ST(0)
+    unsigned RetReg = getReg(RetVal);
     BuildMI(BB, X86::FpSETRESULT, 1).addReg(RetReg);
     // Declare that top-of-stack is live on exit
     BuildMI(BB, X86::IMPLICIT_USE, 2).addReg(X86::ST0).addReg(X86::ESP);
     break;
-  case cLong:
+  }
+  case cLong: {
+    unsigned RetReg = getReg(RetVal);
     BuildMI(BB, X86::MOV32rr, 1, X86::EAX).addReg(RetReg);
     BuildMI(BB, X86::MOV32rr, 1, X86::EDX).addReg(RetReg+1);
     // Declare that EAX & EDX are live on exit
     BuildMI(BB, X86::IMPLICIT_USE, 3).addReg(X86::EAX).addReg(X86::EDX)
       .addReg(X86::ESP);
     break;
+  }
   default:
     visitInstruction(I);
   }
@@ -1011,12 +1222,12 @@ void ISel::visitBranchInst(BranchInst &BI) {
   }
 
   // See if we can fold the setcc into the branch itself...
-  SetCondInst *SCI = canFoldSetCCIntoBranch(BI.getCondition());
+  SetCondInst *SCI = canFoldSetCCIntoBranchOrSelect(BI.getCondition());
   if (SCI == 0) {
     // Nope, cannot fold setcc into this branch.  Emit a branch on a condition
     // computed some other way...
     unsigned condReg = getReg(BI.getCondition());
-    BuildMI(BB, X86::CMP8ri, 2).addReg(condReg).addImm(0);
+    BuildMI(BB, X86::TEST8rr, 2).addReg(condReg).addReg(condReg);
     if (BI.getSuccessor(1) == NextBB) {
       if (BI.getSuccessor(0) != NextBB)
         BuildMI(BB, X86::JNE, 1).addPCDisp(BI.getSuccessor(0));
@@ -1221,6 +1432,7 @@ void ISel::visitCallInst(CallInst &CI) {
 /// LowerUnknownIntrinsicFunctionCalls - This performs a prepass over the
 /// function, lowering any calls to unknown intrinsic functions into the
 /// equivalent LLVM code.
+///
 void ISel::LowerUnknownIntrinsicFunctionCalls(Function &F) {
   for (Function::iterator BB = F.begin(), E = F.end(); BB != E; ++BB)
     for (BasicBlock::iterator I = BB->begin(), E = BB->end(); I != E; )
@@ -1228,9 +1440,9 @@ void ISel::LowerUnknownIntrinsicFunctionCalls(Function &F) {
         if (Function *F = CI->getCalledFunction())
           switch (F->getIntrinsicID()) {
           case Intrinsic::not_intrinsic:
-          case Intrinsic::va_start:
-          case Intrinsic::va_copy:
-          case Intrinsic::va_end:
+          case Intrinsic::vastart:
+          case Intrinsic::vacopy:
+          case Intrinsic::vaend:
           case Intrinsic::returnaddress:
           case Intrinsic::frameaddress:
           case Intrinsic::memcpy:
@@ -1253,18 +1465,18 @@ void ISel::LowerUnknownIntrinsicFunctionCalls(Function &F) {
 void ISel::visitIntrinsicCall(Intrinsic::ID ID, CallInst &CI) {
   unsigned TmpReg1, TmpReg2;
   switch (ID) {
-  case Intrinsic::va_start:
+  case Intrinsic::vastart:
     // Get the address of the first vararg value...
     TmpReg1 = getReg(CI);
     addFrameReference(BuildMI(BB, X86::LEA32r, 5, TmpReg1), VarArgsFrameIndex);
     return;
 
-  case Intrinsic::va_copy:
+  case Intrinsic::vacopy:
     TmpReg1 = getReg(CI);
     TmpReg2 = getReg(CI.getOperand(1));
     BuildMI(BB, X86::MOV32rr, 1, TmpReg1).addReg(TmpReg2);
     return;
-  case Intrinsic::va_end: return;   // Noop on X86
+  case Intrinsic::vaend: return;   // Noop on X86
 
   case Intrinsic::returnaddress:
   case Intrinsic::frameaddress:
@@ -1400,15 +1612,68 @@ void ISel::visitIntrinsicCall(Intrinsic::ID ID, CallInst &CI) {
   }
 }
 
+static bool isSafeToFoldLoadIntoInstruction(LoadInst &LI, Instruction &User) {
+  if (LI.getParent() != User.getParent())
+    return false;
+  BasicBlock::iterator It = &LI;
+  // Check all of the instructions between the load and the user.  We should
+  // really use alias analysis here, but for now we just do something simple.
+  for (++It; It != BasicBlock::iterator(&User); ++It) {
+    switch (It->getOpcode()) {
+    case Instruction::Free:
+    case Instruction::Store:
+    case Instruction::Call:
+    case Instruction::Invoke:
+      return false;
+    }
+  }
+  return true;
+}
+
 
 /// visitSimpleBinary - Implement simple binary operators for integral types...
 /// OperatorClass is one of: 0 for Add, 1 for Sub, 2 for And, 3 for Or, 4 for
 /// Xor.
+///
 void ISel::visitSimpleBinary(BinaryOperator &B, unsigned OperatorClass) {
   unsigned DestReg = getReg(B);
   MachineBasicBlock::iterator MI = BB->end();
-  emitSimpleBinaryOperation(BB, MI, B.getOperand(0), B.getOperand(1),
-                            OperatorClass, DestReg);
+  Value *Op0 = B.getOperand(0), *Op1 = B.getOperand(1);
+
+  // Special case: op Reg, load [mem]
+  if (isa<LoadInst>(Op0) && !isa<LoadInst>(Op1))
+    if (!B.swapOperands())
+      std::swap(Op0, Op1);  // Make sure any loads are in the RHS.
+
+  unsigned Class = getClassB(B.getType());
+  if (isa<LoadInst>(Op1) && Class < cFP &&
+      isSafeToFoldLoadIntoInstruction(*cast<LoadInst>(Op1), B)) {
+
+    static const unsigned OpcodeTab[][3] = {
+      // Arithmetic operators
+      { X86::ADD8rm, X86::ADD16rm, X86::ADD32rm },  // ADD
+      { X86::SUB8rm, X86::SUB16rm, X86::SUB32rm },  // SUB
+      
+      // Bitwise operators
+      { X86::AND8rm, X86::AND16rm, X86::AND32rm },  // AND
+      { X86:: OR8rm, X86:: OR16rm, X86:: OR32rm },  // OR
+      { X86::XOR8rm, X86::XOR16rm, X86::XOR32rm },  // XOR
+    };
+  
+    assert(Class < cFP && "General code handles 64-bit integer types!");
+    unsigned Opcode = OpcodeTab[OperatorClass][Class];
+
+    unsigned BaseReg, Scale, IndexReg, Disp;
+    getAddressingMode(cast<LoadInst>(Op1)->getOperand(0), BaseReg,
+                      Scale, IndexReg, Disp);
+
+    unsigned Op0r = getReg(Op0);
+    addFullAddress(BuildMI(BB, Opcode, 2, DestReg).addReg(Op0r),
+                   BaseReg, Scale, IndexReg, Disp);
+    return;
+  }
+
+  emitSimpleBinaryOperation(BB, MI, Op0, Op1, OperatorClass, DestReg);
 }
 
 /// emitSimpleBinaryOperation - Implement simple binary operators for integral
@@ -1425,22 +1690,24 @@ void ISel::emitSimpleBinaryOperation(MachineBasicBlock *MBB,
   unsigned Class = getClassB(Op0->getType());
 
   // sub 0, X -> neg X
-  if (OperatorClass == 1 && Class != cLong)
+  if (OperatorClass == 1)
     if (ConstantInt *CI = dyn_cast<ConstantInt>(Op0)) {
       if (CI->isNullValue()) {
         unsigned op1Reg = getReg(Op1, MBB, IP);
-        switch (Class) {
-        default: assert(0 && "Unknown class for this function!");
-        case cByte:
-          BuildMI(*MBB, IP, X86::NEG8r, 1, DestReg).addReg(op1Reg);
-          return;
-        case cShort:
-          BuildMI(*MBB, IP, X86::NEG16r, 1, DestReg).addReg(op1Reg);
-          return;
-        case cInt:
-          BuildMI(*MBB, IP, X86::NEG32r, 1, DestReg).addReg(op1Reg);
-          return;
+        static unsigned const NEGTab[] = {
+          X86::NEG8r, X86::NEG16r, X86::NEG32r, 0, X86::NEG32r
+        };
+        BuildMI(*MBB, IP, NEGTab[Class], 1, DestReg).addReg(op1Reg);
+
+        if (Class == cLong) {
+          // We just emitted: Dl = neg Sl
+          // Now emit       : T  = addc Sh, 0
+          //                : Dh = neg T
+          unsigned T = makeAnotherReg(Type::IntTy);
+          BuildMI(*MBB, IP, X86::ADC32ri, 2, T).addReg(op1Reg+1).addImm(0);
+          BuildMI(*MBB, IP, X86::NEG32r, 1, DestReg+1).addReg(T);
         }
+        return;
       }
     } else if (ConstantFP *CFP = dyn_cast<ConstantFP>(Op0))
       if (CFP->isExactlyValue(-0.0)) {
@@ -1450,83 +1717,131 @@ void ISel::emitSimpleBinaryOperation(MachineBasicBlock *MBB,
         return;
       }
 
-  if (!isa<ConstantInt>(Op1) || Class == cLong) {
-    static const unsigned OpcodeTab[][4] = {
+  // Special case: op Reg, <const>
+  if (isa<ConstantInt>(Op1)) {
+    ConstantInt *Op1C = cast<ConstantInt>(Op1);
+    unsigned Op0r = getReg(Op0, MBB, IP);
+
+    // xor X, -1 -> not X
+    if (OperatorClass == 4 && Op1C->isAllOnesValue()) {
+      static unsigned const NOTTab[] = {
+        X86::NOT8r, X86::NOT16r, X86::NOT32r, 0, X86::NOT32r
+      };
+      BuildMI(*MBB, IP, NOTTab[Class], 1, DestReg).addReg(Op0r);
+      if (Class == cLong)  // Invert the top part too
+        BuildMI(*MBB, IP, X86::NOT32r, 1, DestReg+1).addReg(Op0r+1);
+      return;
+    }
+
+    // add X, -1 -> dec X
+    if (OperatorClass == 0 && Op1C->isAllOnesValue()) {
+      static unsigned const DECTab[] = {
+        X86::DEC8r, X86::DEC16r, X86::DEC32r, 0, X86::DEC32r
+      };
+      BuildMI(*MBB, IP, DECTab[Class], 1, DestReg).addReg(Op0r);
+      if (Class == cLong)  // Dh = sbb Sh, 0
+        BuildMI(*MBB, IP, X86::SBB32ri, 2, DestReg+1).addReg(Op0r+1).addImm(0);
+      return;
+    }
+
+    // add X, 1 -> inc X
+    if (OperatorClass == 0 && Op1C->equalsInt(1)) {
+      static unsigned const INCTab[] = {
+        X86::INC8r, X86::INC16r, X86::INC32r, 0, X86::INC32r
+      };
+      BuildMI(*MBB, IP, INCTab[Class], 1, DestReg).addReg(Op0r);
+      if (Class == cLong)  // Dh = adc Sh, 0
+        BuildMI(*MBB, IP, X86::ADC32ri, 2, DestReg+1).addReg(Op0r+1).addImm(0);
+      return;
+    }
+  
+    static const unsigned OpcodeTab[][5] = {
       // Arithmetic operators
-      { X86::ADD8rr, X86::ADD16rr, X86::ADD32rr, X86::FpADD },  // ADD
-      { X86::SUB8rr, X86::SUB16rr, X86::SUB32rr, X86::FpSUB },  // SUB
-      
+      { X86::ADD8ri, X86::ADD16ri, X86::ADD32ri, 0, X86::ADD32ri },  // ADD
+      { X86::SUB8ri, X86::SUB16ri, X86::SUB32ri, 0, X86::SUB32ri },  // SUB
+    
       // Bitwise operators
-      { X86::AND8rr, X86::AND16rr, X86::AND32rr, 0 },  // AND
-      { X86:: OR8rr, X86:: OR16rr, X86:: OR32rr, 0 },  // OR
-      { X86::XOR8rr, X86::XOR16rr, X86::XOR32rr, 0 },  // XOR
+      { X86::AND8ri, X86::AND16ri, X86::AND32ri, 0, X86::AND32ri },  // AND
+      { X86:: OR8ri, X86:: OR16ri, X86:: OR32ri, 0, X86::OR32ri  },  // OR
+      { X86::XOR8ri, X86::XOR16ri, X86::XOR32ri, 0, X86::XOR32ri },  // XOR
     };
-    
-    bool isLong = false;
-    if (Class == cLong) {
-      isLong = true;
-      Class = cInt;          // Bottom 32 bits are handled just like ints
-    }
-    
+  
     unsigned Opcode = OpcodeTab[OperatorClass][Class];
-    assert(Opcode && "Floating point arguments to logical inst?");
-    unsigned Op0r = getReg(Op0, MBB, IP);
-    unsigned Op1r = getReg(Op1, MBB, IP);
-    BuildMI(*MBB, IP, Opcode, 2, DestReg).addReg(Op0r).addReg(Op1r);
-    
-    if (isLong) {        // Handle the upper 32 bits of long values...
-      static const unsigned TopTab[] = {
-        X86::ADC32rr, X86::SBB32rr, X86::AND32rr, X86::OR32rr, X86::XOR32rr
-      };
-      BuildMI(*MBB, IP, TopTab[OperatorClass], 2,
-          DestReg+1).addReg(Op0r+1).addReg(Op1r+1);
-    }
-    return;
-  }
+    unsigned Op1l = cast<ConstantInt>(Op1C)->getRawValue();
 
-  // Special case: op Reg, <const>
-  ConstantInt *Op1C = cast<ConstantInt>(Op1);
-  unsigned Op0r = getReg(Op0, MBB, IP);
+    if (Class != cLong) {
+      BuildMI(*MBB, IP, Opcode, 2, DestReg).addReg(Op0r).addImm(Op1l);
+      return;
+    } else {
+      // If this is a long value and the high or low bits have a special
+      // property, emit some special cases.
+      unsigned Op1h = cast<ConstantInt>(Op1C)->getRawValue() >> 32LL;
+
+      // If the constant is zero in the low 32-bits, just copy the low part
+      // across and apply the normal 32-bit operation to the high parts.  There
+      // will be no carry or borrow into the top.
+      if (Op1l == 0) {
+        if (OperatorClass != 2) // All but and...
+          BuildMI(*MBB, IP, X86::MOV32rr, 1, DestReg).addReg(Op0r);
+        else
+          BuildMI(*MBB, IP, X86::MOV32ri, 1, DestReg).addImm(0);
+        BuildMI(*MBB, IP, OpcodeTab[OperatorClass][cLong], 2, DestReg+1)
+          .addReg(Op0r+1).addImm(Op1h);
+        return;
+      }
 
-  // xor X, -1 -> not X
-  if (OperatorClass == 4 && Op1C->isAllOnesValue()) {
-    static unsigned const NOTTab[] = { X86::NOT8r, X86::NOT16r, X86::NOT32r };
-    BuildMI(*MBB, IP, NOTTab[Class], 1, DestReg).addReg(Op0r);
-    return;
-  }
+      // If this is a logical operation and the top 32-bits are zero, just
+      // operate on the lower 32.
+      if (Op1h == 0 && OperatorClass > 1) {
+        BuildMI(*MBB, IP, OpcodeTab[OperatorClass][cLong], 2, DestReg)
+          .addReg(Op0r).addImm(Op1l);
+        if (OperatorClass != 2)  // All but and
+          BuildMI(*MBB, IP, X86::MOV32rr, 1, DestReg+1).addReg(Op0r+1);
+        else
+          BuildMI(*MBB, IP, X86::MOV32ri, 1, DestReg+1).addImm(0);
+        return;
+      }
 
-  // add X, -1 -> dec X
-  if (OperatorClass == 0 && Op1C->isAllOnesValue()) {
-    static unsigned const DECTab[] = { X86::DEC8r, X86::DEC16r, X86::DEC32r };
-    BuildMI(*MBB, IP, DECTab[Class], 1, DestReg).addReg(Op0r);
-    return;
-  }
+      // TODO: We could handle lots of other special cases here, such as AND'ing
+      // with 0xFFFFFFFF00000000 -> noop, etc.
 
-  // add X, 1 -> inc X
-  if (OperatorClass == 0 && Op1C->equalsInt(1)) {
-    static unsigned const DECTab[] = { X86::INC8r, X86::INC16r, X86::INC32r };
-    BuildMI(*MBB, IP, DECTab[Class], 1, DestReg).addReg(Op0r);
-    return;
+      // Otherwise, code generate the full operation with a constant.
+      static const unsigned TopTab[] = {
+        X86::ADC32ri, X86::SBB32ri, X86::AND32ri, X86::OR32ri, X86::XOR32ri
+      };
+
+      BuildMI(*MBB, IP, Opcode, 2, DestReg).addReg(Op0r).addImm(Op1l);
+      BuildMI(*MBB, IP, TopTab[OperatorClass], 2, DestReg+1)
+          .addReg(Op0r+1).addImm(Op1h);
+      return;
+    }
   }
-  
-  static const unsigned OpcodeTab[][3] = {
+
+  // Finally, handle the general case now.
+  static const unsigned OpcodeTab[][5] = {
     // Arithmetic operators
-    { X86::ADD8ri, X86::ADD16ri, X86::ADD32ri },  // ADD
-    { X86::SUB8ri, X86::SUB16ri, X86::SUB32ri },  // SUB
-    
+    { X86::ADD8rr, X86::ADD16rr, X86::ADD32rr, X86::FpADD, X86::ADD32rr },// ADD
+    { X86::SUB8rr, X86::SUB16rr, X86::SUB32rr, X86::FpSUB, X86::SUB32rr },// SUB
+      
     // Bitwise operators
-    { X86::AND8ri, X86::AND16ri, X86::AND32ri },  // AND
-    { X86:: OR8ri, X86:: OR16ri, X86:: OR32ri },  // OR
-    { X86::XOR8ri, X86::XOR16ri, X86::XOR32ri },  // XOR
+    { X86::AND8rr, X86::AND16rr, X86::AND32rr, 0, X86::AND32rr },  // AND
+    { X86:: OR8rr, X86:: OR16rr, X86:: OR32rr, 0, X86:: OR32rr },  // OR
+    { X86::XOR8rr, X86::XOR16rr, X86::XOR32rr, 0, X86::XOR32rr },  // XOR
   };
-  
-  assert(Class < 3 && "General code handles 64-bit integer types!");
+    
   unsigned Opcode = OpcodeTab[OperatorClass][Class];
-  uint64_t Op1v = cast<ConstantInt>(Op1C)->getRawValue();
-  
-  // Mask off any upper bits of the constant, if there are any...
-  Op1v &= (1ULL << (8 << Class)) - 1;
-  BuildMI(*MBB, IP, Opcode, 2, DestReg).addReg(Op0r).addImm(Op1v);
+  assert(Opcode && "Floating point arguments to logical inst?");
+  unsigned Op0r = getReg(Op0, MBB, IP);
+  unsigned Op1r = getReg(Op1, MBB, IP);
+  BuildMI(*MBB, IP, Opcode, 2, DestReg).addReg(Op0r).addReg(Op1r);
+    
+  if (Class == cLong) {        // Handle the upper 32 bits of long values...
+    static const unsigned TopTab[] = {
+      X86::ADC32rr, X86::SBB32rr, X86::AND32rr, X86::OR32rr, X86::XOR32rr
+    };
+    BuildMI(*MBB, IP, TopTab[OperatorClass], 2,
+            DestReg+1).addReg(Op0r+1).addReg(Op1r+1);
+  }
 }
 
 /// doMultiply - Emit appropriate instructions to multiply together the
@@ -1895,31 +2210,66 @@ void ISel::emitShiftOperation(MachineBasicBlock *MBB,
 }
 
 
-/// visitLoadInst - Implement LLVM load instructions in terms of the x86 'mov'
-/// instruction.  The load and store instructions are the only place where we
-/// need to worry about the memory layout of the target machine.
-///
-void ISel::visitLoadInst(LoadInst &I) {
-  unsigned DestReg = getReg(I);
-  unsigned BaseReg = 0, Scale = 1, IndexReg = 0, Disp = 0;
-  Value *Addr = I.getOperand(0);
+void ISel::getAddressingMode(Value *Addr, unsigned &BaseReg, unsigned &Scale,
+                             unsigned &IndexReg, unsigned &Disp) {
+  BaseReg = 0; Scale = 1; IndexReg = 0; Disp = 0;
   if (GetElementPtrInst *GEP = dyn_cast<GetElementPtrInst>(Addr)) {
     if (isGEPFoldable(BB, GEP->getOperand(0), GEP->op_begin()+1, GEP->op_end(),
                        BaseReg, Scale, IndexReg, Disp))
-      Addr = 0;  // Address is consumed!
+      return;
   } else if (ConstantExpr *CE = dyn_cast<ConstantExpr>(Addr)) {
     if (CE->getOpcode() == Instruction::GetElementPtr)
       if (isGEPFoldable(BB, CE->getOperand(0), CE->op_begin()+1, CE->op_end(),
                         BaseReg, Scale, IndexReg, Disp))
-        Addr = 0;
+        return;
   }
 
-  if (Addr) {
-    // If it's not foldable, reset addr mode.
-    BaseReg = getReg(Addr);
-    Scale = 1; IndexReg = 0; Disp = 0;
+  // If it's not foldable, reset addr mode.
+  BaseReg = getReg(Addr);
+  Scale = 1; IndexReg = 0; Disp = 0;
+}
+
+
+/// visitLoadInst - Implement LLVM load instructions in terms of the x86 'mov'
+/// instruction.  The load and store instructions are the only place where we
+/// need to worry about the memory layout of the target machine.
+///
+void ISel::visitLoadInst(LoadInst &I) {
+  // Check to see if this load instruction is going to be folded into a binary
+  // instruction, like add.  If so, we don't want to emit it.  Wouldn't a real
+  // pattern matching instruction selector be nice?
+  if (I.hasOneUse() && getClassB(I.getType()) < cFP) {
+    Instruction *User = cast<Instruction>(I.use_back());
+    switch (User->getOpcode()) {
+    default: User = 0; break;
+    case Instruction::Add:
+    case Instruction::Sub:
+    case Instruction::And:
+    case Instruction::Or:
+    case Instruction::Xor:
+      break;
+    }
+
+    if (User) {
+      // Okay, we found a user.  If the load is the first operand and there is
+      // no second operand load, reverse the operand ordering.  Note that this
+      // can fail for a subtract (ie, no change will be made).
+      if (!isa<LoadInst>(User->getOperand(1)))
+        cast<BinaryOperator>(User)->swapOperands();
+      
+      // Okay, now that everything is set up, if this load is used by the second
+      // operand, and if there are no instructions that invalidate the load
+      // before the binary operator, eliminate the load.
+      if (User->getOperand(1) == &I &&
+          isSafeToFoldLoadIntoInstruction(I, *User))
+        return;   // Eliminate the load!
+    }
   }
 
+  unsigned DestReg = getReg(I);
+  unsigned BaseReg = 0, Scale = 1, IndexReg = 0, Disp = 0;
+  getAddressingMode(I.getOperand(0), BaseReg, Scale, IndexReg, Disp);
+
   unsigned Class = getClassB(I.getType());
   if (Class == cLong) {
     addFullAddress(BuildMI(BB, X86::MOV32rm, 4, DestReg),
@@ -1942,24 +2292,8 @@ void ISel::visitLoadInst(LoadInst &I) {
 /// instruction.
 ///
 void ISel::visitStoreInst(StoreInst &I) {
-  unsigned BaseReg = 0, Scale = 1, IndexReg = 0, Disp = 0;
-  Value *Addr = I.getOperand(1);
-  if (GetElementPtrInst *GEP = dyn_cast<GetElementPtrInst>(Addr)) {
-    if (isGEPFoldable(BB, GEP->getOperand(0), GEP->op_begin()+1, GEP->op_end(),
-                       BaseReg, Scale, IndexReg, Disp))
-      Addr = 0;  // Address is consumed!
-  } else if (ConstantExpr *CE = dyn_cast<ConstantExpr>(Addr)) {
-    if (CE->getOpcode() == Instruction::GetElementPtr)
-      if (isGEPFoldable(BB, CE->getOperand(0), CE->op_begin()+1, CE->op_end(),
-                        BaseReg, Scale, IndexReg, Disp))
-        Addr = 0;
-  }
-
-  if (Addr) {
-    // If it's not foldable, reset addr mode.
-    BaseReg = getReg(Addr);
-    Scale = 1; IndexReg = 0; Disp = 0;
-  }
+  unsigned BaseReg, Scale, IndexReg, Disp;
+  getAddressingMode(I.getOperand(1), BaseReg, Scale, IndexReg, Disp);
 
   const Type *ValTy = I.getOperand(0)->getType();
   unsigned Class = getClassB(ValTy);
@@ -2003,8 +2337,9 @@ void ISel::visitStoreInst(StoreInst &I) {
 }
 
 
-/// visitCastInst - Here we have various kinds of copying with or without
-/// sign extension going on.
+/// visitCastInst - Here we have various kinds of copying with or without sign
+/// extension going on.
+///
 void ISel::visitCastInst(CastInst &CI) {
   Value *Op = CI.getOperand(0);
   // If this is a cast from a 32-bit integer to a Long type, and the only uses
@@ -2028,8 +2363,9 @@ void ISel::visitCastInst(CastInst &CI) {
   emitCastOperation(BB, MI, Op, CI.getType(), DestReg);
 }
 
-/// emitCastOperation - Common code shared between visitCastInst and
-/// constant expression cast support.
+/// emitCastOperation - Common code shared between visitCastInst and constant
+/// expression cast support.
+///
 void ISel::emitCastOperation(MachineBasicBlock *BB,
                              MachineBasicBlock::iterator IP,
                              Value *Src, const Type *DestTy,
@@ -2371,7 +2707,8 @@ void ISel::visitVAArgInst(VAArgInst &I) {
   }
 }
 
-
+/// visitGetElementPtrInst - instruction-select GEP instructions
+///
 void ISel::visitGetElementPtrInst(GetElementPtrInst &I) {
   // If this GEP instruction will be folded into all of its users, we don't need
   // to explicitly calculate it!
@@ -2444,12 +2781,13 @@ void ISel::getGEPIndex(MachineBasicBlock *MBB, MachineBasicBlock::iterator IP,
       // idx is the index into the array.  Unlike with structure
       // indices, we may not know its actual value at code-generation
       // time.
-      assert(idx->getType() == Type::LongTy && "Bad GEP array index!");
 
       // If idx is a constant, fold it into the offset.
       unsigned TypeSize = TD.getTypeSize(SqTy->getElementType());
       if (ConstantSInt *CSI = dyn_cast<ConstantSInt>(idx)) {
         Disp += TypeSize*CSI->getValue();
+      } else if (ConstantUInt *CUI = dyn_cast<ConstantUInt>(idx)) {
+        Disp += TypeSize*CUI->getValue();
       } else {
         // If the index reg is already taken, we can't handle this index.
         if (IndexReg) return;
@@ -2573,12 +2911,7 @@ void ISel::emitGEPOperation(MachineBasicBlock *MBB,
       GEPOps.pop_back();        // Consume a GEP operand
       GEPTypes.pop_back();
 
-      // idx is the index into the array.  Unlike with structure
-      // indices, we may not know its actual value at code-generation
-      // time.
-      assert(idx->getType() == Type::LongTy && "Bad GEP array index!");
-
-      // Most GEP instructions use a [cast (int/uint) to LongTy] as their
+      // Many GEP instructions use a [cast (int/uint) to LongTy] as their
       // operand on X86.  Handle this case directly now...
       if (CastInst *CI = dyn_cast<CastInst>(idx))
         if (CI->getOperand(0)->getType() == Type::IntTy ||
@@ -2592,9 +2925,9 @@ void ISel::emitGEPOperation(MachineBasicBlock *MBB,
       unsigned elementSize = TD.getTypeSize(ElTy);
 
       // If idxReg is a constant, we don't need to perform the multiply!
-      if (ConstantSInt *CSI = dyn_cast<ConstantSInt>(idx)) {
+      if (ConstantInt *CSI = dyn_cast<ConstantInt>(idx)) {
         if (!CSI->isNullValue()) {
-          unsigned Offset = elementSize*CSI->getValue();
+          unsigned Offset = elementSize*CSI->getRawValue();
           unsigned Reg = makeAnotherReg(Type::UIntTy);
           BuildMI(*MBB, IP, X86::ADD32ri, 2, TargetReg)
                                 .addReg(Reg).addImm(Offset);