Newer
Older
//===-- InstSelectSimple.cpp - A simple instruction selector for x86 ------===//
//
// This file defines a simple peephole instruction selector for the x86 target
//
//===----------------------------------------------------------------------===//
#include "X86.h"
#include "llvm/Function.h"
#include "llvm/iTerminators.h"
#include "llvm/iOperators.h"
#include "llvm/iOther.h"
#include "llvm/iPHINode.h"
#include "llvm/Constants.h"
#include "llvm/Pass.h"
#include "llvm/CodeGen/MachineFunction.h"
#include "llvm/CodeGen/MachineInstrBuilder.h"
#include "llvm/CodeGen/MachineFrameInfo.h"
#include "llvm/CodeGen/MachineConstantPool.h"
#include "llvm/Target/TargetMachine.h"
#include "llvm/Target/MRegisterInfo.h"
#include <map>
/// BMI - A special BuildMI variant that takes an iterator to insert the
/// instruction at as well as a basic block.
/// this is the version for when you have a destination register in mind.
inline static MachineInstrBuilder BMI(MachineBasicBlock *MBB,
MachineBasicBlock::iterator &I,
MachineOpCode Opcode,
unsigned NumOperands,
unsigned DestReg) {
assert(I >= MBB->begin() && I <= MBB->end() && "Bad iterator!");
MachineInstr *MI = new MachineInstr(Opcode, NumOperands+1, true, true);
return MachineInstrBuilder(MI).addReg(DestReg, MOTy::Def);
}
/// BMI - A special BuildMI variant that takes an iterator to insert the
/// instruction at as well as a basic block.
MachineBasicBlock::iterator &I,
MachineOpCode Opcode,
unsigned NumOperands) {
assert(I > MBB->begin() && I <= MBB->end() && "Bad iterator!");
MachineInstr *MI = new MachineInstr(Opcode, NumOperands, true, true);
struct ISel : public FunctionPass, InstVisitor<ISel> {
TargetMachine &TM;
MachineFunction *F; // The function we are compiling into
MachineBasicBlock *BB; // The current MBB we are compiling
std::map<Value*, unsigned> RegMap; // Mapping between Val's and SSA Regs
// MBBMap - Mapping between LLVM BB -> Machine BB
std::map<const BasicBlock*, MachineBasicBlock*> MBBMap;
ISel(TargetMachine &tm) : TM(tm), F(0), BB(0) {}
/// runOnFunction - Top level implementation of instruction selection for
/// the entire function.
///
bool runOnFunction(Function &Fn) {
F = &MachineFunction::construct(&Fn, TM);
// Create all of the machine basic blocks for the function...
for (Function::iterator I = Fn.begin(), E = Fn.end(); I != E; ++I)
F->getBasicBlockList().push_back(MBBMap[I] = new MachineBasicBlock(I));
LoadArgumentsToVirtualRegs(Fn);
// Instruction select everything except PHI nodes
// Select the PHI nodes
SelectPHINodes();
return false; // We never modify the LLVM itself.
}
virtual const char *getPassName() const {
return "X86 Simple Instruction Selection";
}
/// visitBasicBlock - This method is called when we are visiting a new basic
/// block. This simply creates a new MachineBasicBlock to emit code into
/// and adds it to the current MachineFunction. Subsequent visit* for
/// instructions will be invoked for all instructions in the basic block.
///
void visitBasicBlock(BasicBlock &LLVM_BB) {
/// LoadArgumentsToVirtualRegs - Load all of the arguments to this function
/// from the stack into virtual registers.
///
void LoadArgumentsToVirtualRegs(Function &F);
/// SelectPHINodes - Insert machine code to generate phis. This is tricky
/// because we have to generate our sources into the source basic blocks,
/// not the current one.
///
void SelectPHINodes();
// Visitation methods for various instructions. These methods simply emit
// fixed X86 code for each instruction.
//
// Control flow operators
void visitBranchInst(BranchInst &BI);
struct ValueRecord {
unsigned Reg;
const Type *Ty;
ValueRecord(unsigned R, const Type *T) : Reg(R), Ty(T) {}
};
void doCall(const ValueRecord &Ret, MachineInstr *CallMI,
const std::vector<ValueRecord> &Args);
void visitCallInst(CallInst &I);
// Arithmetic operators
void visitSimpleBinary(BinaryOperator &B, unsigned OpcodeClass);
void visitAdd(BinaryOperator &B) { visitSimpleBinary(B, 0); }
void visitSub(BinaryOperator &B) { visitSimpleBinary(B, 1); }
Chris Lattner
committed
void doMultiply(MachineBasicBlock *MBB, MachineBasicBlock::iterator &MBBI,
unsigned DestReg, const Type *DestTy,
unsigned Op0Reg, unsigned Op1Reg);
void visitDiv(BinaryOperator &B) { visitDivRem(B); }
void visitRem(BinaryOperator &B) { visitDivRem(B); }
void visitDivRem(BinaryOperator &B);
void visitAnd(BinaryOperator &B) { visitSimpleBinary(B, 2); }
void visitOr (BinaryOperator &B) { visitSimpleBinary(B, 3); }
void visitXor(BinaryOperator &B) { visitSimpleBinary(B, 4); }
// Binary comparison operators
void visitSetCCInst(SetCondInst &I, unsigned OpNum);
void visitSetEQ(SetCondInst &I) { visitSetCCInst(I, 0); }
void visitSetNE(SetCondInst &I) { visitSetCCInst(I, 1); }
void visitSetLT(SetCondInst &I) { visitSetCCInst(I, 2); }
void visitSetGT(SetCondInst &I) { visitSetCCInst(I, 3); }
void visitSetLE(SetCondInst &I) { visitSetCCInst(I, 4); }
void visitSetGE(SetCondInst &I) { visitSetCCInst(I, 5); }
MachineInstr *doFPLoad(MachineBasicBlock *MBB,
MachineBasicBlock::iterator &MBBI,
const Type *Ty, unsigned DestReg);
void doFPStore(const Type *Ty, unsigned DestAddrReg, unsigned SrcReg);
void visitStoreInst(StoreInst &I);
void visitGetElementPtrInst(GetElementPtrInst &I);
void visitAllocaInst(AllocaInst &I);
void visitMallocInst(MallocInst &I);
void visitFreeInst(FreeInst &I);
void visitShiftInst(ShiftInst &I);
void visitPHINode(PHINode &I) {} // PHI nodes handled by second pass
void visitCastInst(CastInst &I);
void visitInstruction(Instruction &I) {
std::cerr << "Cannot instruction select: " << I;
abort();
}
///
void promote32(unsigned targetReg, const ValueRecord &VR);
/// EmitByteSwap - Byteswap SrcReg into DestReg.
///
void EmitByteSwap(unsigned DestReg, unsigned SrcReg, unsigned Class);
/// emitGEPOperation - Common code shared between visitGetElementPtrInst and
/// constant expression GEP support.
///
void emitGEPOperation(MachineBasicBlock *BB, MachineBasicBlock::iterator&IP,
User::op_iterator IdxEnd, unsigned TargetReg);
/// copyConstantToRegister - Output the instructions required to put the
/// specified constant into the specified register.
///
Chris Lattner
committed
void copyConstantToRegister(MachineBasicBlock *MBB,
MachineBasicBlock::iterator &MBBI,
Constant *C, unsigned Reg);
/// makeAnotherReg - This method returns the next register number we haven't
/// yet used.
///
/// Long values are handled somewhat specially. They are always allocated
/// as pairs of 32 bit integer values. The register number returned is the
/// lower 32 bits of the long value, and the regNum+1 is the upper 32 bits
/// of the long value.
///
unsigned makeAnotherReg(const Type *Ty) {
if (Ty == Type::LongTy || Ty == Type::ULongTy) {
const TargetRegisterClass *RC =
TM.getRegisterInfo()->getRegClassForType(Type::IntTy);
// Create the lower part
F->getSSARegMap()->createVirtualRegister(RC);
// Create the upper part.
return F->getSSARegMap()->createVirtualRegister(RC)-1;
}
// Add the mapping of regnumber => reg class to MachineFunction
const TargetRegisterClass *RC =
TM.getRegisterInfo()->getRegClassForType(Ty);
return F->getSSARegMap()->createVirtualRegister(RC);
/// getReg - This method turns an LLVM value into a register number. This
/// is guaranteed to produce the same register number for a particular value
/// every time it is queried.
///
unsigned getReg(Value &V) { return getReg(&V); } // Allow references
unsigned getReg(Value *V) {
// Just append to the end of the current bb.
MachineBasicBlock::iterator It = BB->end();
return getReg(V, BB, It);
}
if (Reg == 0) {
Reg = makeAnotherReg(V->getType());
RegMap[V] = Reg;
}
// If this operand is a constant, emit the code to copy the constant into
// the register here...
//
if (Constant *C = dyn_cast<Constant>(V)) {
Chris Lattner
committed
copyConstantToRegister(MBB, IPt, C, Reg);
RegMap.erase(V); // Assign a new name to this constant if ref'd again
} else if (GlobalValue *GV = dyn_cast<GlobalValue>(V)) {
// Move the address of the global into the register
BMI(MBB, IPt, X86::MOVir32, 1, Reg).addGlobalAddress(GV);
RegMap.erase(V); // Assign a new name to this address if ref'd again
/// TypeClass - Used by the X86 backend to group LLVM types by their basic X86
/// Representation.
///
enum TypeClass {
/// getClass - Turn a primitive type into a "class" number which is based on the
/// size of the type, and whether or not it is floating point.
///
static inline TypeClass getClass(const Type *Ty) {
switch (Ty->getPrimitiveID()) {
case Type::SByteTyID:
case Type::UByteTyID: return cByte; // Byte operands are class #0
case Type::ShortTyID:
case Type::UShortTyID: return cShort; // Short operands are class #1
case Type::IntTyID:
case Type::UIntTyID:
case Type::PointerTyID: return cInt; // Int's and pointers are class #2
case Type::FloatTyID:
case Type::DoubleTyID: return cFP; // Floating Point is #3
case Type::LongTyID:
case Type::ULongTyID: return cLong; // Longs are class #4
default:
assert(0 && "Invalid type to getClass!");
}
}
// getClassB - Just like getClass, but treat boolean values as bytes.
static inline TypeClass getClassB(const Type *Ty) {
if (Ty == Type::BoolTy) return cByte;
return getClass(Ty);
}
/// copyConstantToRegister - Output the instructions required to put the
/// specified constant into the specified register.
///
Chris Lattner
committed
void ISel::copyConstantToRegister(MachineBasicBlock *MBB,
MachineBasicBlock::iterator &IP,
Constant *C, unsigned R) {
if (ConstantExpr *CE = dyn_cast<ConstantExpr>(C)) {
if (CE->getOpcode() == Instruction::GetElementPtr) {
assert(0 && "Constant expressions not yet handled!\n");
if (C->getType()->isIntegral()) {
unsigned Class = getClassB(C->getType());
if (Class == cLong) {
// Copy the value into the register pair.
uint64_t Val;
if (C->getType()->isSigned())
Val = cast<ConstantSInt>(C)->getValue();
else
Val = cast<ConstantUInt>(C)->getValue();
BMI(MBB, IP, X86::MOVir32, 1, R).addZImm(Val & 0xFFFFFFFF);
BMI(MBB, IP, X86::MOVir32, 1, R+1).addZImm(Val >> 32);
return;
}
assert(Class <= cInt && "Type not handled yet!");
static const unsigned IntegralOpcodeTab[] = {
X86::MOVir8, X86::MOVir16, X86::MOVir32
};
if (C->getType() == Type::BoolTy) {
BMI(MBB, IP, X86::MOVir8, 1, R).addZImm(C == ConstantBool::True);
} else if (C->getType()->isSigned()) {
ConstantSInt *CSI = cast<ConstantSInt>(C);
BMI(MBB, IP, IntegralOpcodeTab[Class], 1, R).addZImm(CSI->getValue());
} else {
ConstantUInt *CUI = cast<ConstantUInt>(C);
}
} else if (ConstantFP *CFP = dyn_cast<ConstantFP>(C)) {
double Value = CFP->getValue();
if (Value == +0.0)
BMI(MBB, IP, X86::FLD0, 0, R);
else if (Value == +1.0)
BMI(MBB, IP, X86::FLD1, 0, R);
else {
// Otherwise we need to spill the constant to memory...
MachineConstantPool *CP = F->getConstantPool();
unsigned CPI = CP->getConstantPoolIndex(CFP);
addConstantPoolReference(doFPLoad(MBB, IP, CFP->getType(), R), CPI);
} else if (ConstantPointerRef *CPR = dyn_cast<ConstantPointerRef>(C)) {
} else {
assert(0 && "Type not handled yet!");
/// LoadArgumentsToVirtualRegs - Load all of the arguments to this function from
/// the stack into virtual registers.
///
void ISel::LoadArgumentsToVirtualRegs(Function &Fn) {
// Emit instructions to load the arguments... On entry to a function on the
// X86, the stack frame looks like this:
//
// [ESP] -- return address
// [ESP + 4] -- first argument (leftmost lexically)
// [ESP + 8] -- second argument, if first argument is four bytes in size
// ...
//
unsigned ArgOffset = 0; // Frame mechanisms handle retaddr slot
MachineFrameInfo *MFI = F->getFrameInfo();
for (Function::aiterator I = Fn.abegin(), E = Fn.aend(); I != E; ++I) {
unsigned Reg = getReg(*I);
int FI; // Frame object index
switch (getClassB(I->getType())) {
case cByte:
FI = MFI->CreateFixedObject(1, ArgOffset);
addFrameReference(BuildMI(BB, X86::MOVmr8, 4, Reg), FI);
break;
case cShort:
FI = MFI->CreateFixedObject(2, ArgOffset);
addFrameReference(BuildMI(BB, X86::MOVmr16, 4, Reg), FI);
break;
case cInt:
FI = MFI->CreateFixedObject(4, ArgOffset);
addFrameReference(BuildMI(BB, X86::MOVmr32, 4, Reg), FI);
break;
case cLong:
FI = MFI->CreateFixedObject(8, ArgOffset);
addFrameReference(BuildMI(BB, X86::MOVmr32, 4, Reg), FI);
addFrameReference(BuildMI(BB, X86::MOVmr32, 4, Reg+1), FI, 4);
ArgOffset += 4; // longs require 4 additional bytes
break;
case cFP:
unsigned Opcode;
if (I->getType() == Type::FloatTy) {
Opcode = X86::FLDr32;
FI = MFI->CreateFixedObject(4, ArgOffset);
} else {
Opcode = X86::FLDr64;
FI = MFI->CreateFixedObject(8, ArgOffset);
ArgOffset += 4; // doubles require 4 additional bytes
}
addFrameReference(BuildMI(BB, Opcode, 4, Reg), FI);
break;
default:
assert(0 && "Unhandled argument type!");
}
ArgOffset += 4; // Each argument takes at least 4 bytes on the stack...
}
}
/// SelectPHINodes - Insert machine code to generate phis. This is tricky
/// because we have to generate our sources into the source basic blocks, not
/// the current one.
///
void ISel::SelectPHINodes() {
const TargetInstrInfo &TII = TM.getInstrInfo();
const Function &LF = *F->getFunction(); // The LLVM function...
for (Function::const_iterator I = LF.begin(), E = LF.end(); I != E; ++I) {
const BasicBlock *BB = I;
MachineBasicBlock *MBB = MBBMap[I];
// Loop over all of the PHI nodes in the LLVM basic block...
unsigned NumPHIs = 0;
for (BasicBlock::const_iterator I = BB->begin();
PHINode *PN = (PHINode*)dyn_cast<PHINode>(&*I); ++I) {
// Create a new machine instr PHI node, and insert it.
unsigned PHIReg = getReg(*PN);
MachineInstr *PhiMI = BuildMI(X86::PHI, PN->getNumOperands(), PHIReg);
MBB->insert(MBB->begin()+NumPHIs++, PhiMI);
MachineInstr *LongPhiMI = 0;
if (PN->getType() == Type::LongTy || PN->getType() == Type::ULongTy) {
LongPhiMI = BuildMI(X86::PHI, PN->getNumOperands(), PHIReg+1);
MBB->insert(MBB->begin()+NumPHIs++, LongPhiMI);
}
for (unsigned i = 0, e = PN->getNumIncomingValues(); i != e; ++i) {
MachineBasicBlock *PredMBB = MBBMap[PN->getIncomingBlock(i)];
// Get the incoming value into a virtual register. If it is not already
// available in a virtual register, insert the computation code into
// PredMBB
MachineBasicBlock::iterator PI = PredMBB->end();
while (PI != PredMBB->begin() &&
TII.isTerminatorInstr((*(PI-1))->getOpcode()))
--PI;
unsigned ValReg = getReg(PN->getIncomingValue(i), PredMBB, PI);
PhiMI->addRegOperand(ValReg);
PhiMI->addMachineBasicBlockOperand(PredMBB);
if (LongPhiMI) {
LongPhiMI->addRegOperand(ValReg+1);
LongPhiMI->addMachineBasicBlockOperand(PredMBB);
}
/// 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::visitSetCCInst(SetCondInst &I, unsigned OpNum) {
// The arguments are already supposed to be of the same type.
const Type *CompTy = I.getOperand(0)->getType();
bool isSigned = CompTy->isSigned();
unsigned reg1 = getReg(I.getOperand(0));
unsigned reg2 = getReg(I.getOperand(1));
unsigned DestReg = getReg(I);
// LLVM -> X86 signed X86 unsigned
// ----- ---------- ------------
// seteq -> sete sete
// setne -> setne setne
// setlt -> setl setb
// setgt -> setg seta
// setle -> setle setbe
// setge -> setge setae
static const unsigned OpcodeTab[2][6] = {
{X86::SETEr, X86::SETNEr, X86::SETBr, X86::SETAr, X86::SETBEr, X86::SETAEr},
{X86::SETEr, X86::SETNEr, X86::SETLr, X86::SETGr, X86::SETLEr, X86::SETGEr},
};
unsigned Class = getClassB(CompTy);
default: assert(0 && "Unknown type class!");
// Emit: cmp <var1>, <var2> (do the comparison). We can
// compare 8-bit with 8-bit, 16-bit with 16-bit, 32-bit with
// 32-bit.
case cByte:
BuildMI(BB, X86::CMPrr8, 2).addReg(reg1).addReg(reg2);
BuildMI(BB, X86::CMPrr16, 2).addReg(reg1).addReg(reg2);
BuildMI(BB, X86::CMPrr32, 2).addReg(reg1).addReg(reg2);
case cFP:
BuildMI(BB, X86::FpUCOM, 2).addReg(reg1).addReg(reg2);
BuildMI(BB, X86::FNSTSWr8, 0);
BuildMI(BB, X86::SAHF, 1);
isSigned = false; // Compare with unsigned operators
if (OpNum < 2) { // seteq, setne
unsigned LoTmp = makeAnotherReg(Type::IntTy);
unsigned HiTmp = makeAnotherReg(Type::IntTy);
unsigned FinalTmp = makeAnotherReg(Type::IntTy);
BuildMI(BB, X86::XORrr32, 2, LoTmp).addReg(reg1).addReg(reg2);
BuildMI(BB, X86::XORrr32, 2, HiTmp).addReg(reg1+1).addReg(reg2+1);
BuildMI(BB, X86::ORrr32, 2, FinalTmp).addReg(LoTmp).addReg(HiTmp);
break; // Allow the sete or setne to be generated from flags set by OR
} else {
// Emit a sequence of code which compares the high and low parts once
// each, then uses a conditional move to handle the overflow case. For
// example, a setlt for long would generate code like this:
//
// AL = lo(op1) < lo(op2) // Signedness depends on operands
// BL = hi(op1) < hi(op2) // Always unsigned comparison
// dest = hi(op1) == hi(op2) ? AL : BL;
//
// FIXME: This would be much better if we had heirarchical register
// classes! Until then, hardcode registers so that we can deal with their
// aliases (because we don't have conditional byte moves).
//
BuildMI(BB, X86::CMPrr32, 2).addReg(reg1).addReg(reg2);
BuildMI(BB, OpcodeTab[0][OpNum], 0, X86::AL);
BuildMI(BB, X86::CMPrr32, 2).addReg(reg1+1).addReg(reg2+1);
BuildMI(BB, OpcodeTab[isSigned][OpNum], 0, X86::BL);
BuildMI(BB, X86::CMOVErr16, 2, X86::BX).addReg(X86::BX).addReg(X86::AX);
BuildMI(BB, X86::MOVrr8, 1, DestReg).addReg(X86::BL);
return;
}
BuildMI(BB, OpcodeTab[isSigned][OpNum], 0, DestReg);
/// 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();
switch (getClassB(VR.Ty)) {
case cByte:
// Extend value into target register (8->32)
if (isUnsigned)
BuildMI(BB, X86::MOVZXr32r8, 1, targetReg).addReg(VR.Reg);
BuildMI(BB, X86::MOVSXr32r8, 1, targetReg).addReg(VR.Reg);
break;
case cShort:
// Extend value into target register (16->32)
if (isUnsigned)
BuildMI(BB, X86::MOVZXr32r16, 1, targetReg).addReg(VR.Reg);
BuildMI(BB, X86::MOVSXr32r16, 1, targetReg).addReg(VR.Reg);
break;
case cInt:
// Move value into target register (32->32)
BuildMI(BB, X86::MOVrr32, 1, targetReg).addReg(VR.Reg);
break;
default:
assert(0 && "Unpromotable operand class in promote32");
}
/// 'ret' instruction - Here we are interested in meeting the x86 ABI. As such,
/// we have the following possibilities:
///
/// ret void: No return value, simply emit a 'ret' instruction
/// ret sbyte, ubyte : Extend value into EAX and return
/// ret short, ushort: Extend value into EAX and return
/// ret int, uint : Move value into EAX and return
/// ret pointer : Move value into EAX and return
/// ret long, ulong : Move value into EAX/EDX and return
/// ret float/double : Top of FP stack
void ISel::visitReturnInst(ReturnInst &I) {
if (I.getNumOperands() == 0) {
BuildMI(BB, X86::RET, 0); // Just emit a 'ret' instruction
return;
}
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()));
break;
case cFP: // Floats & Doubles: Return in ST(0)
BuildMI(BB, X86::FpSETRESULT, 1).addReg(RetReg);
BuildMI(BB, X86::MOVrr32, 1, X86::EAX).addReg(RetReg);
BuildMI(BB, X86::MOVrr32, 1, X86::EDX).addReg(RetReg+1);
break;
visitInstruction(I);
/// visitBranchInst - Handle conditional and unconditional branches here. Note
/// that since code layout is frozen at this point, that if we are trying to
/// jump to a block that is the immediate successor of the current block, we can
/// just make a fall-through. (but we don't currently).
///
void ISel::visitBranchInst(BranchInst &BI) {
if (BI.isConditional()) {
unsigned condReg = getReg(BI.getCondition());
BuildMI(BB, X86::CMPri8, 2).addReg(condReg).addZImm(0);
BuildMI(BB, X86::JE, 1).addPCDisp(BI.getSuccessor(1));
}
BuildMI(BB, X86::JMP, 1).addPCDisp(BI.getSuccessor(0));
/// doCall - This emits an abstract call instruction, setting up the arguments
/// and the return value as appropriate. For the actual function call itself,
/// it inserts the specified CallMI instruction into the stream.
///
void ISel::doCall(const ValueRecord &Ret, MachineInstr *CallMI,
const std::vector<ValueRecord> &Args) {
// Count how many bytes are to be pushed on the stack...
unsigned NumBytes = 0;
if (!Args.empty()) {
for (unsigned i = 0, e = Args.size(); i != e; ++i)
switch (getClassB(Args[i].Ty)) {
case cByte: case cShort: case cInt:
NumBytes += 4; break;
case cLong:
NumBytes += 8; break;
case cFP:
NumBytes += Args[i].Ty == Type::FloatTy ? 4 : 8;
break;
default: assert(0 && "Unknown class!");
}
// Adjust the stack pointer for the new arguments...
BuildMI(BB, X86::ADJCALLSTACKDOWN, 1).addZImm(NumBytes);
// Arguments go on the stack in reverse order, as specified by the ABI.
unsigned ArgOffset = 0;
for (unsigned i = 0, e = Args.size(); i != e; ++i) {
unsigned ArgReg = Args[i].Reg;
switch (getClassB(Args[i].Ty)) {
case cByte:
case cShort: {
// Promote arg to 32 bits wide into a temporary register...
unsigned R = makeAnotherReg(Type::UIntTy);
promote32(R, Args[i]);
addRegOffset(BuildMI(BB, X86::MOVrm32, 5),
X86::ESP, ArgOffset).addReg(R);
break;
}
case cInt:
addRegOffset(BuildMI(BB, X86::MOVrm32, 5),
X86::ESP, ArgOffset).addReg(ArgReg);
break;
case cLong:
addRegOffset(BuildMI(BB, X86::MOVrm32, 5),
X86::ESP, ArgOffset).addReg(ArgReg);
addRegOffset(BuildMI(BB, X86::MOVrm32, 5),
X86::ESP, ArgOffset+4).addReg(ArgReg+1);
ArgOffset += 4; // 8 byte entry, not 4.
break;
case cFP:
if (Args[i].Ty == Type::FloatTy) {
addRegOffset(BuildMI(BB, X86::FSTr32, 5),
X86::ESP, ArgOffset).addReg(ArgReg);
} else {
assert(Args[i].Ty == Type::DoubleTy && "Unknown FP type!");
addRegOffset(BuildMI(BB, X86::FSTr64, 5),
X86::ESP, ArgOffset).addReg(ArgReg);
ArgOffset += 4; // 8 byte entry, not 4.
}
break;
default: assert(0 && "Unknown class!");
}
ArgOffset += 4;
BuildMI(BB, X86::ADJCALLSTACKDOWN, 1).addZImm(0);
Misha Brukman
committed
BB->push_back(CallMI);
BuildMI(BB, X86::ADJCALLSTACKUP, 1).addZImm(NumBytes);
// If there is a return value, scavenge the result from the location the call
// leaves it in...
//
if (Ret.Ty != Type::VoidTy) {
unsigned DestClass = getClassB(Ret.Ty);
switch (DestClass) {
case cByte:
case cShort:
case cInt: {
// Integral results are in %eax, or the appropriate portion
// thereof.
static const unsigned regRegMove[] = {
X86::MOVrr8, X86::MOVrr16, X86::MOVrr32
};
static const unsigned AReg[] = { X86::AL, X86::AX, X86::EAX };
BuildMI(BB, regRegMove[DestClass], 1, Ret.Reg).addReg(AReg[DestClass]);
case cFP: // Floating-point return values live in %ST(0)
BuildMI(BB, X86::FpGETRESULT, 1, Ret.Reg);
case cLong: // Long values are left in EDX:EAX
BuildMI(BB, X86::MOVrr32, 1, Ret.Reg).addReg(X86::EAX);
BuildMI(BB, X86::MOVrr32, 1, Ret.Reg+1).addReg(X86::EDX);
break;
default: assert(0 && "Unknown class!");
/// visitCallInst - Push args on stack and do a procedure call instruction.
void ISel::visitCallInst(CallInst &CI) {
MachineInstr *TheCall;
if (Function *F = CI.getCalledFunction()) {
// Emit a CALL instruction with PC-relative displacement.
TheCall = BuildMI(X86::CALLpcrel32, 1).addGlobalAddress(F, true);
} else { // Emit an indirect call...
unsigned Reg = getReg(CI.getCalledValue());
TheCall = BuildMI(X86::CALLr32, 1).addReg(Reg);
}
std::vector<ValueRecord> Args;
for (unsigned i = 1, e = CI.getNumOperands(); i != e; ++i)
Args.push_back(ValueRecord(getReg(CI.getOperand(i)),
CI.getOperand(i)->getType()));
unsigned DestReg = CI.getType() != Type::VoidTy ? getReg(CI) : 0;
doCall(ValueRecord(DestReg, CI.getType()), TheCall, Args);
}
/// 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 Class = getClassB(B.getType());
static const unsigned OpcodeTab[][4] = {
{ X86::ADDrr8, X86::ADDrr16, X86::ADDrr32, X86::FpADD }, // ADD
{ X86::SUBrr8, X86::SUBrr16, X86::SUBrr32, X86::FpSUB }, // SUB
{ X86::ANDrr8, X86::ANDrr16, X86::ANDrr32, 0 }, // AND
{ X86:: ORrr8, X86:: ORrr16, X86:: ORrr32, 0 }, // OR
{ X86::XORrr8, X86::XORrr16, X86::XORrr32, 0 }, // 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(B.getOperand(0));
unsigned Op1r = getReg(B.getOperand(1));
unsigned DestReg = getReg(B);
BuildMI(BB, Opcode, 2, DestReg).addReg(Op0r).addReg(Op1r);
if (isLong) { // Handle the upper 32 bits of long values...
static const unsigned TopTab[] = {
X86::ADCrr32, X86::SBBrr32, X86::ANDrr32, X86::ORrr32, X86::XORrr32
};
BuildMI(BB, TopTab[OperatorClass], 2,
DestReg+1).addReg(Op0r+1).addReg(Op1r+1);
}
/// doMultiply - Emit appropriate instructions to multiply together the
/// registers op0Reg and op1Reg, and put the result in DestReg. The type of the
/// result should be given as DestTy.
///
/// FIXME: doMultiply should use one of the two address IMUL instructions!
///
Chris Lattner
committed
void ISel::doMultiply(MachineBasicBlock *MBB, MachineBasicBlock::iterator &MBBI,
unsigned DestReg, const Type *DestTy,
Chris Lattner
committed
unsigned op0Reg, unsigned op1Reg) {
unsigned Class = getClass(DestTy);
switch (Class) {
case cFP: // Floating point multiply
BMI(BB, MBBI, X86::FpMUL, 2, DestReg).addReg(op0Reg).addReg(op1Reg);
case cLong: assert(0 && "doMultiply cannot operate on LONG values!");
case cByte:
case cShort:
case cInt: // Small integerals, handled below...
break;
}
static const unsigned Regs[] ={ X86::AL , X86::AX , X86::EAX };
static const unsigned MulOpcode[]={ X86::MULr8 , X86::MULr16 , X86::MULr32 };
static const unsigned MovOpcode[]={ X86::MOVrr8, X86::MOVrr16, X86::MOVrr32 };
// Emit a MOV to put the first operand into the appropriately-sized
// subreg of EAX.
BMI(MBB, MBBI, MovOpcode[Class], 1, Reg).addReg(op0Reg);
BMI(MBB, MBBI, MulOpcode[Class], 1).addReg(op1Reg);
BMI(MBB, MBBI, MovOpcode[Class], 1, DestReg).addReg(Reg);
}
/// visitMul - Multiplies are not simple binary operators because they must deal
/// with the EAX register explicitly.
///
void ISel::visitMul(BinaryOperator &I) {
unsigned Op0Reg = getReg(I.getOperand(0));
unsigned Op1Reg = getReg(I.getOperand(1));
863
864
865
866
867
868
869
870
871
872
873
874
875
876
877
878
879
880
881
882
883
884
885
886
887
888
889
890
891
892
893
unsigned DestReg = getReg(I);
// Simple scalar multiply?
if (I.getType() != Type::LongTy && I.getType() != Type::ULongTy) {
MachineBasicBlock::iterator MBBI = BB->end();
doMultiply(BB, MBBI, DestReg, I.getType(), Op0Reg, Op1Reg);
} else {
// Long value. We have to do things the hard way...
// Multiply the two low parts... capturing carry into EDX
BuildMI(BB, X86::MOVrr32, 1, X86::EAX).addReg(Op0Reg);
BuildMI(BB, X86::MULr32, 1).addReg(Op1Reg); // AL*BL
unsigned OverflowReg = makeAnotherReg(Type::UIntTy);
BuildMI(BB, X86::MOVrr32, 1, DestReg).addReg(X86::EAX); // AL*BL
BuildMI(BB, X86::MOVrr32, 1, OverflowReg).addReg(X86::EDX); // AL*BL >> 32
MachineBasicBlock::iterator MBBI = BB->end();
unsigned AHBLReg = makeAnotherReg(Type::UIntTy);
doMultiply(BB, MBBI, AHBLReg, Type::UIntTy, Op0Reg+1, Op1Reg); // AH*BL
unsigned AHBLplusOverflowReg = makeAnotherReg(Type::UIntTy);
BuildMI(BB, X86::ADDrr32, 2, // AH*BL+(AL*BL >> 32)
AHBLplusOverflowReg).addReg(AHBLReg).addReg(OverflowReg);
MBBI = BB->end();
unsigned ALBHReg = makeAnotherReg(Type::UIntTy);
doMultiply(BB, MBBI, ALBHReg, Type::UIntTy, Op0Reg, Op1Reg+1); // AL*BH
BuildMI(BB, X86::ADDrr32, 2, // AL*BH + AH*BL + (AL*BL >> 32)
DestReg+1).addReg(AHBLplusOverflowReg).addReg(ALBHReg);
}
/// visitDivRem - Handle division and remainder instructions... these
/// instruction both require the same instructions to be generated, they just
/// select the result from a different register. Note that both of these
/// instructions work differently for signed and unsigned operands.
///
void ISel::visitDivRem(BinaryOperator &I) {
unsigned Class = getClass(I.getType());
unsigned Op0Reg = getReg(I.getOperand(0));
unsigned Op1Reg = getReg(I.getOperand(1));
unsigned ResultReg = getReg(I);
switch (Class) {
case cFP: // Floating point divide
if (I.getOpcode() == Instruction::Div)
BuildMI(BB, X86::FpDIV, 2, ResultReg).addReg(Op0Reg).addReg(Op1Reg);
else { // Floating point remainder...
MachineInstr *TheCall =
BuildMI(X86::CALLpcrel32, 1).addExternalSymbol("fmod", true);
std::vector<ValueRecord> Args;
Args.push_back(ValueRecord(Op0Reg, Type::DoubleTy));
Args.push_back(ValueRecord(Op1Reg, Type::DoubleTy));
doCall(ValueRecord(ResultReg, Type::DoubleTy), TheCall, Args);
}
return;
case cLong: {
static const char *FnName[] =
{ "__moddi3", "__divdi3", "__umoddi3", "__udivdi3" };
unsigned NameIdx = I.getType()->isUnsigned()*2;
NameIdx += I.getOpcode() == Instruction::Div;
MachineInstr *TheCall =
BuildMI(X86::CALLpcrel32, 1).addExternalSymbol(FnName[NameIdx], true);
std::vector<ValueRecord> Args;
Args.push_back(ValueRecord(Op0Reg, Type::LongTy));
Args.push_back(ValueRecord(Op1Reg, Type::LongTy));
doCall(ValueRecord(ResultReg, Type::LongTy), TheCall, Args);
}
case cByte: case cShort: case cInt:
break; // Small integerals, handled below...
default: assert(0 && "Unknown class!");
static const unsigned Regs[] ={ X86::AL , X86::AX , X86::EAX };
static const unsigned MovOpcode[]={ X86::MOVrr8, X86::MOVrr16, X86::MOVrr32 };
static const unsigned ExtOpcode[]={ X86::CBW , X86::CWD , X86::CDQ };
static const unsigned ClrOpcode[]={ X86::XORrr8, X86::XORrr16, X86::XORrr32 };
static const unsigned ExtRegs[] ={ X86::AH , X86::DX , X86::EDX };
static const unsigned DivOpcode[][4] = {
{ X86::DIVr8 , X86::DIVr16 , X86::DIVr32 , 0 }, // Unsigned division
{ X86::IDIVr8, X86::IDIVr16, X86::IDIVr32, 0 }, // Signed division
bool isSigned = I.getType()->isSigned();
unsigned Reg = Regs[Class];
unsigned ExtReg = ExtRegs[Class];
// Put the first operand into one of the A registers...
BuildMI(BB, MovOpcode[Class], 1, Reg).addReg(Op0Reg);
if (isSigned) {
// Emit a sign extension instruction...
} else {
// If unsigned, emit a zeroing instruction... (reg = xor reg, reg)
BuildMI(BB, ClrOpcode[Class], 2, ExtReg).addReg(ExtReg).addReg(ExtReg);
}
// Emit the appropriate divide or remainder instruction...
BuildMI(BB, DivOpcode[isSigned][Class], 1).addReg(Op1Reg);
// Figure out which register we want to pick the result out of...
unsigned DestReg = (I.getOpcode() == Instruction::Div) ? Reg : ExtReg;
// Put the result into the destination register...
BuildMI(BB, MovOpcode[Class], 1, ResultReg).addReg(DestReg);
/// Shift instructions: 'shl', 'sar', 'shr' - Some special cases here
/// for constant immediate shift values, and for constant immediate
/// shift values equal to 1. Even the general case is sort of special,
/// because the shift amount has to be in CL, not just any old register.
///
void ISel::visitShiftInst(ShiftInst &I) {
unsigned SrcReg = getReg(I.getOperand(0));
unsigned DestReg = getReg(I);
bool isLeftShift = I.getOpcode() == Instruction::Shl;
bool isSigned = I.getType()->isSigned();
unsigned Class = getClass(I.getType());
static const unsigned ConstantOperand[][4] = {
{ X86::SHRir8, X86::SHRir16, X86::SHRir32, X86::SHRDir32 }, // SHR
{ X86::SARir8, X86::SARir16, X86::SARir32, X86::SHRDir32 }, // SAR
{ X86::SHLir8, X86::SHLir16, X86::SHLir32, X86::SHLDir32 }, // SHL
{ X86::SHLir8, X86::SHLir16, X86::SHLir32, X86::SHLDir32 }, // SAL = SHL
};
static const unsigned NonConstantOperand[][4] = {
{ X86::SHRrr8, X86::SHRrr16, X86::SHRrr32 }, // SHR
{ X86::SARrr8, X86::SARrr16, X86::SARrr32 }, // SAR
{ X86::SHLrr8, X86::SHLrr16, X86::SHLrr32 }, // SHL