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