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