Be a bit more efficient when processing the active and inactive
[oota-llvm.git] / lib / Target / PowerPC / PPC64ISelSimple.cpp
1 //===-- PPC64ISelSimple.cpp - A simple instruction selector for PowerPC ---===//
2 // 
3 //                     The LLVM Compiler Infrastructure
4 //
5 // This file was developed by the LLVM research group and is distributed under
6 // the University of Illinois Open Source License. See LICENSE.TXT for details.
7 // 
8 //===----------------------------------------------------------------------===//
9
10 #define DEBUG_TYPE "isel"
11 #include "PowerPC.h"
12 #include "PowerPCInstrBuilder.h"
13 #include "PowerPCInstrInfo.h"
14 #include "PPC64TargetMachine.h"
15 #include "llvm/Constants.h"
16 #include "llvm/DerivedTypes.h"
17 #include "llvm/Function.h"
18 #include "llvm/Instructions.h"
19 #include "llvm/Pass.h"
20 #include "llvm/CodeGen/IntrinsicLowering.h"
21 #include "llvm/CodeGen/MachineConstantPool.h"
22 #include "llvm/CodeGen/MachineFrameInfo.h"
23 #include "llvm/CodeGen/MachineFunction.h"
24 #include "llvm/CodeGen/SSARegMap.h"
25 #include "llvm/Target/MRegisterInfo.h"
26 #include "llvm/Target/TargetMachine.h"
27 #include "llvm/Support/GetElementPtrTypeIterator.h"
28 #include "llvm/Support/InstVisitor.h"
29 #include "Support/Debug.h"
30 #include "Support/Statistic.h"
31 #include <vector>
32 using namespace llvm;
33
34 namespace {
35   Statistic<> GEPFolds("ppc64-codegen", "Number of GEPs folded");
36
37   /// TypeClass - Used by the PowerPC backend to group LLVM types by their basic
38   /// PPC Representation.
39   ///
40   enum TypeClass {
41     cByte, cShort, cInt, cFP32, cFP64, cLong
42   };
43 }
44
45 /// getClass - Turn a primitive type into a "class" number which is based on the
46 /// size of the type, and whether or not it is floating point.
47 ///
48 static inline TypeClass getClass(const Type *Ty) {
49   switch (Ty->getTypeID()) {
50   case Type::SByteTyID:
51   case Type::UByteTyID:   return cByte;      // Byte operands are class #0
52   case Type::ShortTyID:
53   case Type::UShortTyID:  return cShort;     // Short operands are class #1
54   case Type::IntTyID:
55   case Type::UIntTyID:    return cInt;       // Ints are class #2
56
57   case Type::FloatTyID:   return cFP32;      // Single float is #3
58   case Type::DoubleTyID:  return cFP64;      // Double Point is #4
59
60   case Type::PointerTyID:
61   case Type::LongTyID:
62   case Type::ULongTyID:   return cLong;      // Longs and pointers are class #5
63   default:
64     assert(0 && "Invalid type to getClass!");
65     return cByte;  // not reached
66   }
67 }
68
69 // getClassB - Just like getClass, but treat boolean values as ints.
70 static inline TypeClass getClassB(const Type *Ty) {
71   if (Ty == Type::BoolTy) return cInt;
72   return getClass(Ty);
73 }
74
75 namespace {
76   struct ISel : public FunctionPass, InstVisitor<ISel> {
77     PPC64TargetMachine &TM;
78     MachineFunction *F;                 // The function we are compiling into
79     MachineBasicBlock *BB;              // The current MBB we are compiling
80     int VarArgsFrameIndex;              // FrameIndex for start of varargs area
81     
82     std::map<Value*, unsigned> RegMap;  // Mapping between Values and SSA Regs
83
84     // External functions used in the Module
85     Function *fmodfFn, *fmodFn, *__cmpdi2Fn, *__moddi3Fn, *__divdi3Fn, 
86       *__umoddi3Fn,  *__udivdi3Fn, *__fixsfdiFn, *__fixdfdiFn, *__fixunssfdiFn,
87       *__fixunsdfdiFn, *__floatdisfFn, *__floatdidfFn, *mallocFn, *freeFn;
88
89     // MBBMap - Mapping between LLVM BB -> Machine BB
90     std::map<const BasicBlock*, MachineBasicBlock*> MBBMap;
91
92     // AllocaMap - Mapping from fixed sized alloca instructions to the
93     // FrameIndex for the alloca.
94     std::map<AllocaInst*, unsigned> AllocaMap;
95
96     // Target configuration data
97     const unsigned ParameterSaveAreaOffset, MaxArgumentStackSpace;
98
99     ISel(TargetMachine &tm) : TM(reinterpret_cast<PPC64TargetMachine&>(tm)), 
100       F(0), BB(0), ParameterSaveAreaOffset(24), MaxArgumentStackSpace(32) {}
101
102     bool doInitialization(Module &M) {
103       // Add external functions that we may call
104       Type *i = Type::IntTy;
105       Type *d = Type::DoubleTy;
106       Type *f = Type::FloatTy;
107       Type *l = Type::LongTy;
108       Type *ul = Type::ULongTy;
109       Type *voidPtr = PointerType::get(Type::SByteTy);
110       // float fmodf(float, float);
111       fmodfFn = M.getOrInsertFunction("fmodf", f, f, f, 0);
112       // double fmod(double, double);
113       fmodFn = M.getOrInsertFunction("fmod", d, d, d, 0);
114       // int __cmpdi2(long, long);
115       __cmpdi2Fn = M.getOrInsertFunction("__cmpdi2", i, l, l, 0);
116       // long __moddi3(long, long);
117       __moddi3Fn = M.getOrInsertFunction("__moddi3", l, l, l, 0);
118       // long __divdi3(long, long);
119       __divdi3Fn = M.getOrInsertFunction("__divdi3", l, l, l, 0);
120       // unsigned long __umoddi3(unsigned long, unsigned long);
121       __umoddi3Fn = M.getOrInsertFunction("__umoddi3", ul, ul, ul, 0);
122       // unsigned long __udivdi3(unsigned long, unsigned long);
123       __udivdi3Fn = M.getOrInsertFunction("__udivdi3", ul, ul, ul, 0);
124       // long __fixsfdi(float)
125       __fixsfdiFn = M.getOrInsertFunction("__fixsfdi", l, f, 0);
126       // long __fixdfdi(double)
127       __fixdfdiFn = M.getOrInsertFunction("__fixdfdi", l, d, 0);
128       // unsigned long __fixunssfdi(float)
129       __fixunssfdiFn = M.getOrInsertFunction("__fixunssfdi", ul, f, 0);
130       // unsigned long __fixunsdfdi(double)
131       __fixunsdfdiFn = M.getOrInsertFunction("__fixunsdfdi", ul, d, 0);
132       // float __floatdisf(long)
133       __floatdisfFn = M.getOrInsertFunction("__floatdisf", f, l, 0);
134       // double __floatdidf(long)
135       __floatdidfFn = M.getOrInsertFunction("__floatdidf", d, l, 0);
136       // void* malloc(size_t)
137       mallocFn = M.getOrInsertFunction("malloc", voidPtr, Type::UIntTy, 0);
138       // void free(void*)
139       freeFn = M.getOrInsertFunction("free", Type::VoidTy, voidPtr, 0);
140       return false;
141     }
142
143     /// runOnFunction - Top level implementation of instruction selection for
144     /// the entire function.
145     ///
146     bool runOnFunction(Function &Fn) {
147       // First pass over the function, lower any unknown intrinsic functions
148       // with the IntrinsicLowering class.
149       LowerUnknownIntrinsicFunctionCalls(Fn);
150
151       F = &MachineFunction::construct(&Fn, TM);
152
153       // Create all of the machine basic blocks for the function...
154       for (Function::iterator I = Fn.begin(), E = Fn.end(); I != E; ++I)
155         F->getBasicBlockList().push_back(MBBMap[I] = new MachineBasicBlock(I));
156
157       BB = &F->front();
158
159       // Copy incoming arguments off of the stack...
160       LoadArgumentsToVirtualRegs(Fn);
161
162       // Instruction select everything except PHI nodes
163       visit(Fn);
164
165       // Select the PHI nodes
166       SelectPHINodes();
167
168       RegMap.clear();
169       MBBMap.clear();
170       AllocaMap.clear();
171       F = 0;
172       // We always build a machine code representation for the function
173       return true;
174     }
175
176     virtual const char *getPassName() const {
177       return "PowerPC Simple Instruction Selection";
178     }
179
180     /// visitBasicBlock - This method is called when we are visiting a new basic
181     /// block.  This simply creates a new MachineBasicBlock to emit code into
182     /// and adds it to the current MachineFunction.  Subsequent visit* for
183     /// instructions will be invoked for all instructions in the basic block.
184     ///
185     void visitBasicBlock(BasicBlock &LLVM_BB) {
186       BB = MBBMap[&LLVM_BB];
187     }
188
189     /// LowerUnknownIntrinsicFunctionCalls - This performs a prepass over the
190     /// function, lowering any calls to unknown intrinsic functions into the
191     /// equivalent LLVM code.
192     ///
193     void LowerUnknownIntrinsicFunctionCalls(Function &F);
194
195     /// LoadArgumentsToVirtualRegs - Load all of the arguments to this function
196     /// from the stack into virtual registers.
197     ///
198     void LoadArgumentsToVirtualRegs(Function &F);
199
200     /// SelectPHINodes - Insert machine code to generate phis.  This is tricky
201     /// because we have to generate our sources into the source basic blocks,
202     /// not the current one.
203     ///
204     void SelectPHINodes();
205
206     // Visitation methods for various instructions.  These methods simply emit
207     // fixed PowerPC code for each instruction.
208
209     // Control flow operators
210     void visitReturnInst(ReturnInst &RI);
211     void visitBranchInst(BranchInst &BI);
212
213     struct ValueRecord {
214       Value *Val;
215       unsigned Reg;
216       const Type *Ty;
217       ValueRecord(unsigned R, const Type *T) : Val(0), Reg(R), Ty(T) {}
218       ValueRecord(Value *V) : Val(V), Reg(0), Ty(V->getType()) {}
219     };
220     
221     // This struct is for recording the necessary operations to emit the GEP
222     struct CollapsedGepOp {
223       bool isMul;
224       Value *index;
225       ConstantSInt *size;
226       CollapsedGepOp(bool mul, Value *i, ConstantSInt *s) :
227         isMul(mul), index(i), size(s) {}
228     };
229
230     void doCall(const ValueRecord &Ret, MachineInstr *CallMI,
231                 const std::vector<ValueRecord> &Args, bool isVarArg);
232     void visitCallInst(CallInst &I);
233     void visitIntrinsicCall(Intrinsic::ID ID, CallInst &I);
234
235     // Arithmetic operators
236     void visitSimpleBinary(BinaryOperator &B, unsigned OpcodeClass);
237     void visitAdd(BinaryOperator &B) { visitSimpleBinary(B, 0); }
238     void visitSub(BinaryOperator &B) { visitSimpleBinary(B, 1); }
239     void visitMul(BinaryOperator &B);
240
241     void visitDiv(BinaryOperator &B) { visitDivRem(B); }
242     void visitRem(BinaryOperator &B) { visitDivRem(B); }
243     void visitDivRem(BinaryOperator &B);
244
245     // Bitwise operators
246     void visitAnd(BinaryOperator &B) { visitSimpleBinary(B, 2); }
247     void visitOr (BinaryOperator &B) { visitSimpleBinary(B, 3); }
248     void visitXor(BinaryOperator &B) { visitSimpleBinary(B, 4); }
249
250     // Comparison operators...
251     void visitSetCondInst(SetCondInst &I);
252     unsigned EmitComparison(unsigned OpNum, Value *Op0, Value *Op1,
253                             MachineBasicBlock *MBB,
254                             MachineBasicBlock::iterator MBBI);
255     void visitSelectInst(SelectInst &SI);
256     
257     
258     // Memory Instructions
259     void visitLoadInst(LoadInst &I);
260     void visitStoreInst(StoreInst &I);
261     void visitGetElementPtrInst(GetElementPtrInst &I);
262     void visitAllocaInst(AllocaInst &I);
263     void visitMallocInst(MallocInst &I);
264     void visitFreeInst(FreeInst &I);
265     
266     // Other operators
267     void visitShiftInst(ShiftInst &I);
268     void visitPHINode(PHINode &I) {}      // PHI nodes handled by second pass
269     void visitCastInst(CastInst &I);
270     void visitVANextInst(VANextInst &I);
271     void visitVAArgInst(VAArgInst &I);
272
273     void visitInstruction(Instruction &I) {
274       std::cerr << "Cannot instruction select: " << I;
275       abort();
276     }
277
278     /// promote32 - Make a value 32-bits wide, and put it somewhere.
279     ///
280     void promote32(unsigned targetReg, const ValueRecord &VR);
281
282     /// emitGEPOperation - Common code shared between visitGetElementPtrInst and
283     /// constant expression GEP support.
284     ///
285     void emitGEPOperation(MachineBasicBlock *BB, MachineBasicBlock::iterator IP,
286                           Value *Src, User::op_iterator IdxBegin,
287                           User::op_iterator IdxEnd, unsigned TargetReg,
288                           bool CollapseRemainder, ConstantSInt **Remainder,
289                           unsigned *PendingAddReg);
290
291     /// emitCastOperation - Common code shared between visitCastInst and
292     /// constant expression cast support.
293     ///
294     void emitCastOperation(MachineBasicBlock *BB,MachineBasicBlock::iterator IP,
295                            Value *Src, const Type *DestTy, unsigned TargetReg);
296
297     /// emitSimpleBinaryOperation - Common code shared between visitSimpleBinary
298     /// and constant expression support.
299     ///
300     void emitSimpleBinaryOperation(MachineBasicBlock *BB,
301                                    MachineBasicBlock::iterator IP,
302                                    Value *Op0, Value *Op1,
303                                    unsigned OperatorClass, unsigned TargetReg);
304
305     /// emitBinaryFPOperation - This method handles emission of floating point
306     /// Add (0), Sub (1), Mul (2), and Div (3) operations.
307     void emitBinaryFPOperation(MachineBasicBlock *BB,
308                                MachineBasicBlock::iterator IP,
309                                Value *Op0, Value *Op1,
310                                unsigned OperatorClass, unsigned TargetReg);
311
312     void emitMultiply(MachineBasicBlock *BB, MachineBasicBlock::iterator IP,
313                       Value *Op0, Value *Op1, unsigned TargetReg);
314
315     void doMultiply(MachineBasicBlock *MBB,
316                     MachineBasicBlock::iterator IP,
317                     unsigned DestReg, Value *Op0, Value *Op1);
318   
319     /// doMultiplyConst - This method will multiply the value in Op0Reg by the
320     /// value of the ContantInt *CI
321     void doMultiplyConst(MachineBasicBlock *MBB, 
322                          MachineBasicBlock::iterator IP,
323                          unsigned DestReg, Value *Op0, ConstantInt *CI);
324
325     void emitDivRemOperation(MachineBasicBlock *BB,
326                              MachineBasicBlock::iterator IP,
327                              Value *Op0, Value *Op1, bool isDiv,
328                              unsigned TargetReg);
329
330     /// emitSetCCOperation - Common code shared between visitSetCondInst and
331     /// constant expression support.
332     ///
333     void emitSetCCOperation(MachineBasicBlock *BB,
334                             MachineBasicBlock::iterator IP,
335                             Value *Op0, Value *Op1, unsigned Opcode,
336                             unsigned TargetReg);
337
338     /// emitShiftOperation - Common code shared between visitShiftInst and
339     /// constant expression support.
340     ///
341     void emitShiftOperation(MachineBasicBlock *MBB,
342                             MachineBasicBlock::iterator IP,
343                             Value *Op, Value *ShiftAmount, bool isLeftShift,
344                             const Type *ResultTy, unsigned DestReg);
345       
346     /// emitSelectOperation - Common code shared between visitSelectInst and the
347     /// constant expression support.
348     ///
349     void emitSelectOperation(MachineBasicBlock *MBB,
350                              MachineBasicBlock::iterator IP,
351                              Value *Cond, Value *TrueVal, Value *FalseVal,
352                              unsigned DestReg);
353
354     /// copyConstantToRegister - Output the instructions required to put the
355     /// specified constant into the specified register.
356     ///
357     void copyConstantToRegister(MachineBasicBlock *MBB,
358                                 MachineBasicBlock::iterator MBBI,
359                                 Constant *C, unsigned Reg);
360
361     void emitUCOM(MachineBasicBlock *MBB, MachineBasicBlock::iterator MBBI,
362                    unsigned LHS, unsigned RHS);
363
364     /// makeAnotherReg - This method returns the next register number we haven't
365     /// yet used.
366     ///
367     unsigned makeAnotherReg(const Type *Ty) {
368       assert(dynamic_cast<const PPC64RegisterInfo*>(TM.getRegisterInfo()) &&
369              "Current target doesn't have PPC reg info??");
370       const PPC64RegisterInfo *PPCRI =
371         static_cast<const PPC64RegisterInfo*>(TM.getRegisterInfo());
372       // Add the mapping of regnumber => reg class to MachineFunction
373       const TargetRegisterClass *RC = PPCRI->getRegClassForType(Ty);
374       return F->getSSARegMap()->createVirtualRegister(RC);
375     }
376
377     /// getReg - This method turns an LLVM value into a register number.
378     ///
379     unsigned getReg(Value &V) { return getReg(&V); }  // Allow references
380     unsigned getReg(Value *V) {
381       // Just append to the end of the current bb.
382       MachineBasicBlock::iterator It = BB->end();
383       return getReg(V, BB, It);
384     }
385     unsigned getReg(Value *V, MachineBasicBlock *MBB,
386                     MachineBasicBlock::iterator IPt);
387     
388     /// canUseAsImmediateForOpcode - This method returns whether a ConstantInt
389     /// is okay to use as an immediate argument to a certain binary operation
390     bool canUseAsImmediateForOpcode(ConstantInt *CI, unsigned Opcode);
391
392     /// getFixedSizedAllocaFI - Return the frame index for a fixed sized alloca
393     /// that is to be statically allocated with the initial stack frame
394     /// adjustment.
395     unsigned getFixedSizedAllocaFI(AllocaInst *AI);
396   };
397 }
398
399 /// dyn_castFixedAlloca - If the specified value is a fixed size alloca
400 /// instruction in the entry block, return it.  Otherwise, return a null
401 /// pointer.
402 static AllocaInst *dyn_castFixedAlloca(Value *V) {
403   if (AllocaInst *AI = dyn_cast<AllocaInst>(V)) {
404     BasicBlock *BB = AI->getParent();
405     if (isa<ConstantUInt>(AI->getArraySize()) && BB ==&BB->getParent()->front())
406       return AI;
407   }
408   return 0;
409 }
410
411 /// getReg - This method turns an LLVM value into a register number.
412 ///
413 unsigned ISel::getReg(Value *V, MachineBasicBlock *MBB,
414                       MachineBasicBlock::iterator IPt) {
415   if (Constant *C = dyn_cast<Constant>(V)) {
416     unsigned Reg = makeAnotherReg(V->getType());
417     copyConstantToRegister(MBB, IPt, C, Reg);
418     return Reg;
419   } else if (AllocaInst *AI = dyn_castFixedAlloca(V)) {
420     unsigned Reg = makeAnotherReg(V->getType());
421     unsigned FI = getFixedSizedAllocaFI(AI);
422     addFrameReference(BuildMI(*MBB, IPt, PPC::ADDI, 2, Reg), FI, 0, false);
423     return Reg;
424   }
425
426   unsigned &Reg = RegMap[V];
427   if (Reg == 0) {
428     Reg = makeAnotherReg(V->getType());
429     RegMap[V] = Reg;
430   }
431
432   return Reg;
433 }
434
435 /// canUseAsImmediateForOpcode - This method returns whether a ConstantInt
436 /// is okay to use as an immediate argument to a certain binary operator.
437 ///
438 /// Operator is one of: 0 for Add, 1 for Sub, 2 for And, 3 for Or, 4 for Xor.
439 bool ISel::canUseAsImmediateForOpcode(ConstantInt *CI, unsigned Operator) {
440   ConstantSInt *Op1Cs;
441   ConstantUInt *Op1Cu;
442       
443   // ADDI, Compare, and non-indexed Load take SIMM
444   bool cond1 = (Operator == 0) 
445     && (Op1Cs = dyn_cast<ConstantSInt>(CI))
446     && (Op1Cs->getValue() <= 32767)
447     && (Op1Cs->getValue() >= -32768);
448
449   // SUBI takes -SIMM since it is a mnemonic for ADDI
450   bool cond2 = (Operator == 1)
451     && (Op1Cs = dyn_cast<ConstantSInt>(CI)) 
452     && (Op1Cs->getValue() <= 32768)
453     && (Op1Cs->getValue() >= -32767);
454       
455   // ANDIo, ORI, and XORI take unsigned values
456   bool cond3 = (Operator >= 2)
457     && (Op1Cs = dyn_cast<ConstantSInt>(CI))
458     && (Op1Cs->getValue() >= 0)
459     && (Op1Cs->getValue() <= 32767);
460
461   // ADDI and SUBI take SIMMs, so we have to make sure the UInt would fit
462   bool cond4 = (Operator < 2)
463     && (Op1Cu = dyn_cast<ConstantUInt>(CI)) 
464     && (Op1Cu->getValue() <= 32767);
465
466   // ANDIo, ORI, and XORI take UIMMs, so they can be larger
467   bool cond5 = (Operator >= 2)
468     && (Op1Cu = dyn_cast<ConstantUInt>(CI))
469     && (Op1Cu->getValue() <= 65535);
470
471   if (cond1 || cond2 || cond3 || cond4 || cond5)
472     return true;
473
474   return false;
475 }
476
477 /// getFixedSizedAllocaFI - Return the frame index for a fixed sized alloca
478 /// that is to be statically allocated with the initial stack frame
479 /// adjustment.
480 unsigned ISel::getFixedSizedAllocaFI(AllocaInst *AI) {
481   // Already computed this?
482   std::map<AllocaInst*, unsigned>::iterator I = AllocaMap.lower_bound(AI);
483   if (I != AllocaMap.end() && I->first == AI) return I->second;
484
485   const Type *Ty = AI->getAllocatedType();
486   ConstantUInt *CUI = cast<ConstantUInt>(AI->getArraySize());
487   unsigned TySize = TM.getTargetData().getTypeSize(Ty);
488   TySize *= CUI->getValue();   // Get total allocated size...
489   unsigned Alignment = TM.getTargetData().getTypeAlignment(Ty);
490       
491   // Create a new stack object using the frame manager...
492   int FrameIdx = F->getFrameInfo()->CreateStackObject(TySize, Alignment);
493   AllocaMap.insert(I, std::make_pair(AI, FrameIdx));
494   return FrameIdx;
495 }
496
497
498 /// copyConstantToRegister - Output the instructions required to put the
499 /// specified constant into the specified register.
500 ///
501 void ISel::copyConstantToRegister(MachineBasicBlock *MBB,
502                                   MachineBasicBlock::iterator IP,
503                                   Constant *C, unsigned R) {
504   if (C->getType()->isIntegral()) {
505     unsigned Class = getClassB(C->getType());
506
507     if (Class == cLong) {
508       if (ConstantUInt *CUI = dyn_cast<ConstantUInt>(C)) {
509         uint64_t uval = CUI->getValue();
510         if (uval < (1LL << 32)) {
511           ConstantUInt *CU = ConstantUInt::get(Type::UIntTy, uval);
512           copyConstantToRegister(MBB, IP, CU, R);
513           return;
514         }
515       } else if (ConstantSInt *CSI = dyn_cast<ConstantSInt>(C)) {
516         int64_t val = CUI->getValue();
517         if (val < (1LL << 31)) {
518           ConstantUInt *CU = ConstantUInt::get(Type::UIntTy, val);
519           copyConstantToRegister(MBB, IP, CU, R);
520           return;
521         }
522       } else {
523         std::cerr << "Unhandled long constant type!\n";
524         abort();
525       }
526       // Spill long to the constant pool and load it
527       MachineConstantPool *CP = F->getConstantPool();
528       unsigned CPI = CP->getConstantPoolIndex(C);
529       BuildMI(*MBB, IP, PPC::LD, 1, R)
530         .addReg(PPC::R2).addConstantPoolIndex(CPI);
531       return;
532     }
533     
534     assert(Class <= cInt && "Type not handled yet!");
535
536     // Handle bool
537     if (C->getType() == Type::BoolTy) {
538       BuildMI(*MBB, IP, PPC::LI, 1, R).addSImm(C == ConstantBool::True);
539       return;
540     }
541     
542     // Handle int
543     if (ConstantUInt *CUI = dyn_cast<ConstantUInt>(C)) {
544       unsigned uval = CUI->getValue();
545       if (uval < 32768) {
546         BuildMI(*MBB, IP, PPC::LI, 1, R).addSImm(uval);
547       } else {
548         unsigned Temp = makeAnotherReg(Type::IntTy);
549         BuildMI(*MBB, IP, PPC::LIS, 1, Temp).addSImm(uval >> 16);
550         BuildMI(*MBB, IP, PPC::ORI, 2, R).addReg(Temp).addImm(uval);
551       }
552       return;
553     } else if (ConstantSInt *CSI = dyn_cast<ConstantSInt>(C)) {
554       int sval = CSI->getValue();
555       if (sval < 32768 && sval >= -32768) {
556         BuildMI(*MBB, IP, PPC::LI, 1, R).addSImm(sval);
557       } else {
558         unsigned Temp = makeAnotherReg(Type::IntTy);
559         BuildMI(*MBB, IP, PPC::LIS, 1, Temp).addSImm(sval >> 16);
560         BuildMI(*MBB, IP, PPC::ORI, 2, R).addReg(Temp).addImm(sval);
561       }
562       return;
563     }
564     std::cerr << "Unhandled integer constant!\n";
565     abort();
566   } else if (ConstantFP *CFP = dyn_cast<ConstantFP>(C)) {
567     // We need to spill the constant to memory...
568     MachineConstantPool *CP = F->getConstantPool();
569     unsigned CPI = CP->getConstantPoolIndex(CFP);
570     const Type *Ty = CFP->getType();
571     unsigned LoadOpcode = (Ty == Type::FloatTy) ? PPC::LFS : PPC::LFD;
572     BuildMI(*MBB,IP,LoadOpcode,2,R).addConstantPoolIndex(CPI).addReg(PPC::R2);
573   } else if (isa<ConstantPointerNull>(C)) {
574     // Copy zero (null pointer) to the register.
575     BuildMI(*MBB, IP, PPC::LI, 1, R).addSImm(0);
576   } else if (GlobalValue *GV = dyn_cast<GlobalValue>(C)) {
577     static unsigned OpcodeTable[] = {
578       PPC::LBZ, PPC::LHZ, PPC::LWZ, PPC::LFS, PPC::LFD, PPC::LD
579     };
580     unsigned Opcode = OpcodeTable[getClassB(GV->getType())];
581     BuildMI(*MBB, IP, Opcode, 2, R).addGlobalAddress(GV).addReg(PPC::R2);
582   } else {
583     std::cerr << "Offending constant: " << *C << "\n";
584     assert(0 && "Type not handled yet!");
585   }
586 }
587
588 /// LoadArgumentsToVirtualRegs - Load all of the arguments to this function from
589 /// the stack into virtual registers.
590 void ISel::LoadArgumentsToVirtualRegs(Function &Fn) {
591   unsigned ArgOffset = ParameterSaveAreaOffset;
592   unsigned GPR_remaining = 8;
593   unsigned FPR_remaining = 13;
594   unsigned GPR_idx = 0, FPR_idx = 0;
595   static const unsigned GPR[] = { 
596     PPC::R3, PPC::R4, PPC::R5, PPC::R6,
597     PPC::R7, PPC::R8, PPC::R9, PPC::R10,
598   };
599   static const unsigned FPR[] = {
600     PPC::F1, PPC::F2, PPC::F3, PPC::F4, PPC::F5, PPC::F6, PPC::F7,
601     PPC::F8, PPC::F9, PPC::F10, PPC::F11, PPC::F12, PPC::F13
602   };
603     
604   MachineFrameInfo *MFI = F->getFrameInfo();
605  
606   for (Function::aiterator I = Fn.abegin(), E = Fn.aend(); I != E; ++I) {
607     bool ArgLive = !I->use_empty();
608     unsigned Reg = ArgLive ? getReg(*I) : 0;
609     int FI;          // Frame object index
610
611     switch (getClassB(I->getType())) {
612     case cByte:
613       if (ArgLive) {
614         FI = MFI->CreateFixedObject(4, ArgOffset);
615         if (GPR_remaining > 0) {
616           BuildMI(BB, PPC::IMPLICIT_DEF, 0, GPR[GPR_idx]);
617           BuildMI(BB, PPC::OR, 2, Reg).addReg(GPR[GPR_idx])
618             .addReg(GPR[GPR_idx]);
619         } else {
620           addFrameReference(BuildMI(BB, PPC::LBZ, 2, Reg), FI);
621         }
622       }
623       break;
624     case cShort:
625       if (ArgLive) {
626         FI = MFI->CreateFixedObject(4, ArgOffset);
627         if (GPR_remaining > 0) {
628           BuildMI(BB, PPC::IMPLICIT_DEF, 0, GPR[GPR_idx]);
629           BuildMI(BB, PPC::OR, 2, Reg).addReg(GPR[GPR_idx])
630             .addReg(GPR[GPR_idx]);
631         } else {
632           addFrameReference(BuildMI(BB, PPC::LHZ, 2, Reg), FI);
633         }
634       }
635       break;
636     case cInt:
637       if (ArgLive) {
638         FI = MFI->CreateFixedObject(4, ArgOffset);
639         if (GPR_remaining > 0) {
640           BuildMI(BB, PPC::IMPLICIT_DEF, 0, GPR[GPR_idx]);
641           BuildMI(BB, PPC::OR, 2, Reg).addReg(GPR[GPR_idx])
642             .addReg(GPR[GPR_idx]);
643         } else {
644           addFrameReference(BuildMI(BB, PPC::LWZ, 2, Reg), FI);
645         }
646       }
647       break;
648     case cLong:
649       if (ArgLive) {
650         FI = MFI->CreateFixedObject(8, ArgOffset);
651         if (GPR_remaining > 1) {
652           BuildMI(BB, PPC::IMPLICIT_DEF, 0, GPR[GPR_idx]);
653           BuildMI(BB, PPC::OR, 2, Reg).addReg(GPR[GPR_idx])
654             .addReg(GPR[GPR_idx]);
655         } else {
656           addFrameReference(BuildMI(BB, PPC::LD, 2, Reg), FI);
657         }
658       }
659       // longs require 4 additional bytes
660       ArgOffset += 4;
661       break;
662     case cFP32:
663      if (ArgLive) {
664         FI = MFI->CreateFixedObject(4, ArgOffset);
665
666         if (FPR_remaining > 0) {
667           BuildMI(BB, PPC::IMPLICIT_DEF, 0, FPR[FPR_idx]);
668           BuildMI(BB, PPC::FMR, 1, Reg).addReg(FPR[FPR_idx]);
669           FPR_remaining--;
670           FPR_idx++;
671         } else {
672           addFrameReference(BuildMI(BB, PPC::LFS, 2, Reg), FI);
673         }
674       }
675       break;
676     case cFP64:
677       if (ArgLive) {
678         FI = MFI->CreateFixedObject(8, ArgOffset);
679
680         if (FPR_remaining > 0) {
681           BuildMI(BB, PPC::IMPLICIT_DEF, 0, FPR[FPR_idx]);
682           BuildMI(BB, PPC::FMR, 1, Reg).addReg(FPR[FPR_idx]);
683           FPR_remaining--;
684           FPR_idx++;
685         } else {
686           addFrameReference(BuildMI(BB, PPC::LFD, 2, Reg), FI);
687         }
688       }
689
690       // doubles require 4 additional bytes and use 2 GPRs of param space
691       ArgOffset += 4;   
692       if (GPR_remaining > 0) {
693         GPR_remaining--;
694         GPR_idx++;
695       }
696       break;
697     default:
698       assert(0 && "Unhandled argument type!");
699     }
700     ArgOffset += 4;  // Each argument takes at least 4 bytes on the stack...
701     if (GPR_remaining > 0) {
702       GPR_remaining--;    // uses up 2 GPRs
703       GPR_idx++;
704     }
705   }
706
707   // If the function takes variable number of arguments, add a frame offset for
708   // the start of the first vararg value... this is used to expand
709   // llvm.va_start.
710   if (Fn.getFunctionType()->isVarArg())
711     VarArgsFrameIndex = MFI->CreateFixedObject(4, ArgOffset);
712 }
713
714
715 /// SelectPHINodes - Insert machine code to generate phis.  This is tricky
716 /// because we have to generate our sources into the source basic blocks, not
717 /// the current one.
718 ///
719 void ISel::SelectPHINodes() {
720   const TargetInstrInfo &TII = *TM.getInstrInfo();
721   const Function &LF = *F->getFunction();  // The LLVM function...
722   for (Function::const_iterator I = LF.begin(), E = LF.end(); I != E; ++I) {
723     const BasicBlock *BB = I;
724     MachineBasicBlock &MBB = *MBBMap[I];
725
726     // Loop over all of the PHI nodes in the LLVM basic block...
727     MachineBasicBlock::iterator PHIInsertPoint = MBB.begin();
728     for (BasicBlock::const_iterator I = BB->begin();
729          PHINode *PN = const_cast<PHINode*>(dyn_cast<PHINode>(I)); ++I) {
730
731       // Create a new machine instr PHI node, and insert it.
732       unsigned PHIReg = getReg(*PN);
733       MachineInstr *PhiMI = BuildMI(MBB, PHIInsertPoint,
734                                     PPC::PHI, PN->getNumOperands(), PHIReg);
735
736       // PHIValues - Map of blocks to incoming virtual registers.  We use this
737       // so that we only initialize one incoming value for a particular block,
738       // even if the block has multiple entries in the PHI node.
739       //
740       std::map<MachineBasicBlock*, unsigned> PHIValues;
741
742       for (unsigned i = 0, e = PN->getNumIncomingValues(); i != e; ++i) {
743         MachineBasicBlock *PredMBB = 0;
744         for (MachineBasicBlock::pred_iterator PI = MBB.pred_begin (),
745              PE = MBB.pred_end (); PI != PE; ++PI)
746           if (PN->getIncomingBlock(i) == (*PI)->getBasicBlock()) {
747             PredMBB = *PI;
748             break;
749           }
750         assert (PredMBB && "Couldn't find incoming machine-cfg edge for phi");
751
752         unsigned ValReg;
753         std::map<MachineBasicBlock*, unsigned>::iterator EntryIt =
754           PHIValues.lower_bound(PredMBB);
755
756         if (EntryIt != PHIValues.end() && EntryIt->first == PredMBB) {
757           // We already inserted an initialization of the register for this
758           // predecessor.  Recycle it.
759           ValReg = EntryIt->second;
760         } else {
761           // Get the incoming value into a virtual register.
762           //
763           Value *Val = PN->getIncomingValue(i);
764
765           // If this is a constant or GlobalValue, we may have to insert code
766           // into the basic block to compute it into a virtual register.
767           if ((isa<Constant>(Val) && !isa<ConstantExpr>(Val)) ||
768               isa<GlobalValue>(Val)) {
769             // Simple constants get emitted at the end of the basic block,
770             // before any terminator instructions.  We "know" that the code to
771             // move a constant into a register will never clobber any flags.
772             ValReg = getReg(Val, PredMBB, PredMBB->getFirstTerminator());
773           } else {
774             // Because we don't want to clobber any values which might be in
775             // physical registers with the computation of this constant (which
776             // might be arbitrarily complex if it is a constant expression),
777             // just insert the computation at the top of the basic block.
778             MachineBasicBlock::iterator PI = PredMBB->begin();
779
780             // Skip over any PHI nodes though!
781             while (PI != PredMBB->end() && PI->getOpcode() == PPC::PHI)
782               ++PI;
783
784             ValReg = getReg(Val, PredMBB, PI);
785           }
786
787           // Remember that we inserted a value for this PHI for this predecessor
788           PHIValues.insert(EntryIt, std::make_pair(PredMBB, ValReg));
789         }
790
791         PhiMI->addRegOperand(ValReg);
792         PhiMI->addMachineBasicBlockOperand(PredMBB);
793       }
794
795       // Now that we emitted all of the incoming values for the PHI node, make
796       // sure to reposition the InsertPoint after the PHI that we just added.
797       // This is needed because we might have inserted a constant into this
798       // block, right after the PHI's which is before the old insert point!
799       PHIInsertPoint = PhiMI;
800       ++PHIInsertPoint;
801     }
802   }
803 }
804
805
806 // canFoldSetCCIntoBranchOrSelect - Return the setcc instruction if we can fold
807 // it into the conditional branch or select instruction which is the only user
808 // of the cc instruction.  This is the case if the conditional branch is the
809 // only user of the setcc, and if the setcc is in the same basic block as the
810 // conditional branch.
811 //
812 static SetCondInst *canFoldSetCCIntoBranchOrSelect(Value *V) {
813   if (SetCondInst *SCI = dyn_cast<SetCondInst>(V))
814     if (SCI->hasOneUse()) {
815       Instruction *User = cast<Instruction>(SCI->use_back());
816       if ((isa<BranchInst>(User) || isa<SelectInst>(User)) &&
817           SCI->getParent() == User->getParent())
818         return SCI;
819     }
820   return 0;
821 }
822
823
824 // canFoldGEPIntoLoadOrStore - Return the GEP instruction if we can fold it into
825 // the load or store instruction that is the only user of the GEP.
826 //
827 static GetElementPtrInst *canFoldGEPIntoLoadOrStore(Value *V) {
828   if (GetElementPtrInst *GEPI = dyn_cast<GetElementPtrInst>(V))
829     if (GEPI->hasOneUse()) {
830       Instruction *User = cast<Instruction>(GEPI->use_back());
831       if (isa<StoreInst>(User) &&
832           GEPI->getParent() == User->getParent() &&
833           User->getOperand(0) != GEPI &&
834           User->getOperand(1) == GEPI) {
835         ++GEPFolds;
836         return GEPI;
837       }
838       if (isa<LoadInst>(User) &&
839           GEPI->getParent() == User->getParent() &&
840           User->getOperand(0) == GEPI) {
841         ++GEPFolds;
842         return GEPI;
843       }
844     }
845   return 0;
846 }
847
848
849 // Return a fixed numbering for setcc instructions which does not depend on the
850 // order of the opcodes.
851 //
852 static unsigned getSetCCNumber(unsigned Opcode) {
853   switch (Opcode) {
854   default: assert(0 && "Unknown setcc instruction!");
855   case Instruction::SetEQ: return 0;
856   case Instruction::SetNE: return 1;
857   case Instruction::SetLT: return 2;
858   case Instruction::SetGE: return 3;
859   case Instruction::SetGT: return 4;
860   case Instruction::SetLE: return 5;
861   }
862 }
863
864 static unsigned getPPCOpcodeForSetCCNumber(unsigned Opcode) {
865   switch (Opcode) {
866   default: assert(0 && "Unknown setcc instruction!");
867   case Instruction::SetEQ: return PPC::BEQ;
868   case Instruction::SetNE: return PPC::BNE;
869   case Instruction::SetLT: return PPC::BLT;
870   case Instruction::SetGE: return PPC::BGE;
871   case Instruction::SetGT: return PPC::BGT;
872   case Instruction::SetLE: return PPC::BLE;
873   }
874 }
875
876 /// emitUCOM - emits an unordered FP compare.
877 void ISel::emitUCOM(MachineBasicBlock *MBB, MachineBasicBlock::iterator IP,
878                     unsigned LHS, unsigned RHS) {
879     BuildMI(*MBB, IP, PPC::FCMPU, 2, PPC::CR0).addReg(LHS).addReg(RHS);
880 }
881
882 /// EmitComparison - emits a comparison of the two operands, returning the
883 /// extended setcc code to use.  The result is in CR0.
884 ///
885 unsigned ISel::EmitComparison(unsigned OpNum, Value *Op0, Value *Op1,
886                               MachineBasicBlock *MBB,
887                               MachineBasicBlock::iterator IP) {
888   // The arguments are already supposed to be of the same type.
889   const Type *CompTy = Op0->getType();
890   unsigned Class = getClassB(CompTy);
891   unsigned Op0r = getReg(Op0, MBB, IP);
892
893   // Before we do a comparison, we have to make sure that we're truncating our
894   // registers appropriately.
895   if (Class == cByte) {
896     unsigned TmpReg = makeAnotherReg(CompTy);
897     if (CompTy->isSigned())
898       BuildMI(*MBB, IP, PPC::EXTSB, 1, TmpReg).addReg(Op0r);
899     else
900       BuildMI(*MBB, IP, PPC::RLWINM, 4, TmpReg).addReg(Op0r).addImm(0)
901         .addImm(24).addImm(31);
902     Op0r = TmpReg;
903   } else if (Class == cShort) {
904     unsigned TmpReg = makeAnotherReg(CompTy);
905     if (CompTy->isSigned())
906       BuildMI(*MBB, IP, PPC::EXTSH, 1, TmpReg).addReg(Op0r);
907     else
908       BuildMI(*MBB, IP, PPC::RLWINM, 4, TmpReg).addReg(Op0r).addImm(0)
909         .addImm(16).addImm(31);
910     Op0r = TmpReg;
911   }
912   
913   // Use crand for lt, gt and crandc for le, ge
914   unsigned CROpcode = (OpNum == 2 || OpNum == 4) ? PPC::CRAND : PPC::CRANDC;
915   unsigned Opcode = CompTy->isSigned() ? PPC::CMPW : PPC::CMPLW;
916   unsigned OpcodeImm = CompTy->isSigned() ? PPC::CMPWI : PPC::CMPLWI;
917   if (Class == cLong) {
918     Opcode = CompTy->isSigned() ? PPC::CMPD : PPC::CMPLD;
919     OpcodeImm = CompTy->isSigned() ? PPC::CMPDI : PPC::CMPLDI;
920   }
921
922   // Special case handling of: cmp R, i
923   if (ConstantInt *CI = dyn_cast<ConstantInt>(Op1)) {
924     unsigned Op1v = CI->getRawValue() & 0xFFFF;
925
926     // Treat compare like ADDI for the purposes of immediate suitability
927     if (canUseAsImmediateForOpcode(CI, 0)) {
928       BuildMI(*MBB, IP, OpcodeImm, 2, PPC::CR0).addReg(Op0r).addSImm(Op1v);
929     } else {
930       unsigned Op1r = getReg(Op1, MBB, IP);
931       BuildMI(*MBB, IP, Opcode, 2, PPC::CR0).addReg(Op0r).addReg(Op1r);
932     }
933     return OpNum;
934   }
935
936   unsigned Op1r = getReg(Op1, MBB, IP);
937
938   switch (Class) {
939   default: assert(0 && "Unknown type class!");
940   case cByte:
941   case cShort:
942   case cInt:
943   case cLong:
944     BuildMI(*MBB, IP, Opcode, 2, PPC::CR0).addReg(Op0r).addReg(Op1r);
945     break;
946
947   case cFP32:
948   case cFP64:
949     emitUCOM(MBB, IP, Op0r, Op1r);
950     break;
951   }
952
953   return OpNum;
954 }
955
956 /// visitSetCondInst - emit code to calculate the condition via
957 /// EmitComparison(), and possibly store a 0 or 1 to a register as a result
958 ///
959 void ISel::visitSetCondInst(SetCondInst &I) {
960   if (canFoldSetCCIntoBranchOrSelect(&I))
961     return;
962
963   unsigned DestReg = getReg(I);
964   unsigned OpNum = I.getOpcode();
965   const Type *Ty = I.getOperand (0)->getType();
966
967   EmitComparison(OpNum, I.getOperand(0), I.getOperand(1), BB, BB->end());
968   
969   unsigned Opcode = getPPCOpcodeForSetCCNumber(OpNum);
970   MachineBasicBlock *thisMBB = BB;
971   const BasicBlock *LLVM_BB = BB->getBasicBlock();
972   ilist<MachineBasicBlock>::iterator It = BB;
973   ++It;
974   
975   //  thisMBB:
976   //  ...
977   //   cmpTY cr0, r1, r2
978   //   bCC copy1MBB
979   //   b copy0MBB
980
981   // FIXME: we wouldn't need copy0MBB (we could fold it into thisMBB)
982   // if we could insert other, non-terminator instructions after the
983   // bCC. But MBB->getFirstTerminator() can't understand this.
984   MachineBasicBlock *copy1MBB = new MachineBasicBlock(LLVM_BB);
985   F->getBasicBlockList().insert(It, copy1MBB);
986   BuildMI(BB, Opcode, 2).addReg(PPC::CR0).addMBB(copy1MBB);
987   MachineBasicBlock *copy0MBB = new MachineBasicBlock(LLVM_BB);
988   F->getBasicBlockList().insert(It, copy0MBB);
989   BuildMI(BB, PPC::B, 1).addMBB(copy0MBB);
990   MachineBasicBlock *sinkMBB = new MachineBasicBlock(LLVM_BB);
991   F->getBasicBlockList().insert(It, sinkMBB);
992   // Update machine-CFG edges
993   BB->addSuccessor(copy1MBB);
994   BB->addSuccessor(copy0MBB);
995
996   //  copy1MBB:
997   //   %TrueValue = li 1
998   //   b sinkMBB
999   BB = copy1MBB;
1000   unsigned TrueValue = makeAnotherReg(I.getType());
1001   BuildMI(BB, PPC::LI, 1, TrueValue).addSImm(1);
1002   BuildMI(BB, PPC::B, 1).addMBB(sinkMBB);
1003   // Update machine-CFG edges
1004   BB->addSuccessor(sinkMBB);
1005
1006   //  copy0MBB:
1007   //   %FalseValue = li 0
1008   //   fallthrough
1009   BB = copy0MBB;
1010   unsigned FalseValue = makeAnotherReg(I.getType());
1011   BuildMI(BB, PPC::LI, 1, FalseValue).addSImm(0);
1012   // Update machine-CFG edges
1013   BB->addSuccessor(sinkMBB);
1014
1015   //  sinkMBB:
1016   //   %Result = phi [ %FalseValue, copy0MBB ], [ %TrueValue, copy1MBB ]
1017   //  ...
1018   BB = sinkMBB;
1019   BuildMI(BB, PPC::PHI, 4, DestReg).addReg(FalseValue)
1020     .addMBB(copy0MBB).addReg(TrueValue).addMBB(copy1MBB);
1021 }
1022
1023 void ISel::visitSelectInst(SelectInst &SI) {
1024   unsigned DestReg = getReg(SI);
1025   MachineBasicBlock::iterator MII = BB->end();
1026   emitSelectOperation(BB, MII, SI.getCondition(), SI.getTrueValue(),
1027                       SI.getFalseValue(), DestReg);
1028 }
1029  
1030 /// emitSelect - Common code shared between visitSelectInst and the constant
1031 /// expression support.
1032 /// FIXME: this is most likely broken in one or more ways.  Namely, PowerPC has
1033 /// no select instruction.  FSEL only works for comparisons against zero.
1034 void ISel::emitSelectOperation(MachineBasicBlock *MBB,
1035                                MachineBasicBlock::iterator IP,
1036                                Value *Cond, Value *TrueVal, Value *FalseVal,
1037                                unsigned DestReg) {
1038   unsigned SelectClass = getClassB(TrueVal->getType());
1039   unsigned Opcode;
1040
1041   // See if we can fold the setcc into the select instruction, or if we have
1042   // to get the register of the Cond value
1043   if (SetCondInst *SCI = canFoldSetCCIntoBranchOrSelect(Cond)) {
1044     // We successfully folded the setcc into the select instruction.
1045     unsigned OpNum = getSetCCNumber(SCI->getOpcode());
1046     OpNum = EmitComparison(OpNum, SCI->getOperand(0),SCI->getOperand(1),MBB,IP);
1047     Opcode = getPPCOpcodeForSetCCNumber(SCI->getOpcode());
1048   } else {
1049     unsigned CondReg = getReg(Cond, MBB, IP);
1050     BuildMI(*MBB, IP, PPC::CMPI, 2, PPC::CR0).addReg(CondReg).addSImm(0);
1051     Opcode = getPPCOpcodeForSetCCNumber(Instruction::SetNE);
1052   }
1053
1054   //  thisMBB:
1055   //  ...
1056   //   cmpTY cr0, r1, r2
1057   //   bCC copy1MBB
1058   //   b copy0MBB
1059
1060   MachineBasicBlock *thisMBB = BB;
1061   const BasicBlock *LLVM_BB = BB->getBasicBlock();
1062   ilist<MachineBasicBlock>::iterator It = BB;
1063   ++It;
1064
1065   // FIXME: we wouldn't need copy0MBB (we could fold it into thisMBB)
1066   // if we could insert other, non-terminator instructions after the
1067   // bCC. But MBB->getFirstTerminator() can't understand this.
1068   MachineBasicBlock *copy1MBB = new MachineBasicBlock(LLVM_BB);
1069   F->getBasicBlockList().insert(It, copy1MBB);
1070   BuildMI(BB, Opcode, 2).addReg(PPC::CR0).addMBB(copy1MBB);
1071   MachineBasicBlock *copy0MBB = new MachineBasicBlock(LLVM_BB);
1072   F->getBasicBlockList().insert(It, copy0MBB);
1073   BuildMI(BB, PPC::B, 1).addMBB(copy0MBB);
1074   MachineBasicBlock *sinkMBB = new MachineBasicBlock(LLVM_BB);
1075   F->getBasicBlockList().insert(It, sinkMBB);
1076   // Update machine-CFG edges
1077   BB->addSuccessor(copy1MBB);
1078   BB->addSuccessor(copy0MBB);
1079
1080   //  copy1MBB:
1081   //   %TrueValue = ...
1082   //   b sinkMBB
1083   BB = copy1MBB;
1084   unsigned TrueValue = getReg(TrueVal, BB, BB->begin());
1085   BuildMI(BB, PPC::B, 1).addMBB(sinkMBB);
1086   // Update machine-CFG edges
1087   BB->addSuccessor(sinkMBB);
1088
1089   //  copy0MBB:
1090   //   %FalseValue = ...
1091   //   fallthrough
1092   BB = copy0MBB;
1093   unsigned FalseValue = getReg(FalseVal, BB, BB->begin());
1094   // Update machine-CFG edges
1095   BB->addSuccessor(sinkMBB);
1096
1097   //  sinkMBB:
1098   //   %Result = phi [ %FalseValue, copy0MBB ], [ %TrueValue, copy1MBB ]
1099   //  ...
1100   BB = sinkMBB;
1101   BuildMI(BB, PPC::PHI, 4, DestReg).addReg(FalseValue)
1102     .addMBB(copy0MBB).addReg(TrueValue).addMBB(copy1MBB);
1103   return;
1104 }
1105
1106
1107
1108 /// promote32 - Emit instructions to turn a narrow operand into a 32-bit-wide
1109 /// operand, in the specified target register.
1110 ///
1111 void ISel::promote32(unsigned targetReg, const ValueRecord &VR) {
1112   bool isUnsigned = VR.Ty->isUnsigned() || VR.Ty == Type::BoolTy;
1113
1114   Value *Val = VR.Val;
1115   const Type *Ty = VR.Ty;
1116   if (Val) {
1117     if (Constant *C = dyn_cast<Constant>(Val)) {
1118       Val = ConstantExpr::getCast(C, Type::IntTy);
1119       if (isa<ConstantExpr>(Val))   // Could not fold
1120         Val = C;
1121       else
1122         Ty = Type::IntTy;           // Folded!
1123     }
1124
1125     // If this is a simple constant, just emit a load directly to avoid the copy
1126     if (ConstantInt *CI = dyn_cast<ConstantInt>(Val)) {
1127       int TheVal = CI->getRawValue() & 0xFFFFFFFF;
1128
1129       if (TheVal < 32768 && TheVal >= -32768) {
1130         BuildMI(BB, PPC::LI, 1, targetReg).addSImm(TheVal);
1131       } else {
1132         unsigned TmpReg = makeAnotherReg(Type::IntTy);
1133         BuildMI(BB, PPC::LIS, 1, TmpReg).addSImm(TheVal >> 16);
1134         BuildMI(BB, PPC::ORI, 2, targetReg).addReg(TmpReg)
1135           .addImm(TheVal & 0xFFFF);
1136       }
1137       return;
1138     }
1139   }
1140
1141   // Make sure we have the register number for this value...
1142   unsigned Reg = Val ? getReg(Val) : VR.Reg;
1143   switch (getClassB(Ty)) {
1144   case cByte:
1145     // Extend value into target register (8->32)
1146     if (isUnsigned)
1147       BuildMI(BB, PPC::RLWINM, 4, targetReg).addReg(Reg).addZImm(0)
1148         .addZImm(24).addZImm(31);
1149     else
1150       BuildMI(BB, PPC::EXTSB, 1, targetReg).addReg(Reg);
1151     break;
1152   case cShort:
1153     // Extend value into target register (16->32)
1154     if (isUnsigned)
1155       BuildMI(BB, PPC::RLWINM, 4, targetReg).addReg(Reg).addZImm(0)
1156         .addZImm(16).addZImm(31);
1157     else
1158       BuildMI(BB, PPC::EXTSH, 1, targetReg).addReg(Reg);
1159     break;
1160   case cInt:
1161   case cLong:
1162     // Move value into target register (32->32)
1163     BuildMI(BB, PPC::OR, 2, targetReg).addReg(Reg).addReg(Reg);
1164     break;
1165   default:
1166     assert(0 && "Unpromotable operand class in promote32");
1167   }
1168 }
1169
1170 /// visitReturnInst - implemented with BLR
1171 ///
1172 void ISel::visitReturnInst(ReturnInst &I) {
1173   // Only do the processing if this is a non-void return
1174   if (I.getNumOperands() > 0) {
1175     Value *RetVal = I.getOperand(0);
1176     switch (getClassB(RetVal->getType())) {
1177     case cByte:   // integral return values: extend or move into r3 and return
1178     case cShort:
1179     case cInt:
1180     case cLong:
1181       promote32(PPC::R3, ValueRecord(RetVal));
1182       break;
1183     case cFP32:
1184     case cFP64: {   // Floats & Doubles: Return in f1
1185       unsigned RetReg = getReg(RetVal);
1186       BuildMI(BB, PPC::FMR, 1, PPC::F1).addReg(RetReg);
1187       break;
1188     }
1189     default:
1190       visitInstruction(I);
1191     }
1192   }
1193   BuildMI(BB, PPC::BLR, 1).addImm(1);
1194 }
1195
1196 // getBlockAfter - Return the basic block which occurs lexically after the
1197 // specified one.
1198 static inline BasicBlock *getBlockAfter(BasicBlock *BB) {
1199   Function::iterator I = BB; ++I;  // Get iterator to next block
1200   return I != BB->getParent()->end() ? &*I : 0;
1201 }
1202
1203 /// visitBranchInst - Handle conditional and unconditional branches here.  Note
1204 /// that since code layout is frozen at this point, that if we are trying to
1205 /// jump to a block that is the immediate successor of the current block, we can
1206 /// just make a fall-through (but we don't currently).
1207 ///
1208 void ISel::visitBranchInst(BranchInst &BI) {
1209   // Update machine-CFG edges
1210   BB->addSuccessor(MBBMap[BI.getSuccessor(0)]);
1211   if (BI.isConditional())
1212     BB->addSuccessor(MBBMap[BI.getSuccessor(1)]);
1213   
1214   BasicBlock *NextBB = getBlockAfter(BI.getParent());  // BB after current one
1215
1216   if (!BI.isConditional()) {  // Unconditional branch?
1217     if (BI.getSuccessor(0) != NextBB) 
1218       BuildMI(BB, PPC::B, 1).addMBB(MBBMap[BI.getSuccessor(0)]);
1219     return;
1220   }
1221   
1222   // See if we can fold the setcc into the branch itself...
1223   SetCondInst *SCI = canFoldSetCCIntoBranchOrSelect(BI.getCondition());
1224   if (SCI == 0) {
1225     // Nope, cannot fold setcc into this branch.  Emit a branch on a condition
1226     // computed some other way...
1227     unsigned condReg = getReg(BI.getCondition());
1228     BuildMI(BB, PPC::CMPLI, 3, PPC::CR0).addImm(0).addReg(condReg)
1229       .addImm(0);
1230     if (BI.getSuccessor(1) == NextBB) {
1231       if (BI.getSuccessor(0) != NextBB)
1232         BuildMI(BB, PPC::COND_BRANCH, 3).addReg(PPC::CR0).addImm(PPC::BNE)
1233           .addMBB(MBBMap[BI.getSuccessor(0)])
1234           .addMBB(MBBMap[BI.getSuccessor(1)]);
1235     } else {
1236       BuildMI(BB, PPC::COND_BRANCH, 3).addReg(PPC::CR0).addImm(PPC::BEQ)
1237         .addMBB(MBBMap[BI.getSuccessor(1)])
1238         .addMBB(MBBMap[BI.getSuccessor(0)]);
1239       if (BI.getSuccessor(0) != NextBB)
1240         BuildMI(BB, PPC::B, 1).addMBB(MBBMap[BI.getSuccessor(0)]);
1241     }
1242     return;
1243   }
1244
1245   unsigned OpNum = getSetCCNumber(SCI->getOpcode());
1246   unsigned Opcode = getPPCOpcodeForSetCCNumber(SCI->getOpcode());
1247   MachineBasicBlock::iterator MII = BB->end();
1248   OpNum = EmitComparison(OpNum, SCI->getOperand(0), SCI->getOperand(1), BB,MII);
1249   
1250   if (BI.getSuccessor(0) != NextBB) {
1251     BuildMI(BB, PPC::COND_BRANCH, 3).addReg(PPC::CR0).addImm(Opcode)
1252       .addMBB(MBBMap[BI.getSuccessor(0)])
1253       .addMBB(MBBMap[BI.getSuccessor(1)]);
1254     if (BI.getSuccessor(1) != NextBB)
1255       BuildMI(BB, PPC::B, 1).addMBB(MBBMap[BI.getSuccessor(1)]);
1256   } else {
1257     // Change to the inverse condition...
1258     if (BI.getSuccessor(1) != NextBB) {
1259       Opcode = PPC64InstrInfo::invertPPCBranchOpcode(Opcode);
1260       BuildMI(BB, PPC::COND_BRANCH, 3).addReg(PPC::CR0).addImm(Opcode)
1261         .addMBB(MBBMap[BI.getSuccessor(1)])
1262         .addMBB(MBBMap[BI.getSuccessor(0)]);
1263     }
1264   }
1265 }
1266
1267 /// doCall - This emits an abstract call instruction, setting up the arguments
1268 /// and the return value as appropriate.  For the actual function call itself,
1269 /// it inserts the specified CallMI instruction into the stream.
1270 ///
1271 void ISel::doCall(const ValueRecord &Ret, MachineInstr *CallMI,
1272                   const std::vector<ValueRecord> &Args, bool isVarArg) {
1273   // Count how many bytes are to be pushed on the stack, including the linkage
1274   // area, and parameter passing area.
1275   unsigned NumBytes = ParameterSaveAreaOffset;
1276   unsigned ArgOffset = ParameterSaveAreaOffset;
1277
1278   if (!Args.empty()) {
1279     for (unsigned i = 0, e = Args.size(); i != e; ++i)
1280       switch (getClassB(Args[i].Ty)) {
1281       case cByte: case cShort: case cInt:
1282         NumBytes += 4; break;
1283       case cLong:
1284         NumBytes += 8; break;
1285       case cFP32:
1286         NumBytes += 4; break;
1287       case cFP64:
1288         NumBytes += 8; break;
1289         break;
1290       default: assert(0 && "Unknown class!");
1291       }
1292
1293     // Just to be safe, we'll always reserve the full argument passing space in
1294     // case any called code gets funky on us.
1295     if (NumBytes < ParameterSaveAreaOffset + MaxArgumentStackSpace) 
1296       NumBytes = ParameterSaveAreaOffset + MaxArgumentStackSpace;
1297
1298     // Adjust the stack pointer for the new arguments...
1299     // These functions are automatically eliminated by the prolog/epilog pass
1300     BuildMI(BB, PPC::ADJCALLSTACKDOWN, 1).addImm(NumBytes);
1301
1302     // Arguments go on the stack in reverse order, as specified by the ABI.
1303     int GPR_remaining = 8, FPR_remaining = 13;
1304     unsigned GPR_idx = 0, FPR_idx = 0;
1305     static const unsigned GPR[] = { 
1306       PPC::R3, PPC::R4, PPC::R5, PPC::R6,
1307       PPC::R7, PPC::R8, PPC::R9, PPC::R10,
1308     };
1309     static const unsigned FPR[] = {
1310       PPC::F1, PPC::F2, PPC::F3, PPC::F4, PPC::F5, PPC::F6, 
1311       PPC::F7, PPC::F8, PPC::F9, PPC::F10, PPC::F11, PPC::F12, 
1312       PPC::F13
1313     };
1314     
1315     for (unsigned i = 0, e = Args.size(); i != e; ++i) {
1316       unsigned ArgReg;
1317       switch (getClassB(Args[i].Ty)) {
1318       case cByte:
1319       case cShort:
1320         // Promote arg to 32 bits wide into a temporary register...
1321         ArgReg = makeAnotherReg(Type::UIntTy);
1322         promote32(ArgReg, Args[i]);
1323           
1324         // Reg or stack?
1325         if (GPR_remaining > 0) {
1326           BuildMI(BB, PPC::OR, 2, GPR[GPR_idx]).addReg(ArgReg)
1327             .addReg(ArgReg);
1328           CallMI->addRegOperand(GPR[GPR_idx], MachineOperand::Use);
1329         }
1330         if (GPR_remaining <= 0 || isVarArg) {
1331           BuildMI(BB, PPC::STW, 3).addReg(ArgReg).addSImm(ArgOffset)
1332             .addReg(PPC::R1);
1333         }
1334         break;
1335       case cInt:
1336         ArgReg = Args[i].Val ? getReg(Args[i].Val) : Args[i].Reg;
1337
1338         // Reg or stack?
1339         if (GPR_remaining > 0) {
1340           BuildMI(BB, PPC::OR, 2, GPR[GPR_idx]).addReg(ArgReg)
1341             .addReg(ArgReg);
1342           CallMI->addRegOperand(GPR[GPR_idx], MachineOperand::Use);
1343         }
1344         if (GPR_remaining <= 0 || isVarArg) {
1345           BuildMI(BB, PPC::STW, 3).addReg(ArgReg).addSImm(ArgOffset)
1346             .addReg(PPC::R1);
1347         }
1348         break;
1349       case cLong:
1350         ArgReg = Args[i].Val ? getReg(Args[i].Val) : Args[i].Reg;
1351
1352         // Reg or stack?
1353         if (GPR_remaining > 0) {
1354           BuildMI(BB, PPC::OR, 2, GPR[GPR_idx]).addReg(ArgReg)
1355             .addReg(ArgReg);
1356           CallMI->addRegOperand(GPR[GPR_idx], MachineOperand::Use);
1357         }
1358         if (GPR_remaining <= 0 || isVarArg) {
1359           BuildMI(BB, PPC::STD, 3).addReg(ArgReg).addSImm(ArgOffset)
1360             .addReg(PPC::R1);
1361         }
1362         ArgOffset += 4;        // 8 byte entry, not 4.
1363         break;
1364       case cFP32:
1365         ArgReg = Args[i].Val ? getReg(Args[i].Val) : Args[i].Reg;
1366         // Reg or stack?
1367         if (FPR_remaining > 0) {
1368           BuildMI(BB, PPC::FMR, 1, FPR[FPR_idx]).addReg(ArgReg);
1369           CallMI->addRegOperand(FPR[FPR_idx], MachineOperand::Use);
1370           FPR_remaining--;
1371           FPR_idx++;
1372           
1373           // If this is a vararg function, and there are GPRs left, also
1374           // pass the float in an int.  Otherwise, put it on the stack.
1375           if (isVarArg) {
1376             BuildMI(BB, PPC::STFS, 3).addReg(ArgReg).addSImm(ArgOffset)
1377               .addReg(PPC::R1);
1378             if (GPR_remaining > 0) {
1379               BuildMI(BB, PPC::LWZ, 2, GPR[GPR_idx])
1380               .addSImm(ArgOffset).addReg(ArgReg);
1381               CallMI->addRegOperand(GPR[GPR_idx], MachineOperand::Use);
1382             }
1383           }
1384         } else {
1385           BuildMI(BB, PPC::STFS, 3).addReg(ArgReg).addSImm(ArgOffset)
1386           .addReg(PPC::R1);
1387         }
1388         break;
1389       case cFP64:
1390         ArgReg = Args[i].Val ? getReg(Args[i].Val) : Args[i].Reg;
1391         // Reg or stack?
1392         if (FPR_remaining > 0) {
1393           BuildMI(BB, PPC::FMR, 1, FPR[FPR_idx]).addReg(ArgReg);
1394           CallMI->addRegOperand(FPR[FPR_idx], MachineOperand::Use);
1395           FPR_remaining--;
1396           FPR_idx++;
1397           // For vararg functions, must pass doubles via int regs as well
1398           if (isVarArg) {
1399             BuildMI(BB, PPC::STFD, 3).addReg(ArgReg).addSImm(ArgOffset)
1400             .addReg(PPC::R1);
1401             
1402             if (GPR_remaining > 0) {
1403               BuildMI(BB, PPC::LD, 2, GPR[GPR_idx]).addSImm(ArgOffset)
1404               .addReg(PPC::R1);
1405               CallMI->addRegOperand(GPR[GPR_idx], MachineOperand::Use);
1406             }
1407           }
1408         } else {
1409           BuildMI(BB, PPC::STFD, 3).addReg(ArgReg).addSImm(ArgOffset)
1410           .addReg(PPC::R1);
1411         }
1412         // Doubles use 8 bytes
1413         ArgOffset += 4;
1414         break;
1415         
1416       default: assert(0 && "Unknown class!");
1417       }
1418       ArgOffset += 4;
1419       GPR_remaining--;
1420       GPR_idx++;
1421     }
1422   } else {
1423     BuildMI(BB, PPC::ADJCALLSTACKDOWN, 1).addImm(0);
1424   }
1425
1426   BuildMI(BB, PPC::IMPLICIT_DEF, 0, PPC::LR);
1427   BB->push_back(CallMI);
1428   BuildMI(BB, PPC::NOP, 0);
1429   
1430   // These functions are automatically eliminated by the prolog/epilog pass
1431   BuildMI(BB, PPC::ADJCALLSTACKUP, 1).addImm(NumBytes);
1432
1433   // If there is a return value, scavenge the result from the location the call
1434   // leaves it in...
1435   //
1436   if (Ret.Ty != Type::VoidTy) {
1437     unsigned DestClass = getClassB(Ret.Ty);
1438     switch (DestClass) {
1439     case cByte:
1440     case cShort:
1441     case cInt:
1442     case cLong:
1443       // Integral results are in r3
1444       BuildMI(BB, PPC::OR, 2, Ret.Reg).addReg(PPC::R3).addReg(PPC::R3);
1445       break;
1446     case cFP32:   // Floating-point return values live in f1
1447     case cFP64:
1448       BuildMI(BB, PPC::FMR, 1, Ret.Reg).addReg(PPC::F1);
1449       break;
1450     default: assert(0 && "Unknown class!");
1451     }
1452   }
1453 }
1454
1455
1456 /// visitCallInst - Push args on stack and do a procedure call instruction.
1457 void ISel::visitCallInst(CallInst &CI) {
1458   MachineInstr *TheCall;
1459   Function *F = CI.getCalledFunction();
1460   if (F) {
1461     // Is it an intrinsic function call?
1462     if (Intrinsic::ID ID = (Intrinsic::ID)F->getIntrinsicID()) {
1463       visitIntrinsicCall(ID, CI);   // Special intrinsics are not handled here
1464       return;
1465     }
1466     // Emit a CALL instruction with PC-relative displacement.
1467     TheCall = BuildMI(PPC::CALLpcrel, 1).addGlobalAddress(F, true);
1468   } else {  // Emit an indirect call through the CTR
1469     unsigned Reg = getReg(CI.getCalledValue());
1470     BuildMI(BB, PPC::MTCTR, 1).addReg(Reg);
1471     TheCall = BuildMI(PPC::CALLindirect, 2).addZImm(20).addZImm(0);
1472   }
1473
1474   std::vector<ValueRecord> Args;
1475   for (unsigned i = 1, e = CI.getNumOperands(); i != e; ++i)
1476     Args.push_back(ValueRecord(CI.getOperand(i)));
1477
1478   unsigned DestReg = CI.getType() != Type::VoidTy ? getReg(CI) : 0;
1479   bool isVarArg = F ? F->getFunctionType()->isVarArg() : true;
1480   doCall(ValueRecord(DestReg, CI.getType()), TheCall, Args, isVarArg);
1481 }         
1482
1483
1484 /// dyncastIsNan - Return the operand of an isnan operation if this is an isnan.
1485 ///
1486 static Value *dyncastIsNan(Value *V) {
1487   if (CallInst *CI = dyn_cast<CallInst>(V))
1488     if (Function *F = CI->getCalledFunction())
1489       if (F->getIntrinsicID() == Intrinsic::isunordered)
1490         return CI->getOperand(1);
1491   return 0;
1492 }
1493
1494 /// isOnlyUsedByUnorderedComparisons - Return true if this value is only used by
1495 /// or's whos operands are all calls to the isnan predicate.
1496 static bool isOnlyUsedByUnorderedComparisons(Value *V) {
1497   assert(dyncastIsNan(V) && "The value isn't an isnan call!");
1498
1499   // Check all uses, which will be or's of isnans if this predicate is true.
1500   for (Value::use_iterator UI = V->use_begin(), E = V->use_end(); UI != E;++UI){
1501     Instruction *I = cast<Instruction>(*UI);
1502     if (I->getOpcode() != Instruction::Or) return false;
1503     if (I->getOperand(0) != V && !dyncastIsNan(I->getOperand(0))) return false;
1504     if (I->getOperand(1) != V && !dyncastIsNan(I->getOperand(1))) return false;
1505   }
1506
1507   return true;
1508 }
1509
1510 /// LowerUnknownIntrinsicFunctionCalls - This performs a prepass over the
1511 /// function, lowering any calls to unknown intrinsic functions into the
1512 /// equivalent LLVM code.
1513 ///
1514 void ISel::LowerUnknownIntrinsicFunctionCalls(Function &F) {
1515   for (Function::iterator BB = F.begin(), E = F.end(); BB != E; ++BB)
1516     for (BasicBlock::iterator I = BB->begin(), E = BB->end(); I != E; )
1517       if (CallInst *CI = dyn_cast<CallInst>(I++))
1518         if (Function *F = CI->getCalledFunction())
1519           switch (F->getIntrinsicID()) {
1520           case Intrinsic::not_intrinsic:
1521           case Intrinsic::vastart:
1522           case Intrinsic::vacopy:
1523           case Intrinsic::vaend:
1524           case Intrinsic::returnaddress:
1525           case Intrinsic::frameaddress:
1526             // FIXME: should lower these ourselves
1527             // case Intrinsic::isunordered:
1528             // case Intrinsic::memcpy: -> doCall().  system memcpy almost
1529             // guaranteed to be faster than anything we generate ourselves
1530             // We directly implement these intrinsics
1531             break;
1532           case Intrinsic::readio: {
1533             // On PPC, memory operations are in-order.  Lower this intrinsic
1534             // into a volatile load.
1535             Instruction *Before = CI->getPrev();
1536             LoadInst * LI = new LoadInst(CI->getOperand(1), "", true, CI);
1537             CI->replaceAllUsesWith(LI);
1538             BB->getInstList().erase(CI);
1539             break;
1540           }
1541           case Intrinsic::writeio: {
1542             // On PPC, memory operations are in-order.  Lower this intrinsic
1543             // into a volatile store.
1544             Instruction *Before = CI->getPrev();
1545             StoreInst *SI = new StoreInst(CI->getOperand(1),
1546                                           CI->getOperand(2), true, CI);
1547             CI->replaceAllUsesWith(SI);
1548             BB->getInstList().erase(CI);
1549             break;
1550           }
1551           default:
1552             // All other intrinsic calls we must lower.
1553             Instruction *Before = CI->getPrev();
1554             TM.getIntrinsicLowering().LowerIntrinsicCall(CI);
1555             if (Before) {        // Move iterator to instruction after call
1556               I = Before; ++I;
1557             } else {
1558               I = BB->begin();
1559             }
1560           }
1561 }
1562
1563 void ISel::visitIntrinsicCall(Intrinsic::ID ID, CallInst &CI) {
1564   unsigned TmpReg1, TmpReg2, TmpReg3;
1565   switch (ID) {
1566   case Intrinsic::vastart:
1567     // Get the address of the first vararg value...
1568     TmpReg1 = getReg(CI);
1569     addFrameReference(BuildMI(BB, PPC::ADDI, 2, TmpReg1), VarArgsFrameIndex, 
1570                       0, false);
1571     return;
1572
1573   case Intrinsic::vacopy:
1574     TmpReg1 = getReg(CI);
1575     TmpReg2 = getReg(CI.getOperand(1));
1576     BuildMI(BB, PPC::OR, 2, TmpReg1).addReg(TmpReg2).addReg(TmpReg2);
1577     return;
1578   case Intrinsic::vaend: return;
1579
1580   case Intrinsic::returnaddress:
1581     TmpReg1 = getReg(CI);
1582     if (cast<Constant>(CI.getOperand(1))->isNullValue()) {
1583       MachineFrameInfo *MFI = F->getFrameInfo();
1584       unsigned NumBytes = MFI->getStackSize();
1585       
1586       BuildMI(BB, PPC::LWZ, 2, TmpReg1).addSImm(NumBytes+8)
1587         .addReg(PPC::R1);
1588     } else {
1589       // Values other than zero are not implemented yet.
1590       BuildMI(BB, PPC::LI, 1, TmpReg1).addSImm(0);
1591     }
1592     return;
1593
1594   case Intrinsic::frameaddress:
1595     TmpReg1 = getReg(CI);
1596     if (cast<Constant>(CI.getOperand(1))->isNullValue()) {
1597       BuildMI(BB, PPC::OR, 2, TmpReg1).addReg(PPC::R1).addReg(PPC::R1);
1598     } else {
1599       // Values other than zero are not implemented yet.
1600       BuildMI(BB, PPC::LI, 1, TmpReg1).addSImm(0);
1601     }
1602     return;
1603     
1604 #if 0
1605     // This may be useful for supporting isunordered
1606   case Intrinsic::isnan:
1607     // If this is only used by 'isunordered' style comparisons, don't emit it.
1608     if (isOnlyUsedByUnorderedComparisons(&CI)) return;
1609     TmpReg1 = getReg(CI.getOperand(1));
1610     emitUCOM(BB, BB->end(), TmpReg1, TmpReg1);
1611     TmpReg2 = makeAnotherReg(Type::IntTy);
1612     BuildMI(BB, PPC::MFCR, TmpReg2);
1613     TmpReg3 = getReg(CI);
1614     BuildMI(BB, PPC::RLWINM, 4, TmpReg3).addReg(TmpReg2).addImm(4).addImm(31).addImm(31);
1615     return;
1616 #endif
1617     
1618   default: assert(0 && "Error: unknown intrinsics should have been lowered!");
1619   }
1620 }
1621
1622 /// visitSimpleBinary - Implement simple binary operators for integral types...
1623 /// OperatorClass is one of: 0 for Add, 1 for Sub, 2 for And, 3 for Or, 4 for
1624 /// Xor.
1625 ///
1626 void ISel::visitSimpleBinary(BinaryOperator &B, unsigned OperatorClass) {
1627   unsigned DestReg = getReg(B);
1628   MachineBasicBlock::iterator MI = BB->end();
1629   Value *Op0 = B.getOperand(0), *Op1 = B.getOperand(1);
1630   unsigned Class = getClassB(B.getType());
1631
1632   emitSimpleBinaryOperation(BB, MI, Op0, Op1, OperatorClass, DestReg);
1633 }
1634
1635 /// emitBinaryFPOperation - This method handles emission of floating point
1636 /// Add (0), Sub (1), Mul (2), and Div (3) operations.
1637 void ISel::emitBinaryFPOperation(MachineBasicBlock *BB,
1638                                  MachineBasicBlock::iterator IP,
1639                                  Value *Op0, Value *Op1,
1640                                  unsigned OperatorClass, unsigned DestReg) {
1641
1642   static const unsigned OpcodeTab[][4] = {
1643     { PPC::FADDS, PPC::FSUBS, PPC::FMULS, PPC::FDIVS },  // Float
1644     { PPC::FADD,  PPC::FSUB,  PPC::FMUL,  PPC::FDIV },   // Double
1645   };
1646
1647   // Special case: R1 = op <const fp>, R2
1648   if (ConstantFP *Op0C = dyn_cast<ConstantFP>(Op0))
1649     if (Op0C->isExactlyValue(-0.0) && OperatorClass == 1) {
1650       // -0.0 - X === -X
1651       unsigned op1Reg = getReg(Op1, BB, IP);
1652       BuildMI(*BB, IP, PPC::FNEG, 1, DestReg).addReg(op1Reg);
1653       return;
1654     }
1655
1656   unsigned Opcode = OpcodeTab[Op0->getType() == Type::DoubleTy][OperatorClass];
1657   unsigned Op0r = getReg(Op0, BB, IP);
1658   unsigned Op1r = getReg(Op1, BB, IP);
1659   BuildMI(*BB, IP, Opcode, 2, DestReg).addReg(Op0r).addReg(Op1r);
1660 }
1661
1662 /// emitSimpleBinaryOperation - Implement simple binary operators for integral
1663 /// types...  OperatorClass is one of: 0 for Add, 1 for Sub, 2 for And, 3 for
1664 /// Or, 4 for Xor.
1665 ///
1666 /// emitSimpleBinaryOperation - Common code shared between visitSimpleBinary
1667 /// and constant expression support.
1668 ///
1669 void ISel::emitSimpleBinaryOperation(MachineBasicBlock *MBB,
1670                                      MachineBasicBlock::iterator IP,
1671                                      Value *Op0, Value *Op1,
1672                                      unsigned OperatorClass, unsigned DestReg) {
1673   unsigned Class = getClassB(Op0->getType());
1674
1675   // Arithmetic and Bitwise operators
1676   static const unsigned OpcodeTab[] = {
1677     PPC::ADD, PPC::SUB, PPC::AND, PPC::OR, PPC::XOR
1678   };
1679   static const unsigned ImmOpcodeTab[] = {
1680     PPC::ADDI, PPC::SUBI, PPC::ANDIo, PPC::ORI, PPC::XORI
1681   };
1682   static const unsigned RImmOpcodeTab[] = {
1683     PPC::ADDI, PPC::SUBFIC, PPC::ANDIo, PPC::ORI, PPC::XORI
1684   };
1685
1686   if (Class == cFP32 || Class == cFP64) {
1687     assert(OperatorClass < 2 && "No logical ops for FP!");
1688     emitBinaryFPOperation(MBB, IP, Op0, Op1, OperatorClass, DestReg);
1689     return;
1690   }
1691
1692   if (Op0->getType() == Type::BoolTy) {
1693     if (OperatorClass == 3)
1694       // If this is an or of two isnan's, emit an FP comparison directly instead
1695       // of or'ing two isnan's together.
1696       if (Value *LHS = dyncastIsNan(Op0))
1697         if (Value *RHS = dyncastIsNan(Op1)) {
1698           unsigned Op0Reg = getReg(RHS, MBB, IP), Op1Reg = getReg(LHS, MBB, IP);
1699           unsigned TmpReg = makeAnotherReg(Type::IntTy);
1700           emitUCOM(MBB, IP, Op0Reg, Op1Reg);
1701           BuildMI(*MBB, IP, PPC::MFCR, TmpReg);
1702           BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(TmpReg).addImm(4)
1703             .addImm(31).addImm(31);
1704           return;
1705         }
1706   }
1707
1708   // Special case: op <const int>, Reg
1709   if (ConstantInt *CI = dyn_cast<ConstantInt>(Op0)) {
1710     // sub 0, X -> subfic
1711     if (OperatorClass == 1 && canUseAsImmediateForOpcode(CI, 0)) {
1712       unsigned Op1r = getReg(Op1, MBB, IP);
1713       int imm = CI->getRawValue() & 0xFFFF;
1714       BuildMI(*MBB, IP, PPC::SUBFIC, 2, DestReg).addReg(Op1r).addSImm(imm);
1715       return;
1716     }
1717     
1718     // If it is easy to do, swap the operands and emit an immediate op
1719     if (Class != cLong && OperatorClass != 1 && 
1720         canUseAsImmediateForOpcode(CI, OperatorClass)) {
1721       unsigned Op1r = getReg(Op1, MBB, IP);
1722       int imm = CI->getRawValue() & 0xFFFF;
1723     
1724       if (OperatorClass < 2)
1725         BuildMI(*MBB, IP, RImmOpcodeTab[OperatorClass], 2, DestReg).addReg(Op1r)
1726           .addSImm(imm);
1727       else
1728         BuildMI(*MBB, IP, RImmOpcodeTab[OperatorClass], 2, DestReg).addReg(Op1r)
1729           .addZImm(imm);
1730       return;
1731     }
1732   }
1733
1734   // Special case: op Reg, <const int>
1735   if (ConstantInt *Op1C = dyn_cast<ConstantInt>(Op1)) {
1736     unsigned Op0r = getReg(Op0, MBB, IP);
1737
1738     // xor X, -1 -> not X
1739     if (OperatorClass == 4 && Op1C->isAllOnesValue()) {
1740       BuildMI(*MBB, IP, PPC::NOR, 2, DestReg).addReg(Op0r).addReg(Op0r);
1741       return;
1742     }
1743     
1744     if (canUseAsImmediateForOpcode(Op1C, OperatorClass)) {
1745       int immediate = Op1C->getRawValue() & 0xFFFF;
1746       
1747       if (OperatorClass < 2)
1748         BuildMI(*MBB, IP, ImmOpcodeTab[OperatorClass], 2,DestReg).addReg(Op0r)
1749           .addSImm(immediate);
1750       else
1751         BuildMI(*MBB, IP, ImmOpcodeTab[OperatorClass], 2,DestReg).addReg(Op0r)
1752           .addZImm(immediate);
1753     } else {
1754       unsigned Op1r = getReg(Op1, MBB, IP);
1755       BuildMI(*MBB, IP, OpcodeTab[OperatorClass], 2, DestReg).addReg(Op0r)
1756         .addReg(Op1r);
1757     }
1758     return;
1759   }
1760   
1761   // We couldn't generate an immediate variant of the op, load both halves into
1762   // registers and emit the appropriate opcode.
1763   unsigned Op0r = getReg(Op0, MBB, IP);
1764   unsigned Op1r = getReg(Op1, MBB, IP);
1765   unsigned Opcode = OpcodeTab[OperatorClass];
1766   BuildMI(*MBB, IP, Opcode, 2, DestReg).addReg(Op0r).addReg(Op1r);
1767 }
1768
1769 // ExactLog2 - This function solves for (Val == 1 << (N-1)) and returns N.  It
1770 // returns zero when the input is not exactly a power of two.
1771 static unsigned ExactLog2(unsigned Val) {
1772   if (Val == 0 || (Val & (Val-1))) return 0;
1773   unsigned Count = 0;
1774   while (Val != 1) {
1775     Val >>= 1;
1776     ++Count;
1777   }
1778   return Count;
1779 }
1780
1781 /// doMultiply - Emit appropriate instructions to multiply together the
1782 /// Values Op0 and Op1, and put the result in DestReg.
1783 ///
1784 void ISel::doMultiply(MachineBasicBlock *MBB,
1785                       MachineBasicBlock::iterator IP,
1786                       unsigned DestReg, Value *Op0, Value *Op1) {
1787   unsigned Class0 = getClass(Op0->getType());
1788   unsigned Class1 = getClass(Op1->getType());
1789   
1790   unsigned Op0r = getReg(Op0, MBB, IP);
1791   unsigned Op1r = getReg(Op1, MBB, IP);
1792   
1793   // 64 x 64 -> 64
1794   if (Class0 == cLong && Class1 == cLong) {
1795     BuildMI(*MBB, IP, PPC::MULLD, 2, DestReg).addReg(Op0r).addReg(Op1r);
1796     return;
1797   }
1798   
1799   // 64 x 32 or less, promote 32 to 64 and do a 64 x 64
1800   if (Class0 == cLong && Class1 <= cInt) {
1801     // FIXME: CLEAR or SIGN EXTEND Op1
1802     BuildMI(*MBB, IP, PPC::MULLD, 2, DestReg).addReg(Op0r).addReg(Op1r);
1803     return;
1804   }
1805   
1806   // 32 x 32 -> 32
1807   if (Class0 <= cInt && Class1 <= cInt) {
1808     BuildMI(*MBB, IP, PPC::MULLW, 2, DestReg).addReg(Op0r).addReg(Op1r);
1809     return;
1810   }
1811   
1812   assert(0 && "doMultiply cannot operate on unknown type!");
1813 }
1814
1815 /// doMultiplyConst - This method will multiply the value in Op0 by the
1816 /// value of the ContantInt *CI
1817 void ISel::doMultiplyConst(MachineBasicBlock *MBB,
1818                            MachineBasicBlock::iterator IP,
1819                            unsigned DestReg, Value *Op0, ConstantInt *CI) {
1820   unsigned Class = getClass(Op0->getType());
1821
1822   // Mul op0, 0 ==> 0
1823   if (CI->isNullValue()) {
1824     BuildMI(*MBB, IP, PPC::LI, 1, DestReg).addSImm(0);
1825     return;
1826   }
1827   
1828   // Mul op0, 1 ==> op0
1829   if (CI->equalsInt(1)) {
1830     unsigned Op0r = getReg(Op0, MBB, IP);
1831     BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(Op0r).addReg(Op0r);
1832     return;
1833   }
1834
1835   // If the element size is exactly a power of 2, use a shift to get it.
1836   if (unsigned Shift = ExactLog2(CI->getRawValue())) {
1837     ConstantUInt *ShiftCI = ConstantUInt::get(Type::UByteTy, Shift);
1838     emitShiftOperation(MBB, IP, Op0, ShiftCI, true, Op0->getType(), DestReg);
1839     return;
1840   }
1841   
1842   // If 32 bits or less and immediate is in right range, emit mul by immediate
1843   if (Class == cByte || Class == cShort || Class == cInt) {
1844     if (canUseAsImmediateForOpcode(CI, 0)) {
1845       unsigned Op0r = getReg(Op0, MBB, IP);
1846       unsigned imm = CI->getRawValue() & 0xFFFF;
1847       BuildMI(*MBB, IP, PPC::MULLI, 2, DestReg).addReg(Op0r).addSImm(imm);
1848       return;
1849     }
1850   }
1851   
1852   doMultiply(MBB, IP, DestReg, Op0, CI);
1853 }
1854
1855 void ISel::visitMul(BinaryOperator &I) {
1856   unsigned ResultReg = getReg(I);
1857
1858   Value *Op0 = I.getOperand(0);
1859   Value *Op1 = I.getOperand(1);
1860
1861   MachineBasicBlock::iterator IP = BB->end();
1862   emitMultiply(BB, IP, Op0, Op1, ResultReg);
1863 }
1864
1865 void ISel::emitMultiply(MachineBasicBlock *MBB, MachineBasicBlock::iterator IP,
1866                         Value *Op0, Value *Op1, unsigned DestReg) {
1867   TypeClass Class = getClass(Op0->getType());
1868
1869   switch (Class) {
1870   case cByte:
1871   case cShort:
1872   case cInt:
1873   case cLong:
1874     if (ConstantInt *CI = dyn_cast<ConstantInt>(Op1)) {
1875       doMultiplyConst(MBB, IP, DestReg, Op0, CI);
1876     } else {
1877       doMultiply(MBB, IP, DestReg, Op0, Op1);
1878     }
1879     return;
1880   case cFP32:
1881   case cFP64:
1882     emitBinaryFPOperation(MBB, IP, Op0, Op1, 2, DestReg);
1883     return;
1884     break;
1885   }
1886 }
1887
1888
1889 /// visitDivRem - Handle division and remainder instructions... these
1890 /// instruction both require the same instructions to be generated, they just
1891 /// select the result from a different register.  Note that both of these
1892 /// instructions work differently for signed and unsigned operands.
1893 ///
1894 void ISel::visitDivRem(BinaryOperator &I) {
1895   unsigned ResultReg = getReg(I);
1896   Value *Op0 = I.getOperand(0), *Op1 = I.getOperand(1);
1897
1898   MachineBasicBlock::iterator IP = BB->end();
1899   emitDivRemOperation(BB, IP, Op0, Op1, I.getOpcode() == Instruction::Div,
1900                       ResultReg);
1901 }
1902
1903 void ISel::emitDivRemOperation(MachineBasicBlock *BB,
1904                                MachineBasicBlock::iterator IP,
1905                                Value *Op0, Value *Op1, bool isDiv,
1906                                unsigned ResultReg) {
1907   const Type *Ty = Op0->getType();
1908   unsigned Class = getClass(Ty);
1909   switch (Class) {
1910   case cFP32:
1911     if (isDiv) {
1912       // Floating point divide...
1913       emitBinaryFPOperation(BB, IP, Op0, Op1, 3, ResultReg);
1914       return;
1915     } else {
1916       // Floating point remainder via fmodf(float x, float y);
1917       unsigned Op0Reg = getReg(Op0, BB, IP);
1918       unsigned Op1Reg = getReg(Op1, BB, IP);
1919       MachineInstr *TheCall =
1920         BuildMI(PPC::CALLpcrel, 1).addGlobalAddress(fmodfFn, true);
1921       std::vector<ValueRecord> Args;
1922       Args.push_back(ValueRecord(Op0Reg, Type::FloatTy));
1923       Args.push_back(ValueRecord(Op1Reg, Type::FloatTy));
1924       doCall(ValueRecord(ResultReg, Type::FloatTy), TheCall, Args, false);
1925     }
1926     return;
1927   case cFP64:
1928     if (isDiv) {
1929       // Floating point divide...
1930       emitBinaryFPOperation(BB, IP, Op0, Op1, 3, ResultReg);
1931       return;
1932     } else {               
1933       // Floating point remainder via fmod(double x, double y);
1934       unsigned Op0Reg = getReg(Op0, BB, IP);
1935       unsigned Op1Reg = getReg(Op1, BB, IP);
1936       MachineInstr *TheCall =
1937         BuildMI(PPC::CALLpcrel, 1).addGlobalAddress(fmodFn, true);
1938       std::vector<ValueRecord> Args;
1939       Args.push_back(ValueRecord(Op0Reg, Type::DoubleTy));
1940       Args.push_back(ValueRecord(Op1Reg, Type::DoubleTy));
1941       doCall(ValueRecord(ResultReg, Type::DoubleTy), TheCall, Args, false);
1942     }
1943     return;
1944   case cLong: {
1945     static Function* const Funcs[] =
1946       { __moddi3Fn, __divdi3Fn, __umoddi3Fn, __udivdi3Fn };
1947     unsigned Op0Reg = getReg(Op0, BB, IP);
1948     unsigned Op1Reg = getReg(Op1, BB, IP);
1949     unsigned NameIdx = Ty->isUnsigned()*2 + isDiv;
1950     MachineInstr *TheCall =
1951       BuildMI(PPC::CALLpcrel, 1).addGlobalAddress(Funcs[NameIdx], true);
1952
1953     std::vector<ValueRecord> Args;
1954     Args.push_back(ValueRecord(Op0Reg, Type::LongTy));
1955     Args.push_back(ValueRecord(Op1Reg, Type::LongTy));
1956     doCall(ValueRecord(ResultReg, Type::LongTy), TheCall, Args, false);
1957     return;
1958   }
1959   case cByte: case cShort: case cInt:
1960     break;          // Small integrals, handled below...
1961   default: assert(0 && "Unknown class!");
1962   }
1963
1964   // Special case signed division by power of 2.
1965   if (isDiv)
1966     if (ConstantSInt *CI = dyn_cast<ConstantSInt>(Op1)) {
1967       assert(Class != cLong && "This doesn't handle 64-bit divides!");
1968       int V = CI->getValue();
1969
1970       if (V == 1) {       // X /s 1 => X
1971         unsigned Op0Reg = getReg(Op0, BB, IP);
1972         BuildMI(*BB, IP, PPC::OR, 2, ResultReg).addReg(Op0Reg).addReg(Op0Reg);
1973         return;
1974       }
1975
1976       if (V == -1) {      // X /s -1 => -X
1977         unsigned Op0Reg = getReg(Op0, BB, IP);
1978         BuildMI(*BB, IP, PPC::NEG, 1, ResultReg).addReg(Op0Reg);
1979         return;
1980       }
1981
1982       unsigned log2V = ExactLog2(V);
1983       if (log2V != 0 && Ty->isSigned()) {
1984         unsigned Op0Reg = getReg(Op0, BB, IP);
1985         unsigned TmpReg = makeAnotherReg(Op0->getType());
1986         
1987         BuildMI(*BB, IP, PPC::SRAWI, 2, TmpReg).addReg(Op0Reg).addImm(log2V);
1988         BuildMI(*BB, IP, PPC::ADDZE, 1, ResultReg).addReg(TmpReg);
1989         return;
1990       }
1991     }
1992
1993   unsigned Op0Reg = getReg(Op0, BB, IP);
1994   unsigned Op1Reg = getReg(Op1, BB, IP);
1995   unsigned Opcode = Ty->isSigned() ? PPC::DIVW : PPC::DIVWU;
1996   
1997   if (isDiv) {
1998     BuildMI(*BB, IP, Opcode, 2, ResultReg).addReg(Op0Reg).addReg(Op1Reg);
1999   } else { // Remainder
2000     unsigned TmpReg1 = makeAnotherReg(Op0->getType());
2001     unsigned TmpReg2 = makeAnotherReg(Op0->getType());
2002     
2003     BuildMI(*BB, IP, Opcode, 2, TmpReg1).addReg(Op0Reg).addReg(Op1Reg);
2004     BuildMI(*BB, IP, PPC::MULLW, 2, TmpReg2).addReg(TmpReg1).addReg(Op1Reg);
2005     BuildMI(*BB, IP, PPC::SUBF, 2, ResultReg).addReg(TmpReg2).addReg(Op0Reg);
2006   }
2007 }
2008
2009
2010 /// Shift instructions: 'shl', 'sar', 'shr' - Some special cases here
2011 /// for constant immediate shift values, and for constant immediate
2012 /// shift values equal to 1. Even the general case is sort of special,
2013 /// because the shift amount has to be in CL, not just any old register.
2014 ///
2015 void ISel::visitShiftInst(ShiftInst &I) {
2016   MachineBasicBlock::iterator IP = BB->end();
2017   emitShiftOperation(BB, IP, I.getOperand(0), I.getOperand(1),
2018                      I.getOpcode() == Instruction::Shl, I.getType(),
2019                      getReg(I));
2020 }
2021
2022 /// emitShiftOperation - Common code shared between visitShiftInst and
2023 /// constant expression support.
2024 ///
2025 void ISel::emitShiftOperation(MachineBasicBlock *MBB,
2026                               MachineBasicBlock::iterator IP,
2027                               Value *Op, Value *ShiftAmount, bool isLeftShift,
2028                               const Type *ResultTy, unsigned DestReg) {
2029   unsigned SrcReg = getReg (Op, MBB, IP);
2030   bool isSigned = ResultTy->isSigned ();
2031   unsigned Class = getClass (ResultTy);
2032   
2033   // Longs, as usual, are handled specially...
2034   if (Class == cLong) {
2035     // If we have a constant shift, we can generate much more efficient code
2036     // than otherwise...
2037     //
2038     if (ConstantUInt *CUI = dyn_cast<ConstantUInt>(ShiftAmount)) {
2039       unsigned Amount = CUI->getValue();
2040       assert(Amount < 64 && "Invalid immediate shift amount!");
2041       if (isLeftShift) {
2042         BuildMI(*MBB, IP, PPC::RLDICR, 3, DestReg).addReg(SrcReg).addImm(Amount)
2043           .addImm(63-Amount);
2044       } else {
2045         if (isSigned) {
2046           BuildMI(*MBB, IP, PPC::SRADI, 2, DestReg).addReg(SrcReg)
2047             .addImm(Amount);
2048         } else {
2049           BuildMI(*MBB, IP, PPC::RLDICL, 3, DestReg).addReg(SrcReg)
2050             .addImm(64-Amount).addImm(Amount);
2051         }
2052       }
2053     } else {
2054       unsigned ShiftReg = getReg (ShiftAmount, MBB, IP);
2055
2056       if (isLeftShift) {
2057         BuildMI(*MBB, IP, PPC::SLD, 2, DestReg).addReg(SrcReg).addReg(ShiftReg);
2058       } else {
2059         unsigned Opcode = (isSigned) ? PPC::SRAD : PPC::SRD;
2060         BuildMI(*MBB, IP, Opcode, DestReg).addReg(SrcReg).addReg(ShiftReg);
2061       }
2062     }
2063     return;
2064   }
2065
2066   if (ConstantUInt *CUI = dyn_cast<ConstantUInt>(ShiftAmount)) {
2067     // The shift amount is constant, guaranteed to be a ubyte. Get its value.
2068     assert(CUI->getType() == Type::UByteTy && "Shift amount not a ubyte?");
2069     unsigned Amount = CUI->getValue();
2070
2071     if (isLeftShift) {
2072       BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(SrcReg)
2073         .addImm(Amount).addImm(0).addImm(31-Amount);
2074     } else {
2075       if (isSigned) {
2076         BuildMI(*MBB, IP, PPC::SRAWI,2,DestReg).addReg(SrcReg).addImm(Amount);
2077       } else {
2078         BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(SrcReg)
2079           .addImm(32-Amount).addImm(Amount).addImm(31);
2080       }
2081     }
2082   } else {                  // The shift amount is non-constant.
2083     unsigned ShiftAmountReg = getReg(ShiftAmount, MBB, IP);
2084
2085     if (isLeftShift) {
2086       BuildMI(*MBB, IP, PPC::SLW, 2, DestReg).addReg(SrcReg)
2087         .addReg(ShiftAmountReg);
2088     } else {
2089       BuildMI(*MBB, IP, isSigned ? PPC::SRAW : PPC::SRW, 2, DestReg)
2090         .addReg(SrcReg).addReg(ShiftAmountReg);
2091     }
2092   }
2093 }
2094
2095
2096 /// visitLoadInst - Implement LLVM load instructions.  Pretty straightforward
2097 /// mapping of LLVM classes to PPC load instructions, with the exception of
2098 /// signed byte loads, which need a sign extension following them.
2099 ///
2100 void ISel::visitLoadInst(LoadInst &I) {
2101   // Immediate opcodes, for reg+imm addressing
2102   static const unsigned ImmOpcodes[] = { 
2103     PPC::LBZ, PPC::LHZ, PPC::LWZ, 
2104     PPC::LFS, PPC::LFD, PPC::LWZ
2105   };
2106   // Indexed opcodes, for reg+reg addressing
2107   static const unsigned IdxOpcodes[] = {
2108     PPC::LBZX, PPC::LHZX, PPC::LWZX,
2109     PPC::LFSX, PPC::LFDX, PPC::LWZX
2110   };
2111
2112   unsigned Class     = getClassB(I.getType());
2113   unsigned ImmOpcode = ImmOpcodes[Class];
2114   unsigned IdxOpcode = IdxOpcodes[Class];
2115   unsigned DestReg   = getReg(I);
2116   Value *SourceAddr  = I.getOperand(0);
2117   
2118   if (Class == cShort && I.getType()->isSigned()) ImmOpcode = PPC::LHA;
2119   if (Class == cShort && I.getType()->isSigned()) IdxOpcode = PPC::LHAX;
2120
2121   if (AllocaInst *AI = dyn_castFixedAlloca(SourceAddr)) {
2122     unsigned FI = getFixedSizedAllocaFI(AI);
2123     if (Class == cByte && I.getType()->isSigned()) {
2124       unsigned TmpReg = makeAnotherReg(I.getType());
2125       addFrameReference(BuildMI(BB, ImmOpcode, 2, TmpReg), FI);
2126       BuildMI(BB, PPC::EXTSB, 1, DestReg).addReg(TmpReg);
2127     } else {
2128       addFrameReference(BuildMI(BB, ImmOpcode, 2, DestReg), FI);
2129     }
2130     return;
2131   }
2132   
2133   // If this load is the only use of the GEP instruction that is its address,
2134   // then we can fold the GEP directly into the load instruction.
2135   // emitGEPOperation with a second to last arg of 'true' will place the
2136   // base register for the GEP into baseReg, and the constant offset from that
2137   // into offset.  If the offset fits in 16 bits, we can emit a reg+imm store
2138   // otherwise, we copy the offset into another reg, and use reg+reg addressing.
2139   if (GetElementPtrInst *GEPI = canFoldGEPIntoLoadOrStore(SourceAddr)) {
2140     unsigned baseReg = getReg(GEPI);
2141     unsigned pendingAdd;
2142     ConstantSInt *offset;
2143     
2144     emitGEPOperation(BB, BB->end(), GEPI->getOperand(0), GEPI->op_begin()+1, 
2145                      GEPI->op_end(), baseReg, true, &offset, &pendingAdd);
2146
2147     if (pendingAdd == 0 && Class != cLong && 
2148         canUseAsImmediateForOpcode(offset, 0)) {
2149       if (Class == cByte && I.getType()->isSigned()) {
2150         unsigned TmpReg = makeAnotherReg(I.getType());
2151         BuildMI(BB, ImmOpcode, 2, TmpReg).addSImm(offset->getValue())
2152           .addReg(baseReg);
2153         BuildMI(BB, PPC::EXTSB, 1, DestReg).addReg(TmpReg);
2154       } else {
2155         BuildMI(BB, ImmOpcode, 2, DestReg).addSImm(offset->getValue())
2156           .addReg(baseReg);
2157       }
2158       return;
2159     }
2160     
2161     unsigned indexReg = (pendingAdd != 0) ? pendingAdd : getReg(offset);
2162
2163     if (Class == cByte && I.getType()->isSigned()) {
2164       unsigned TmpReg = makeAnotherReg(I.getType());
2165       BuildMI(BB, IdxOpcode, 2, TmpReg).addReg(indexReg).addReg(baseReg);
2166       BuildMI(BB, PPC::EXTSB, 1, DestReg).addReg(TmpReg);
2167     } else {
2168       BuildMI(BB, IdxOpcode, 2, DestReg).addReg(indexReg).addReg(baseReg);
2169     }
2170     return;
2171   }
2172   
2173   // The fallback case, where the load was from a source that could not be
2174   // folded into the load instruction. 
2175   unsigned SrcAddrReg = getReg(SourceAddr);
2176     
2177   if (Class == cByte && I.getType()->isSigned()) {
2178     unsigned TmpReg = makeAnotherReg(I.getType());
2179     BuildMI(BB, ImmOpcode, 2, TmpReg).addSImm(0).addReg(SrcAddrReg);
2180     BuildMI(BB, PPC::EXTSB, 1, DestReg).addReg(TmpReg);
2181   } else {
2182     BuildMI(BB, ImmOpcode, 2, DestReg).addSImm(0).addReg(SrcAddrReg);
2183   }
2184 }
2185
2186 /// visitStoreInst - Implement LLVM store instructions
2187 ///
2188 void ISel::visitStoreInst(StoreInst &I) {
2189   // Immediate opcodes, for reg+imm addressing
2190   static const unsigned ImmOpcodes[] = {
2191     PPC::STB, PPC::STH, PPC::STW, 
2192     PPC::STFS, PPC::STFD, PPC::STW
2193   };
2194   // Indexed opcodes, for reg+reg addressing
2195   static const unsigned IdxOpcodes[] = {
2196     PPC::STBX, PPC::STHX, PPC::STWX, 
2197     PPC::STFSX, PPC::STFDX, PPC::STWX
2198   };
2199   
2200   Value *SourceAddr  = I.getOperand(1);
2201   const Type *ValTy  = I.getOperand(0)->getType();
2202   unsigned Class     = getClassB(ValTy);
2203   unsigned ImmOpcode = ImmOpcodes[Class];
2204   unsigned IdxOpcode = IdxOpcodes[Class];
2205   unsigned ValReg    = getReg(I.getOperand(0));
2206
2207   // If this store is the only use of the GEP instruction that is its address,
2208   // then we can fold the GEP directly into the store instruction.
2209   // emitGEPOperation with a second to last arg of 'true' will place the
2210   // base register for the GEP into baseReg, and the constant offset from that
2211   // into offset.  If the offset fits in 16 bits, we can emit a reg+imm store
2212   // otherwise, we copy the offset into another reg, and use reg+reg addressing.
2213   if (GetElementPtrInst *GEPI = canFoldGEPIntoLoadOrStore(SourceAddr)) {
2214     unsigned baseReg = getReg(GEPI);
2215     unsigned pendingAdd;
2216     ConstantSInt *offset;
2217     
2218     emitGEPOperation(BB, BB->end(), GEPI->getOperand(0), GEPI->op_begin()+1, 
2219                      GEPI->op_end(), baseReg, true, &offset, &pendingAdd);
2220
2221     if (0 == pendingAdd && Class != cLong && 
2222         canUseAsImmediateForOpcode(offset, 0)) {
2223       BuildMI(BB, ImmOpcode, 3).addReg(ValReg).addSImm(offset->getValue())
2224         .addReg(baseReg);
2225       return;
2226     }
2227     
2228     unsigned indexReg = (pendingAdd != 0) ? pendingAdd : getReg(offset);
2229     BuildMI(BB, IdxOpcode, 3).addReg(ValReg).addReg(indexReg).addReg(baseReg);
2230     return;
2231   }
2232   
2233   // If the store address wasn't the only use of a GEP, we fall back to the
2234   // standard path: store the ValReg at the value in AddressReg.
2235   unsigned AddressReg  = getReg(I.getOperand(1));
2236   BuildMI(BB, ImmOpcode, 3).addReg(ValReg).addSImm(0).addReg(AddressReg);
2237 }
2238
2239
2240 /// visitCastInst - Here we have various kinds of copying with or without sign
2241 /// extension going on.
2242 ///
2243 void ISel::visitCastInst(CastInst &CI) {
2244   Value *Op = CI.getOperand(0);
2245
2246   unsigned SrcClass = getClassB(Op->getType());
2247   unsigned DestClass = getClassB(CI.getType());
2248
2249   // If this is a cast from a 32-bit integer to a Long type, and the only uses
2250   // of the case are GEP instructions, then the cast does not need to be
2251   // generated explicitly, it will be folded into the GEP.
2252   if (DestClass == cLong && SrcClass == cInt) {
2253     bool AllUsesAreGEPs = true;
2254     for (Value::use_iterator I = CI.use_begin(), E = CI.use_end(); I != E; ++I)
2255       if (!isa<GetElementPtrInst>(*I)) {
2256         AllUsesAreGEPs = false;
2257         break;
2258       }        
2259
2260     // No need to codegen this cast if all users are getelementptr instrs...
2261     if (AllUsesAreGEPs) return;
2262   }
2263
2264   unsigned DestReg = getReg(CI);
2265   MachineBasicBlock::iterator MI = BB->end();
2266   emitCastOperation(BB, MI, Op, CI.getType(), DestReg);
2267 }
2268
2269 /// emitCastOperation - Common code shared between visitCastInst and constant
2270 /// expression cast support.
2271 ///
2272 void ISel::emitCastOperation(MachineBasicBlock *MBB,
2273                              MachineBasicBlock::iterator IP,
2274                              Value *Src, const Type *DestTy,
2275                              unsigned DestReg) {
2276   const Type *SrcTy = Src->getType();
2277   unsigned SrcClass = getClassB(SrcTy);
2278   unsigned DestClass = getClassB(DestTy);
2279   unsigned SrcReg = getReg(Src, MBB, IP);
2280
2281   // Implement casts to bool by using compare on the operand followed by set if
2282   // not zero on the result.
2283   if (DestTy == Type::BoolTy) {
2284     switch (SrcClass) {
2285     case cByte:
2286     case cShort:
2287     case cInt:
2288     case cLong: {
2289       unsigned TmpReg = makeAnotherReg(Type::IntTy);
2290       BuildMI(*MBB, IP, PPC::ADDIC, 2, TmpReg).addReg(SrcReg).addSImm(-1);
2291       BuildMI(*MBB, IP, PPC::SUBFE, 2, DestReg).addReg(TmpReg).addReg(SrcReg);
2292       break;
2293     }
2294     case cFP32:
2295     case cFP64:
2296       // FSEL perhaps?
2297       std::cerr << "ERROR: Cast fp-to-bool not implemented!\n";
2298       abort();
2299     }
2300     return;
2301   }
2302
2303   // Handle cast of Float -> Double
2304   if (SrcClass == cFP32 && DestClass == cFP64) {
2305     BuildMI(*MBB, IP, PPC::FMR, 1, DestReg).addReg(SrcReg);
2306     return;
2307   }
2308   
2309   // Handle cast of Double -> Float
2310   if (SrcClass == cFP64 && DestClass == cFP32) {
2311     BuildMI(*MBB, IP, PPC::FRSP, 1, DestReg).addReg(SrcReg);
2312     return;
2313   }
2314   
2315   // Handle casts from integer to floating point now...
2316   if (DestClass == cFP32 || DestClass == cFP64) {
2317
2318     // Spill the integer to memory and reload it from there.
2319     unsigned TmpReg = makeAnotherReg(Type::DoubleTy);
2320     int ValueFrameIdx =
2321       F->getFrameInfo()->CreateStackObject(Type::DoubleTy, TM.getTargetData());
2322
2323     if (SrcClass == cLong) {
2324       if (SrcTy->isSigned()) {
2325         addFrameReference(BuildMI(*MBB, IP, PPC::STD, 3).addReg(SrcReg), 
2326                           ValueFrameIdx);
2327         addFrameReference(BuildMI(*MBB, IP, PPC::LFD, 2, TmpReg), 
2328                           ValueFrameIdx);
2329         BuildMI(*MBB, IP, PPC::FCFID, 1, DestReg).addReg(TmpReg);
2330       } else {
2331         unsigned Scale = getReg(ConstantFP::get(Type::DoubleTy, 0x1p32));
2332         unsigned TmpHi = makeAnotherReg(Type::IntTy);
2333         unsigned TmpLo = makeAnotherReg(Type::IntTy);
2334         unsigned FPLow = makeAnotherReg(Type::DoubleTy);
2335         unsigned FPTmpHi = makeAnotherReg(Type::DoubleTy);
2336         unsigned FPTmpLo = makeAnotherReg(Type::DoubleTy);
2337         int OtherFrameIdx = F->getFrameInfo()->CreateStackObject(Type::DoubleTy, 
2338                                                             TM.getTargetData());
2339         BuildMI(*MBB, IP, PPC::RLDICL, 3, TmpHi).addReg(SrcReg).addImm(32)
2340           .addImm(32);
2341         BuildMI(*MBB, IP, PPC::RLDICL, 3, TmpLo).addReg(SrcReg).addImm(0)
2342           .addImm(32);
2343         addFrameReference(BuildMI(*MBB, IP, PPC::STD, 3).addReg(TmpHi), 
2344                           ValueFrameIdx);
2345         addFrameReference(BuildMI(*MBB, IP, PPC::STD, 3).addReg(TmpLo), 
2346                           OtherFrameIdx);
2347         addFrameReference(BuildMI(*MBB, IP, PPC::LFD, 2, TmpReg), 
2348                           ValueFrameIdx);
2349         addFrameReference(BuildMI(*MBB, IP, PPC::LFD, 2, FPLow), 
2350                           OtherFrameIdx);
2351         BuildMI(*MBB, IP, PPC::FCFID, 1, FPTmpHi).addReg(TmpReg);
2352         BuildMI(*MBB, IP, PPC::FCFID, 1, FPTmpLo).addReg(FPLow);
2353         BuildMI(*MBB, IP, PPC::FMADD, 3, DestReg).addReg(Scale).addReg(FPTmpHi)
2354           .addReg(FPTmpLo);
2355       }
2356       return;
2357     }
2358     
2359     // FIXME: really want a promote64
2360     unsigned IntTmp = makeAnotherReg(Type::IntTy);
2361
2362     if (SrcTy->isSigned())
2363       BuildMI(*MBB, IP, PPC::EXTSW, 1, IntTmp).addReg(SrcReg);
2364     else
2365       BuildMI(*MBB, IP, PPC::RLDICL, 3, IntTmp).addReg(SrcReg).addImm(0)
2366         .addImm(32);
2367     addFrameReference(BuildMI(*MBB, IP, PPC::STD, 3).addReg(IntTmp), 
2368                       ValueFrameIdx);
2369     addFrameReference(BuildMI(*MBB, IP, PPC::LFD, 2, TmpReg), 
2370                       ValueFrameIdx);
2371     BuildMI(*MBB, IP, PPC::FCFID, 1, DestReg).addReg(TmpReg);
2372     return;
2373   }
2374
2375   // Handle casts from floating point to integer now...
2376   if (SrcClass == cFP32 || SrcClass == cFP64) {
2377     static Function* const Funcs[] =
2378       { __fixsfdiFn, __fixdfdiFn, __fixunssfdiFn, __fixunsdfdiFn };
2379     // emit library call
2380     if (DestClass == cLong) {
2381       bool isDouble = SrcClass == cFP64;
2382       unsigned nameIndex = 2 * DestTy->isSigned() + isDouble;
2383       std::vector<ValueRecord> Args;
2384       Args.push_back(ValueRecord(SrcReg, SrcTy));
2385       Function *floatFn = Funcs[nameIndex];
2386       MachineInstr *TheCall =
2387         BuildMI(PPC::CALLpcrel, 1).addGlobalAddress(floatFn, true);
2388       doCall(ValueRecord(DestReg, DestTy), TheCall, Args, false);
2389       return;
2390     }
2391
2392     int ValueFrameIdx =
2393       F->getFrameInfo()->CreateStackObject(SrcTy, TM.getTargetData());
2394
2395     if (DestTy->isSigned()) {
2396       unsigned TempReg = makeAnotherReg(Type::DoubleTy);
2397       
2398       // Convert to integer in the FP reg and store it to a stack slot
2399       BuildMI(*BB, IP, PPC::FCTIWZ, 1, TempReg).addReg(SrcReg);
2400       addFrameReference(BuildMI(*BB, IP, PPC::STFD, 3)
2401                           .addReg(TempReg), ValueFrameIdx);
2402
2403       // There is no load signed byte opcode, so we must emit a sign extend for
2404       // that particular size.  Make sure to source the new integer from the 
2405       // correct offset.
2406       if (DestClass == cByte) {
2407         unsigned TempReg2 = makeAnotherReg(DestTy);
2408         addFrameReference(BuildMI(*BB, IP, PPC::LBZ, 2, TempReg2), 
2409                           ValueFrameIdx, 7);
2410         BuildMI(*MBB, IP, PPC::EXTSB, DestReg).addReg(TempReg2);
2411       } else {
2412         int offset = (DestClass == cShort) ? 6 : 4;
2413         unsigned LoadOp = (DestClass == cShort) ? PPC::LHA : PPC::LWZ;
2414         addFrameReference(BuildMI(*BB, IP, LoadOp, 2, DestReg), 
2415                           ValueFrameIdx, offset);
2416       }
2417     } else {
2418       unsigned Zero = getReg(ConstantFP::get(Type::DoubleTy, 0.0f));
2419       double maxInt = (1LL << 32) - 1;
2420       unsigned MaxInt = getReg(ConstantFP::get(Type::DoubleTy, maxInt));
2421       double border = 1LL << 31;
2422       unsigned Border = getReg(ConstantFP::get(Type::DoubleTy, border));
2423       unsigned UseZero = makeAnotherReg(Type::DoubleTy);
2424       unsigned UseMaxInt = makeAnotherReg(Type::DoubleTy);
2425       unsigned UseChoice = makeAnotherReg(Type::DoubleTy);
2426       unsigned TmpReg = makeAnotherReg(Type::DoubleTy);
2427       unsigned TmpReg2 = makeAnotherReg(Type::DoubleTy);
2428       unsigned ConvReg = makeAnotherReg(Type::DoubleTy);
2429       unsigned IntTmp = makeAnotherReg(Type::IntTy);
2430       unsigned XorReg = makeAnotherReg(Type::IntTy);
2431       int FrameIdx = 
2432         F->getFrameInfo()->CreateStackObject(SrcTy, TM.getTargetData());
2433       // Update machine-CFG edges
2434       MachineBasicBlock *XorMBB = new MachineBasicBlock(BB->getBasicBlock());
2435       MachineBasicBlock *PhiMBB = new MachineBasicBlock(BB->getBasicBlock());
2436       MachineBasicBlock *OldMBB = BB;
2437       ilist<MachineBasicBlock>::iterator It = BB; ++It;
2438       F->getBasicBlockList().insert(It, XorMBB);
2439       F->getBasicBlockList().insert(It, PhiMBB);
2440       BB->addSuccessor(XorMBB);
2441       BB->addSuccessor(PhiMBB);
2442
2443       // Convert from floating point to unsigned 32-bit value
2444       // Use 0 if incoming value is < 0.0
2445       BuildMI(*BB, IP, PPC::FSEL, 3, UseZero).addReg(SrcReg).addReg(SrcReg)
2446         .addReg(Zero);
2447       // Use 2**32 - 1 if incoming value is >= 2**32
2448       BuildMI(*BB, IP, PPC::FSUB, 2, UseMaxInt).addReg(MaxInt).addReg(SrcReg);
2449       BuildMI(*BB, IP, PPC::FSEL, 3, UseChoice).addReg(UseMaxInt)
2450         .addReg(UseZero).addReg(MaxInt);
2451       // Subtract 2**31
2452       BuildMI(*BB, IP, PPC::FSUB, 2, TmpReg).addReg(UseChoice).addReg(Border);
2453       // Use difference if >= 2**31
2454       BuildMI(*BB, IP, PPC::FCMPU, 2, PPC::CR0).addReg(UseChoice)
2455         .addReg(Border);
2456       BuildMI(*BB, IP, PPC::FSEL, 3, TmpReg2).addReg(TmpReg).addReg(TmpReg)
2457         .addReg(UseChoice);
2458       // Convert to integer
2459       BuildMI(*BB, IP, PPC::FCTIWZ, 1, ConvReg).addReg(TmpReg2);
2460       addFrameReference(BuildMI(*BB, IP, PPC::STFD, 3).addReg(ConvReg),
2461                         FrameIdx);
2462       if (DestClass == cByte) {
2463         addFrameReference(BuildMI(*BB, IP, PPC::LBZ, 2, DestReg),
2464                           FrameIdx, 7);
2465       } else if (DestClass == cShort) {
2466         addFrameReference(BuildMI(*BB, IP, PPC::LHZ, 2, DestReg),
2467                           FrameIdx, 6);
2468       } if (DestClass == cInt) {
2469         addFrameReference(BuildMI(*BB, IP, PPC::LWZ, 2, IntTmp),
2470                           FrameIdx, 4);
2471         BuildMI(*BB, IP, PPC::BLT, 2).addReg(PPC::CR0).addMBB(PhiMBB);
2472         BuildMI(*BB, IP, PPC::B, 1).addMBB(XorMBB);
2473
2474         // XorMBB:
2475         //   add 2**31 if input was >= 2**31
2476         BB = XorMBB;
2477         BuildMI(BB, PPC::XORIS, 2, XorReg).addReg(IntTmp).addImm(0x8000);
2478         XorMBB->addSuccessor(PhiMBB);
2479
2480         // PhiMBB:
2481         //   DestReg = phi [ IntTmp, OldMBB ], [ XorReg, XorMBB ]
2482         BB = PhiMBB;
2483         BuildMI(BB, PPC::PHI, 4, DestReg).addReg(IntTmp).addMBB(OldMBB)
2484           .addReg(XorReg).addMBB(XorMBB);
2485       }
2486     }
2487     return;
2488   }
2489
2490   // Check our invariants
2491   assert((SrcClass <= cInt || SrcClass == cLong) && 
2492          "Unhandled source class for cast operation!");
2493   assert((DestClass <= cInt || DestClass == cLong) && 
2494          "Unhandled destination class for cast operation!");
2495
2496   bool sourceUnsigned = SrcTy->isUnsigned() || SrcTy == Type::BoolTy;
2497   bool destUnsigned = DestTy->isUnsigned();
2498
2499   // Unsigned -> Unsigned, clear if larger
2500   if (sourceUnsigned && destUnsigned) {
2501     // handle long dest class now to keep switch clean
2502     if (DestClass == cLong) {
2503       BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
2504       return;
2505     }
2506
2507     // handle u{ byte, short, int } x u{ byte, short, int }
2508     unsigned clearBits = (SrcClass == cByte || DestClass == cByte) ? 24 : 16;
2509     switch (SrcClass) {
2510     case cByte:
2511     case cShort:
2512       if (SrcClass == DestClass)
2513         BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
2514       else
2515         BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(SrcReg)
2516           .addImm(0).addImm(clearBits).addImm(31);
2517       break;
2518     case cInt:
2519     case cLong:
2520       if (DestClass == cInt)
2521         BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
2522       else
2523         BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(SrcReg)
2524           .addImm(0).addImm(clearBits).addImm(31);
2525       break;
2526     }
2527     return;
2528   }
2529
2530   // Signed -> Signed
2531   if (!sourceUnsigned && !destUnsigned) {
2532     // handle long dest class now to keep switch clean
2533     if (DestClass == cLong) {
2534       BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
2535       return;
2536     }
2537
2538     // handle { byte, short, int } x { byte, short, int }
2539     switch (SrcClass) {
2540     case cByte:
2541       if (DestClass == cByte)
2542         BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
2543       else
2544         BuildMI(*MBB, IP, PPC::EXTSB, 1, DestReg).addReg(SrcReg);
2545       break;
2546     case cShort:
2547       if (DestClass == cByte)
2548         BuildMI(*MBB, IP, PPC::EXTSB, 1, DestReg).addReg(SrcReg);
2549       else if (DestClass == cShort)
2550         BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
2551       else
2552         BuildMI(*MBB, IP, PPC::EXTSH, 1, DestReg).addReg(SrcReg);
2553       break;
2554     case cInt:
2555     case cLong:
2556       if (DestClass == cByte)
2557         BuildMI(*MBB, IP, PPC::EXTSB, 1, DestReg).addReg(SrcReg);
2558       else if (DestClass == cShort)
2559         BuildMI(*MBB, IP, PPC::EXTSH, 1, DestReg).addReg(SrcReg);
2560       else
2561         BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
2562       break;
2563     }
2564     return;
2565   }
2566
2567   // Unsigned -> Signed
2568   if (sourceUnsigned && !destUnsigned) {
2569     // handle long dest class now to keep switch clean
2570     if (DestClass == cLong) {
2571       BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
2572       return;
2573     }
2574
2575     // handle u{ byte, short, int } -> { byte, short, int }
2576     switch (SrcClass) {
2577     case cByte:
2578       if (DestClass == cByte)
2579         // uByte 255 -> signed byte == -1
2580         BuildMI(*MBB, IP, PPC::EXTSB, 1, DestReg).addReg(SrcReg);
2581       else
2582         // uByte 255 -> signed short/int == 255
2583         BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(SrcReg).addImm(0)
2584           .addImm(24).addImm(31);
2585       break;
2586     case cShort:
2587       if (DestClass == cByte)
2588         BuildMI(*MBB, IP, PPC::EXTSB, 1, DestReg).addReg(SrcReg);
2589       else if (DestClass == cShort)
2590         BuildMI(*MBB, IP, PPC::EXTSH, 1, DestReg).addReg(SrcReg);
2591       else
2592         BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(SrcReg).addImm(0)
2593           .addImm(16).addImm(31);
2594       break;
2595     case cInt:
2596     case cLong:
2597       if (DestClass == cByte)
2598         BuildMI(*MBB, IP, PPC::EXTSB, 1, DestReg).addReg(SrcReg);
2599       else if (DestClass == cShort)
2600         BuildMI(*MBB, IP, PPC::EXTSH, 1, DestReg).addReg(SrcReg);
2601       else
2602         BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
2603       break;
2604     }
2605     return;
2606   }
2607
2608   // Signed -> Unsigned
2609   if (!sourceUnsigned && destUnsigned) {
2610     // handle long dest class now to keep switch clean
2611     if (DestClass == cLong) {
2612       BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
2613       return;
2614     }
2615
2616     // handle { byte, short, int } -> u{ byte, short, int }
2617     unsigned clearBits = (DestClass == cByte) ? 24 : 16;
2618     switch (SrcClass) {
2619     case cByte:
2620     case cShort:
2621       if (DestClass == cByte || DestClass == cShort)
2622         // sbyte -1 -> ubyte 0x000000FF
2623         BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(SrcReg)
2624           .addImm(0).addImm(clearBits).addImm(31);
2625       else
2626         // sbyte -1 -> ubyte 0xFFFFFFFF
2627         BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
2628       break;
2629     case cInt:
2630     case cLong:
2631       if (DestClass == cInt)
2632         BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
2633       else
2634         BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(SrcReg)
2635           .addImm(0).addImm(clearBits).addImm(31);
2636       break;
2637     }
2638     return;
2639   }
2640
2641   // Anything we haven't handled already, we can't (yet) handle at all.
2642   std::cerr << "Unhandled cast from " << SrcTy->getDescription()
2643             << "to " << DestTy->getDescription() << '\n';
2644   abort();
2645 }
2646
2647 /// visitVANextInst - Implement the va_next instruction...
2648 ///
2649 void ISel::visitVANextInst(VANextInst &I) {
2650   unsigned VAList = getReg(I.getOperand(0));
2651   unsigned DestReg = getReg(I);
2652
2653   unsigned Size;
2654   switch (I.getArgType()->getTypeID()) {
2655   default:
2656     std::cerr << I;
2657     assert(0 && "Error: bad type for va_next instruction!");
2658     return;
2659   case Type::PointerTyID:
2660   case Type::UIntTyID:
2661   case Type::IntTyID:
2662     Size = 4;
2663     break;
2664   case Type::ULongTyID:
2665   case Type::LongTyID:
2666   case Type::DoubleTyID:
2667     Size = 8;
2668     break;
2669   }
2670
2671   // Increment the VAList pointer...
2672   BuildMI(BB, PPC::ADDI, 2, DestReg).addReg(VAList).addSImm(Size);
2673 }
2674
2675 void ISel::visitVAArgInst(VAArgInst &I) {
2676   unsigned VAList = getReg(I.getOperand(0));
2677   unsigned DestReg = getReg(I);
2678
2679   switch (I.getType()->getTypeID()) {
2680   default:
2681     std::cerr << I;
2682     assert(0 && "Error: bad type for va_next instruction!");
2683     return;
2684   case Type::PointerTyID:
2685   case Type::UIntTyID:
2686   case Type::IntTyID:
2687     BuildMI(BB, PPC::LWZ, 2, DestReg).addSImm(0).addReg(VAList);
2688     break;
2689   case Type::ULongTyID:
2690   case Type::LongTyID:
2691     BuildMI(BB, PPC::LD, 2, DestReg).addSImm(0).addReg(VAList);
2692     break;
2693   case Type::FloatTyID:
2694     BuildMI(BB, PPC::LFS, 2, DestReg).addSImm(0).addReg(VAList);
2695     break;
2696   case Type::DoubleTyID:
2697     BuildMI(BB, PPC::LFD, 2, DestReg).addSImm(0).addReg(VAList);
2698     break;
2699   }
2700 }
2701
2702 /// visitGetElementPtrInst - instruction-select GEP instructions
2703 ///
2704 void ISel::visitGetElementPtrInst(GetElementPtrInst &I) {
2705   if (canFoldGEPIntoLoadOrStore(&I))
2706     return;
2707
2708   unsigned outputReg = getReg(I);
2709   emitGEPOperation(BB, BB->end(), I.getOperand(0), I.op_begin()+1, I.op_end(), 
2710                    outputReg, false, 0, 0);
2711 }
2712
2713 /// emitGEPOperation - Common code shared between visitGetElementPtrInst and
2714 /// constant expression GEP support.
2715 ///
2716 void ISel::emitGEPOperation(MachineBasicBlock *MBB,
2717                             MachineBasicBlock::iterator IP,
2718                             Value *Src, User::op_iterator IdxBegin,
2719                             User::op_iterator IdxEnd, unsigned TargetReg,
2720                             bool GEPIsFolded, ConstantSInt **RemainderPtr,
2721                             unsigned *PendingAddReg) {
2722   const TargetData &TD = TM.getTargetData();
2723   const Type *Ty = Src->getType();
2724   unsigned basePtrReg = getReg(Src, MBB, IP);
2725   int64_t constValue = 0;
2726   
2727   // Record the operations to emit the GEP in a vector so that we can emit them
2728   // after having analyzed the entire instruction.
2729   std::vector<CollapsedGepOp> ops;
2730   
2731   // GEPs have zero or more indices; we must perform a struct access
2732   // or array access for each one.
2733   for (GetElementPtrInst::op_iterator oi = IdxBegin, oe = IdxEnd; oi != oe;
2734        ++oi) {
2735     Value *idx = *oi;
2736     if (const StructType *StTy = dyn_cast<StructType>(Ty)) {
2737       // It's a struct access.  idx is the index into the structure,
2738       // which names the field. Use the TargetData structure to
2739       // pick out what the layout of the structure is in memory.
2740       // Use the (constant) structure index's value to find the
2741       // right byte offset from the StructLayout class's list of
2742       // structure member offsets.
2743       unsigned fieldIndex = cast<ConstantUInt>(idx)->getValue();
2744       unsigned memberOffset =
2745         TD.getStructLayout(StTy)->MemberOffsets[fieldIndex];
2746
2747       // StructType member offsets are always constant values.  Add it to the
2748       // running total.
2749       constValue += memberOffset;
2750
2751       // The next type is the member of the structure selected by the
2752       // index.
2753       Ty = StTy->getElementType (fieldIndex);
2754     } else if (const SequentialType *SqTy = dyn_cast<SequentialType> (Ty)) {
2755       // Many GEP instructions use a [cast (int/uint) to LongTy] as their
2756       // operand.  Handle this case directly now...
2757       if (CastInst *CI = dyn_cast<CastInst>(idx))
2758         if (CI->getOperand(0)->getType() == Type::IntTy ||
2759             CI->getOperand(0)->getType() == Type::UIntTy)
2760           idx = CI->getOperand(0);
2761
2762       // It's an array or pointer access: [ArraySize x ElementType].
2763       // We want to add basePtrReg to (idxReg * sizeof ElementType). First, we
2764       // must find the size of the pointed-to type (Not coincidentally, the next
2765       // type is the type of the elements in the array).
2766       Ty = SqTy->getElementType();
2767       unsigned elementSize = TD.getTypeSize(Ty);
2768       
2769       if (ConstantInt *C = dyn_cast<ConstantInt>(idx)) {
2770         if (ConstantSInt *CS = dyn_cast<ConstantSInt>(C))
2771           constValue += CS->getValue() * elementSize;
2772         else if (ConstantUInt *CU = dyn_cast<ConstantUInt>(C))
2773           constValue += CU->getValue() * elementSize;
2774         else
2775           assert(0 && "Invalid ConstantInt GEP index type!");
2776       } else {
2777         // Push current gep state to this point as an add
2778         ops.push_back(CollapsedGepOp(false, 0, 
2779           ConstantSInt::get(Type::IntTy,constValue)));
2780         
2781         // Push multiply gep op and reset constant value
2782         ops.push_back(CollapsedGepOp(true, idx, 
2783           ConstantSInt::get(Type::IntTy, elementSize)));
2784         
2785         constValue = 0;
2786       }
2787     }
2788   }
2789   // Emit instructions for all the collapsed ops
2790   bool pendingAdd = false;
2791   unsigned pendingAddReg = 0;
2792   
2793   for(std::vector<CollapsedGepOp>::iterator cgo_i = ops.begin(),
2794       cgo_e = ops.end(); cgo_i != cgo_e; ++cgo_i) {
2795     CollapsedGepOp& cgo = *cgo_i;
2796     unsigned nextBasePtrReg = makeAnotherReg(Type::IntTy);
2797   
2798     // If we didn't emit an add last time through the loop, we need to now so
2799     // that the base reg is updated appropriately.
2800     if (pendingAdd) {
2801       assert(pendingAddReg != 0 && "Uninitialized register in pending add!");
2802       BuildMI(*MBB, IP, PPC::ADD, 2, nextBasePtrReg).addReg(basePtrReg)
2803         .addReg(pendingAddReg);
2804       basePtrReg = nextBasePtrReg;
2805       nextBasePtrReg = makeAnotherReg(Type::IntTy);
2806       pendingAddReg = 0;
2807       pendingAdd = false;
2808     }
2809
2810     if (cgo.isMul) {
2811       // We know the elementSize is a constant, so we can emit a constant mul
2812       unsigned TmpReg = makeAnotherReg(Type::IntTy);
2813       doMultiplyConst(MBB, IP, nextBasePtrReg, cgo.index, cgo.size);
2814       pendingAddReg = basePtrReg;
2815       pendingAdd = true;
2816     } else {
2817       // Try and generate an immediate addition if possible
2818       if (cgo.size->isNullValue()) {
2819         BuildMI(*MBB, IP, PPC::OR, 2, nextBasePtrReg).addReg(basePtrReg)
2820           .addReg(basePtrReg);
2821       } else if (canUseAsImmediateForOpcode(cgo.size, 0)) {
2822         BuildMI(*MBB, IP, PPC::ADDI, 2, nextBasePtrReg).addReg(basePtrReg)
2823           .addSImm(cgo.size->getValue());
2824       } else {
2825         unsigned Op1r = getReg(cgo.size, MBB, IP);
2826         BuildMI(*MBB, IP, PPC::ADD, 2, nextBasePtrReg).addReg(basePtrReg)
2827           .addReg(Op1r);
2828       }
2829     }
2830
2831     basePtrReg = nextBasePtrReg;
2832   }
2833   // Add the current base register plus any accumulated constant value
2834   ConstantSInt *remainder = ConstantSInt::get(Type::IntTy, constValue);
2835   
2836   // If we are emitting this during a fold, copy the current base register to
2837   // the target, and save the current constant offset so the folding load or
2838   // store can try and use it as an immediate.
2839   if (GEPIsFolded) {
2840     // If this is a folded GEP and the last element was an index, then we need
2841     // to do some extra work to turn a shift/add/stw into a shift/stwx
2842     if (pendingAdd && 0 == remainder->getValue()) {
2843       assert(pendingAddReg != 0 && "Uninitialized register in pending add!");
2844       *PendingAddReg = pendingAddReg;
2845     } else {
2846       *PendingAddReg = 0;
2847       if (pendingAdd) {
2848         unsigned nextBasePtrReg = makeAnotherReg(Type::IntTy);
2849         assert(pendingAddReg != 0 && "Uninitialized register in pending add!");
2850         BuildMI(*MBB, IP, PPC::ADD, 2, nextBasePtrReg).addReg(basePtrReg)
2851           .addReg(pendingAddReg);
2852         basePtrReg = nextBasePtrReg;
2853       }
2854     }
2855     BuildMI (*MBB, IP, PPC::OR, 2, TargetReg).addReg(basePtrReg)
2856       .addReg(basePtrReg);
2857     *RemainderPtr = remainder;
2858     return;
2859   }
2860
2861   // If we still have a pending add at this point, emit it now
2862   if (pendingAdd) {
2863     unsigned TmpReg = makeAnotherReg(Type::IntTy);
2864     BuildMI(*MBB, IP, PPC::ADD, 2, TmpReg).addReg(pendingAddReg)
2865       .addReg(basePtrReg);
2866     basePtrReg = TmpReg;
2867   }
2868   
2869   // After we have processed all the indices, the result is left in
2870   // basePtrReg.  Move it to the register where we were expected to
2871   // put the answer.
2872   if (remainder->isNullValue()) {
2873     BuildMI (*MBB, IP, PPC::OR, 2, TargetReg).addReg(basePtrReg)
2874       .addReg(basePtrReg);
2875   } else if (canUseAsImmediateForOpcode(remainder, 0)) {
2876     BuildMI(*MBB, IP, PPC::ADDI, 2, TargetReg).addReg(basePtrReg)
2877       .addSImm(remainder->getValue());
2878   } else {
2879     unsigned Op1r = getReg(remainder, MBB, IP);
2880     BuildMI(*MBB, IP, PPC::ADD, 2, TargetReg).addReg(basePtrReg).addReg(Op1r);
2881   }
2882 }
2883
2884 /// visitAllocaInst - If this is a fixed size alloca, allocate space from the
2885 /// frame manager, otherwise do it the hard way.
2886 ///
2887 void ISel::visitAllocaInst(AllocaInst &I) {
2888   // If this is a fixed size alloca in the entry block for the function, we
2889   // statically stack allocate the space, so we don't need to do anything here.
2890   //
2891   if (dyn_castFixedAlloca(&I)) return;
2892   
2893   // Find the data size of the alloca inst's getAllocatedType.
2894   const Type *Ty = I.getAllocatedType();
2895   unsigned TySize = TM.getTargetData().getTypeSize(Ty);
2896
2897   // Create a register to hold the temporary result of multiplying the type size
2898   // constant by the variable amount.
2899   unsigned TotalSizeReg = makeAnotherReg(Type::UIntTy);
2900   
2901   // TotalSizeReg = mul <numelements>, <TypeSize>
2902   MachineBasicBlock::iterator MBBI = BB->end();
2903   ConstantUInt *CUI = ConstantUInt::get(Type::UIntTy, TySize);
2904   doMultiplyConst(BB, MBBI, TotalSizeReg, I.getArraySize(), CUI);
2905
2906   // AddedSize = add <TotalSizeReg>, 15
2907   unsigned AddedSizeReg = makeAnotherReg(Type::UIntTy);
2908   BuildMI(BB, PPC::ADDI, 2, AddedSizeReg).addReg(TotalSizeReg).addSImm(15);
2909
2910   // AlignedSize = and <AddedSize>, ~15
2911   unsigned AlignedSize = makeAnotherReg(Type::UIntTy);
2912   BuildMI(BB, PPC::RLWINM, 4, AlignedSize).addReg(AddedSizeReg).addImm(0)
2913     .addImm(0).addImm(27);
2914   
2915   // Subtract size from stack pointer, thereby allocating some space.
2916   BuildMI(BB, PPC::SUB, 2, PPC::R1).addReg(PPC::R1).addReg(AlignedSize);
2917
2918   // Put a pointer to the space into the result register, by copying
2919   // the stack pointer.
2920   BuildMI(BB, PPC::OR, 2, getReg(I)).addReg(PPC::R1).addReg(PPC::R1);
2921
2922   // Inform the Frame Information that we have just allocated a variable-sized
2923   // object.
2924   F->getFrameInfo()->CreateVariableSizedObject();
2925 }
2926
2927 /// visitMallocInst - Malloc instructions are code generated into direct calls
2928 /// to the library malloc.
2929 ///
2930 void ISel::visitMallocInst(MallocInst &I) {
2931   unsigned AllocSize = TM.getTargetData().getTypeSize(I.getAllocatedType());
2932   unsigned Arg;
2933
2934   if (ConstantUInt *C = dyn_cast<ConstantUInt>(I.getOperand(0))) {
2935     Arg = getReg(ConstantUInt::get(Type::UIntTy, C->getValue() * AllocSize));
2936   } else {
2937     Arg = makeAnotherReg(Type::UIntTy);
2938     MachineBasicBlock::iterator MBBI = BB->end();
2939     ConstantUInt *CUI = ConstantUInt::get(Type::UIntTy, AllocSize);
2940     doMultiplyConst(BB, MBBI, Arg, I.getOperand(0), CUI);
2941   }
2942
2943   std::vector<ValueRecord> Args;
2944   Args.push_back(ValueRecord(Arg, Type::UIntTy));
2945   MachineInstr *TheCall = 
2946     BuildMI(PPC::CALLpcrel, 1).addGlobalAddress(mallocFn, true);
2947   doCall(ValueRecord(getReg(I), I.getType()), TheCall, Args, false);
2948 }
2949
2950
2951 /// visitFreeInst - Free instructions are code gen'd to call the free libc
2952 /// function.
2953 ///
2954 void ISel::visitFreeInst(FreeInst &I) {
2955   std::vector<ValueRecord> Args;
2956   Args.push_back(ValueRecord(I.getOperand(0)));
2957   MachineInstr *TheCall = 
2958     BuildMI(PPC::CALLpcrel, 1).addGlobalAddress(freeFn, true);
2959   doCall(ValueRecord(0, Type::VoidTy), TheCall, Args, false);
2960 }
2961    
2962 /// createPPC64ISelSimple - This pass converts an LLVM function into a machine
2963 /// code representation is a very simple peep-hole fashion.
2964 ///
2965 FunctionPass *llvm::createPPC64ISelSimple(TargetMachine &TM) {
2966   return new ISel(TM);
2967 }