* Speed up canUseAsImmediateForOpcode() by comparing Operand before
[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   return;
1158 }
1159
1160
1161
1162 /// promote32 - Emit instructions to turn a narrow operand into a 32-bit-wide
1163 /// operand, in the specified target register.
1164 ///
1165 void ISel::promote32(unsigned targetReg, const ValueRecord &VR) {
1166   bool isUnsigned = VR.Ty->isUnsigned() || VR.Ty == Type::BoolTy;
1167
1168   Value *Val = VR.Val;
1169   const Type *Ty = VR.Ty;
1170   if (Val) {
1171     if (Constant *C = dyn_cast<Constant>(Val)) {
1172       Val = ConstantExpr::getCast(C, Type::IntTy);
1173       Ty = Type::IntTy;
1174     }
1175
1176     // If this is a simple constant, just emit a load directly to avoid the copy
1177     if (ConstantInt *CI = dyn_cast<ConstantInt>(Val)) {
1178       int TheVal = CI->getRawValue() & 0xFFFFFFFF;
1179
1180       if (TheVal < 32768 && TheVal >= -32768) {
1181         BuildMI(BB, PPC32::LI, 1, targetReg).addSImm(TheVal);
1182       } else {
1183         unsigned TmpReg = makeAnotherReg(Type::IntTy);
1184         BuildMI(BB, PPC32::LIS, 1, TmpReg).addSImm(TheVal >> 16);
1185         BuildMI(BB, PPC32::ORI, 2, targetReg).addReg(TmpReg)
1186           .addImm(TheVal & 0xFFFF);
1187       }
1188       return;
1189     }
1190   }
1191
1192   // Make sure we have the register number for this value...
1193   unsigned Reg = Val ? getReg(Val) : VR.Reg;
1194
1195   switch (getClassB(Ty)) {
1196   case cByte:
1197     // Extend value into target register (8->32)
1198     if (isUnsigned)
1199       BuildMI(BB, PPC32::RLWINM, 4, targetReg).addReg(Reg).addZImm(0)
1200         .addZImm(24).addZImm(31);
1201     else
1202       BuildMI(BB, PPC32::EXTSB, 1, targetReg).addReg(Reg);
1203     break;
1204   case cShort:
1205     // Extend value into target register (16->32)
1206     if (isUnsigned)
1207       BuildMI(BB, PPC32::RLWINM, 4, targetReg).addReg(Reg).addZImm(0)
1208         .addZImm(16).addZImm(31);
1209     else
1210       BuildMI(BB, PPC32::EXTSH, 1, targetReg).addReg(Reg);
1211     break;
1212   case cInt:
1213     // Move value into target register (32->32)
1214     BuildMI(BB, PPC32::OR, 2, targetReg).addReg(Reg).addReg(Reg);
1215     break;
1216   default:
1217     assert(0 && "Unpromotable operand class in promote32");
1218   }
1219 }
1220
1221 /// visitReturnInst - implemented with BLR
1222 ///
1223 void ISel::visitReturnInst(ReturnInst &I) {
1224   // Only do the processing if this is a non-void return
1225   if (I.getNumOperands() > 0) {
1226     Value *RetVal = I.getOperand(0);
1227     switch (getClassB(RetVal->getType())) {
1228     case cByte:   // integral return values: extend or move into r3 and return
1229     case cShort:
1230     case cInt:
1231       promote32(PPC32::R3, ValueRecord(RetVal));
1232       break;
1233     case cFP32:
1234     case cFP64: {   // Floats & Doubles: Return in f1
1235       unsigned RetReg = getReg(RetVal);
1236       BuildMI(BB, PPC32::FMR, 1, PPC32::F1).addReg(RetReg);
1237       break;
1238     }
1239     case cLong: {
1240       unsigned RetReg = getReg(RetVal);
1241       BuildMI(BB, PPC32::OR, 2, PPC32::R3).addReg(RetReg).addReg(RetReg);
1242       BuildMI(BB, PPC32::OR, 2, PPC32::R4).addReg(RetReg+1).addReg(RetReg+1);
1243       break;
1244     }
1245     default:
1246       visitInstruction(I);
1247     }
1248   }
1249   BuildMI(BB, PPC32::BLR, 1).addImm(0);
1250 }
1251
1252 // getBlockAfter - Return the basic block which occurs lexically after the
1253 // specified one.
1254 static inline BasicBlock *getBlockAfter(BasicBlock *BB) {
1255   Function::iterator I = BB; ++I;  // Get iterator to next block
1256   return I != BB->getParent()->end() ? &*I : 0;
1257 }
1258
1259 /// visitBranchInst - Handle conditional and unconditional branches here.  Note
1260 /// that since code layout is frozen at this point, that if we are trying to
1261 /// jump to a block that is the immediate successor of the current block, we can
1262 /// just make a fall-through (but we don't currently).
1263 ///
1264 void ISel::visitBranchInst(BranchInst &BI) {
1265   // Update machine-CFG edges
1266   BB->addSuccessor (MBBMap[BI.getSuccessor(0)]);
1267   if (BI.isConditional())
1268     BB->addSuccessor (MBBMap[BI.getSuccessor(1)]);
1269   
1270   BasicBlock *NextBB = getBlockAfter(BI.getParent());  // BB after current one
1271
1272   if (!BI.isConditional()) {  // Unconditional branch?
1273     if (BI.getSuccessor(0) != NextBB) 
1274       BuildMI(BB, PPC32::B, 1).addMBB(MBBMap[BI.getSuccessor(0)]);
1275     return;
1276   }
1277   
1278   // See if we can fold the setcc into the branch itself...
1279   SetCondInst *SCI = canFoldSetCCIntoBranchOrSelect(BI.getCondition());
1280   if (SCI == 0) {
1281     // Nope, cannot fold setcc into this branch.  Emit a branch on a condition
1282     // computed some other way...
1283     unsigned condReg = getReg(BI.getCondition());
1284     BuildMI(BB, PPC32::CMPLI, 3, PPC32::CR1).addImm(0).addReg(condReg)
1285       .addImm(0);
1286     if (BI.getSuccessor(1) == NextBB) {
1287       if (BI.getSuccessor(0) != NextBB)
1288         BuildMI(BB, PPC32::BNE, 2).addReg(PPC32::CR1)
1289           .addMBB(MBBMap[BI.getSuccessor(0)]);
1290     } else {
1291       BuildMI(BB, PPC32::BEQ, 2).addReg(PPC32::CR1)
1292         .addMBB(MBBMap[BI.getSuccessor(1)]);
1293       
1294       if (BI.getSuccessor(0) != NextBB)
1295         BuildMI(BB, PPC32::B, 1).addMBB(MBBMap[BI.getSuccessor(0)]);
1296     }
1297     return;
1298   }
1299
1300   unsigned OpNum = getSetCCNumber(SCI->getOpcode());
1301   unsigned Opcode = getPPCOpcodeForSetCCNumber(SCI->getOpcode());
1302   MachineBasicBlock::iterator MII = BB->end();
1303   OpNum = EmitComparison(OpNum, SCI->getOperand(0), SCI->getOperand(1), BB,MII);
1304   
1305   if (BI.getSuccessor(0) != NextBB) {
1306     BuildMI(BB, Opcode, 2).addReg(PPC32::CR0)
1307       .addMBB(MBBMap[BI.getSuccessor(0)]);
1308     if (BI.getSuccessor(1) != NextBB)
1309       BuildMI(BB, PPC32::B, 1).addMBB(MBBMap[BI.getSuccessor(1)]);
1310   } else {
1311     // Change to the inverse condition...
1312     if (BI.getSuccessor(1) != NextBB) {
1313       Opcode = invertPPCBranchOpcode(Opcode);
1314       BuildMI(BB, Opcode, 2).addReg(PPC32::CR0)
1315         .addMBB(MBBMap[BI.getSuccessor(1)]);
1316     }
1317   }
1318 }
1319
1320 /// doCall - This emits an abstract call instruction, setting up the arguments
1321 /// and the return value as appropriate.  For the actual function call itself,
1322 /// it inserts the specified CallMI instruction into the stream.
1323 ///
1324 /// FIXME: See Documentation at the following URL for "correct" behavior
1325 /// <http://developer.apple.com/documentation/DeveloperTools/Conceptual/MachORuntime/2rt_powerpc_abi/chapter_9_section_5.html>
1326 void ISel::doCall(const ValueRecord &Ret, MachineInstr *CallMI,
1327                   const std::vector<ValueRecord> &Args, bool isVarArg) {
1328   // Count how many bytes are to be pushed on the stack...
1329   unsigned NumBytes = 0;
1330
1331   if (!Args.empty()) {
1332     for (unsigned i = 0, e = Args.size(); i != e; ++i)
1333       switch (getClassB(Args[i].Ty)) {
1334       case cByte: case cShort: case cInt:
1335         NumBytes += 4; break;
1336       case cLong:
1337         NumBytes += 8; break;
1338       case cFP32:
1339         NumBytes += 4; break;
1340       case cFP64:
1341         NumBytes += 8; break;
1342         break;
1343       default: assert(0 && "Unknown class!");
1344       }
1345
1346     // Adjust the stack pointer for the new arguments...
1347     BuildMI(BB, PPC32::ADJCALLSTACKDOWN, 1).addSImm(NumBytes);
1348
1349     // Arguments go on the stack in reverse order, as specified by the ABI.
1350     // Offset to the paramater area on the stack is 24.
1351     unsigned ArgOffset = 24;
1352     int GPR_remaining = 8, FPR_remaining = 13;
1353     unsigned GPR_idx = 0, FPR_idx = 0;
1354     static const unsigned GPR[] = { 
1355       PPC32::R3, PPC32::R4, PPC32::R5, PPC32::R6,
1356       PPC32::R7, PPC32::R8, PPC32::R9, PPC32::R10,
1357     };
1358     static const unsigned FPR[] = {
1359       PPC32::F1, PPC32::F2, PPC32::F3, PPC32::F4, PPC32::F5, PPC32::F6, 
1360       PPC32::F7, PPC32::F8, PPC32::F9, PPC32::F10, PPC32::F11, PPC32::F12, 
1361       PPC32::F13
1362     };
1363     
1364     for (unsigned i = 0, e = Args.size(); i != e; ++i) {
1365       unsigned ArgReg;
1366       switch (getClassB(Args[i].Ty)) {
1367       case cByte:
1368       case cShort:
1369         // Promote arg to 32 bits wide into a temporary register...
1370         ArgReg = makeAnotherReg(Type::UIntTy);
1371         promote32(ArgReg, Args[i]);
1372           
1373         // Reg or stack?
1374         if (GPR_remaining > 0) {
1375           BuildMI(BB, PPC32::OR, 2, GPR[GPR_idx]).addReg(ArgReg)
1376             .addReg(ArgReg);
1377           CallMI->addRegOperand(GPR[GPR_idx], MachineOperand::Use);
1378         } else {
1379           BuildMI(BB, PPC32::STW, 3).addReg(ArgReg).addSImm(ArgOffset)
1380             .addReg(PPC32::R1);
1381         }
1382         break;
1383       case cInt:
1384         ArgReg = Args[i].Val ? getReg(Args[i].Val) : Args[i].Reg;
1385
1386         // Reg or stack?
1387         if (GPR_remaining > 0) {
1388           BuildMI(BB, PPC32::OR, 2, GPR[GPR_idx]).addReg(ArgReg)
1389             .addReg(ArgReg);
1390           CallMI->addRegOperand(GPR[GPR_idx], MachineOperand::Use);
1391         } else {
1392           BuildMI(BB, PPC32::STW, 3).addReg(ArgReg).addSImm(ArgOffset)
1393             .addReg(PPC32::R1);
1394         }
1395         break;
1396       case cLong:
1397         ArgReg = Args[i].Val ? getReg(Args[i].Val) : Args[i].Reg;
1398
1399         // Reg or stack?  Note that PPC calling conventions state that long args
1400         // are passed rN = hi, rN+1 = lo, opposite of LLVM.
1401         if (GPR_remaining > 1) {
1402           BuildMI(BB, PPC32::OR, 2, GPR[GPR_idx]).addReg(ArgReg)
1403             .addReg(ArgReg);
1404           BuildMI(BB, PPC32::OR, 2, GPR[GPR_idx+1]).addReg(ArgReg+1)
1405             .addReg(ArgReg+1);
1406           CallMI->addRegOperand(GPR[GPR_idx], MachineOperand::Use);
1407           CallMI->addRegOperand(GPR[GPR_idx+1], MachineOperand::Use);
1408         } else {
1409           BuildMI(BB, PPC32::STW, 3).addReg(ArgReg).addSImm(ArgOffset)
1410             .addReg(PPC32::R1);
1411           BuildMI(BB, PPC32::STW, 3).addReg(ArgReg+1).addSImm(ArgOffset+4)
1412             .addReg(PPC32::R1);
1413         }
1414
1415         ArgOffset += 4;        // 8 byte entry, not 4.
1416         GPR_remaining -= 1;    // uses up 2 GPRs
1417         GPR_idx += 1;
1418         break;
1419       case cFP32:
1420         ArgReg = Args[i].Val ? getReg(Args[i].Val) : Args[i].Reg;
1421         // Reg or stack?
1422         if (FPR_remaining > 0) {
1423           BuildMI(BB, PPC32::FMR, 1, FPR[FPR_idx]).addReg(ArgReg);
1424           CallMI->addRegOperand(FPR[FPR_idx], MachineOperand::Use);
1425           FPR_remaining--;
1426           FPR_idx++;
1427           
1428           // If this is a vararg function, and there are GPRs left, also
1429           // pass the float in an int.  Otherwise, put it on the stack.
1430           if (isVarArg) {
1431             BuildMI(BB, PPC32::STFS, 3).addReg(ArgReg).addSImm(ArgOffset)
1432             .addReg(PPC32::R1);
1433             if (GPR_remaining > 0) {
1434               BuildMI(BB, PPC32::LWZ, 2, GPR[GPR_idx])
1435               .addSImm(ArgOffset).addReg(ArgReg);
1436               CallMI->addRegOperand(GPR[GPR_idx], MachineOperand::Use);
1437             }
1438           }
1439         } else {
1440           BuildMI(BB, PPC32::STFS, 3).addReg(ArgReg).addSImm(ArgOffset)
1441           .addReg(PPC32::R1);
1442         }
1443         break;
1444       case cFP64:
1445         ArgReg = Args[i].Val ? getReg(Args[i].Val) : Args[i].Reg;
1446         // Reg or stack?
1447         if (FPR_remaining > 0) {
1448           BuildMI(BB, PPC32::FMR, 1, FPR[FPR_idx]).addReg(ArgReg);
1449           CallMI->addRegOperand(FPR[FPR_idx], MachineOperand::Use);
1450           FPR_remaining--;
1451           FPR_idx++;
1452           // For vararg functions, must pass doubles via int regs as well
1453           if (isVarArg) {
1454             BuildMI(BB, PPC32::STFD, 3).addReg(ArgReg).addSImm(ArgOffset)
1455             .addReg(PPC32::R1);
1456             
1457             if (GPR_remaining > 1) {
1458               BuildMI(BB, PPC32::LWZ, 2, GPR[GPR_idx]).addSImm(ArgOffset)
1459               .addReg(PPC32::R1);
1460               BuildMI(BB, PPC32::LWZ, 2, GPR[GPR_idx+1])
1461                 .addSImm(ArgOffset+4).addReg(PPC32::R1);
1462               CallMI->addRegOperand(GPR[GPR_idx], MachineOperand::Use);
1463               CallMI->addRegOperand(GPR[GPR_idx+1], MachineOperand::Use);
1464             }
1465           }
1466         } else {
1467           BuildMI(BB, PPC32::STFD, 3).addReg(ArgReg).addSImm(ArgOffset)
1468           .addReg(PPC32::R1);
1469         }
1470         // Doubles use 8 bytes, and 2 GPRs worth of param space
1471         ArgOffset += 4;
1472         GPR_remaining--;
1473         GPR_idx++;
1474         break;
1475         
1476       default: assert(0 && "Unknown class!");
1477       }
1478       ArgOffset += 4;
1479       GPR_remaining--;
1480       GPR_idx++;
1481     }
1482   } else {
1483     BuildMI(BB, PPC32::ADJCALLSTACKDOWN, 1).addSImm(0);
1484   }
1485
1486   BB->push_back(CallMI);
1487   BuildMI(BB, PPC32::ADJCALLSTACKUP, 1).addSImm(NumBytes);
1488
1489   // If there is a return value, scavenge the result from the location the call
1490   // leaves it in...
1491   //
1492   if (Ret.Ty != Type::VoidTy) {
1493     unsigned DestClass = getClassB(Ret.Ty);
1494     switch (DestClass) {
1495     case cByte:
1496     case cShort:
1497     case cInt:
1498       // Integral results are in r3
1499       BuildMI(BB, PPC32::OR, 2, Ret.Reg).addReg(PPC32::R3).addReg(PPC32::R3);
1500       break;
1501     case cFP32:     // Floating-point return values live in f1
1502     case cFP64:
1503       BuildMI(BB, PPC32::FMR, 1, Ret.Reg).addReg(PPC32::F1);
1504       break;
1505     case cLong:   // Long values are in r3 hi:r4 lo
1506       BuildMI(BB, PPC32::OR, 2, Ret.Reg).addReg(PPC32::R3).addReg(PPC32::R3);
1507       BuildMI(BB, PPC32::OR, 2, Ret.Reg+1).addReg(PPC32::R4).addReg(PPC32::R4);
1508       break;
1509     default: assert(0 && "Unknown class!");
1510     }
1511   }
1512 }
1513
1514
1515 /// visitCallInst - Push args on stack and do a procedure call instruction.
1516 void ISel::visitCallInst(CallInst &CI) {
1517   MachineInstr *TheCall;
1518   Function *F = CI.getCalledFunction();
1519   if (F) {
1520     // Is it an intrinsic function call?
1521     if (Intrinsic::ID ID = (Intrinsic::ID)F->getIntrinsicID()) {
1522       visitIntrinsicCall(ID, CI);   // Special intrinsics are not handled here
1523       return;
1524     }
1525
1526     // Emit a CALL instruction with PC-relative displacement.
1527     TheCall = BuildMI(PPC32::CALLpcrel, 1).addGlobalAddress(F, true);
1528   } else {  // Emit an indirect call through the CTR
1529     unsigned Reg = getReg(CI.getCalledValue());
1530     BuildMI(BB, PPC32::MTCTR, 1).addReg(Reg);
1531     TheCall = BuildMI(PPC32::CALLindirect, 2).addZImm(20).addZImm(0);
1532   }
1533
1534   std::vector<ValueRecord> Args;
1535   for (unsigned i = 1, e = CI.getNumOperands(); i != e; ++i)
1536     Args.push_back(ValueRecord(CI.getOperand(i)));
1537
1538   unsigned DestReg = CI.getType() != Type::VoidTy ? getReg(CI) : 0;
1539   bool isVarArg = F ? F->getFunctionType()->isVarArg() : true;
1540   doCall(ValueRecord(DestReg, CI.getType()), TheCall, Args, isVarArg);
1541 }         
1542
1543
1544 /// dyncastIsNan - Return the operand of an isnan operation if this is an isnan.
1545 ///
1546 static Value *dyncastIsNan(Value *V) {
1547   if (CallInst *CI = dyn_cast<CallInst>(V))
1548     if (Function *F = CI->getCalledFunction())
1549       if (F->getIntrinsicID() == Intrinsic::isunordered)
1550         return CI->getOperand(1);
1551   return 0;
1552 }
1553
1554 /// isOnlyUsedByUnorderedComparisons - Return true if this value is only used by
1555 /// or's whos operands are all calls to the isnan predicate.
1556 static bool isOnlyUsedByUnorderedComparisons(Value *V) {
1557   assert(dyncastIsNan(V) && "The value isn't an isnan call!");
1558
1559   // Check all uses, which will be or's of isnans if this predicate is true.
1560   for (Value::use_iterator UI = V->use_begin(), E = V->use_end(); UI != E;++UI){
1561     Instruction *I = cast<Instruction>(*UI);
1562     if (I->getOpcode() != Instruction::Or) return false;
1563     if (I->getOperand(0) != V && !dyncastIsNan(I->getOperand(0))) return false;
1564     if (I->getOperand(1) != V && !dyncastIsNan(I->getOperand(1))) return false;
1565   }
1566
1567   return true;
1568 }
1569
1570 /// LowerUnknownIntrinsicFunctionCalls - This performs a prepass over the
1571 /// function, lowering any calls to unknown intrinsic functions into the
1572 /// equivalent LLVM code.
1573 ///
1574 void ISel::LowerUnknownIntrinsicFunctionCalls(Function &F) {
1575   for (Function::iterator BB = F.begin(), E = F.end(); BB != E; ++BB)
1576     for (BasicBlock::iterator I = BB->begin(), E = BB->end(); I != E; )
1577       if (CallInst *CI = dyn_cast<CallInst>(I++))
1578         if (Function *F = CI->getCalledFunction())
1579           switch (F->getIntrinsicID()) {
1580           case Intrinsic::not_intrinsic:
1581           case Intrinsic::vastart:
1582           case Intrinsic::vacopy:
1583           case Intrinsic::vaend:
1584           case Intrinsic::returnaddress:
1585           case Intrinsic::frameaddress:
1586             // FIXME: should lower this ourselves
1587             // case Intrinsic::isunordered:
1588             // We directly implement these intrinsics
1589             break;
1590           case Intrinsic::readio: {
1591             // On PPC, memory operations are in-order.  Lower this intrinsic
1592             // into a volatile load.
1593             Instruction *Before = CI->getPrev();
1594             LoadInst * LI = new LoadInst(CI->getOperand(1), "", true, CI);
1595             CI->replaceAllUsesWith(LI);
1596             BB->getInstList().erase(CI);
1597             break;
1598           }
1599           case Intrinsic::writeio: {
1600             // On PPC, memory operations are in-order.  Lower this intrinsic
1601             // into a volatile store.
1602             Instruction *Before = CI->getPrev();
1603             StoreInst *SI = new StoreInst(CI->getOperand(1),
1604                                           CI->getOperand(2), true, CI);
1605             CI->replaceAllUsesWith(SI);
1606             BB->getInstList().erase(CI);
1607             break;
1608           }
1609           default:
1610             // All other intrinsic calls we must lower.
1611             Instruction *Before = CI->getPrev();
1612             TM.getIntrinsicLowering().LowerIntrinsicCall(CI);
1613             if (Before) {        // Move iterator to instruction after call
1614               I = Before; ++I;
1615             } else {
1616               I = BB->begin();
1617             }
1618           }
1619 }
1620
1621 void ISel::visitIntrinsicCall(Intrinsic::ID ID, CallInst &CI) {
1622   unsigned TmpReg1, TmpReg2, TmpReg3;
1623   switch (ID) {
1624   case Intrinsic::vastart:
1625     // Get the address of the first vararg value...
1626     TmpReg1 = getReg(CI);
1627     addFrameReference(BuildMI(BB, PPC32::ADDI, 2, TmpReg1), VarArgsFrameIndex, 
1628                       0, false);
1629     return;
1630
1631   case Intrinsic::vacopy:
1632     TmpReg1 = getReg(CI);
1633     TmpReg2 = getReg(CI.getOperand(1));
1634     BuildMI(BB, PPC32::OR, 2, TmpReg1).addReg(TmpReg2).addReg(TmpReg2);
1635     return;
1636   case Intrinsic::vaend: return;
1637
1638   case Intrinsic::returnaddress:
1639     TmpReg1 = getReg(CI);
1640     if (cast<Constant>(CI.getOperand(1))->isNullValue()) {
1641       MachineFrameInfo *MFI = F->getFrameInfo();
1642       unsigned NumBytes = MFI->getStackSize();
1643       
1644       BuildMI(BB, PPC32::LWZ, 2, TmpReg1).addSImm(NumBytes+8)
1645         .addReg(PPC32::R1);
1646     } else {
1647       // Values other than zero are not implemented yet.
1648       BuildMI(BB, PPC32::LI, 1, TmpReg1).addSImm(0);
1649     }
1650     return;
1651
1652   case Intrinsic::frameaddress:
1653     TmpReg1 = getReg(CI);
1654     if (cast<Constant>(CI.getOperand(1))->isNullValue()) {
1655       BuildMI(BB, PPC32::OR, 2, TmpReg1).addReg(PPC32::R1).addReg(PPC32::R1);
1656     } else {
1657       // Values other than zero are not implemented yet.
1658       BuildMI(BB, PPC32::LI, 1, TmpReg1).addSImm(0);
1659     }
1660     return;
1661
1662 #if 0
1663     // This may be useful for supporting isunordered
1664   case Intrinsic::isnan:
1665     // If this is only used by 'isunordered' style comparisons, don't emit it.
1666     if (isOnlyUsedByUnorderedComparisons(&CI)) return;
1667     TmpReg1 = getReg(CI.getOperand(1));
1668     emitUCOM(BB, BB->end(), TmpReg1, TmpReg1);
1669     TmpReg2 = makeAnotherReg(Type::IntTy);
1670     BuildMI(BB, PPC32::MFCR, TmpReg2);
1671     TmpReg3 = getReg(CI);
1672     BuildMI(BB, PPC32::RLWINM, 4, TmpReg3).addReg(TmpReg2).addImm(4).addImm(31).addImm(31);
1673     return;
1674 #endif
1675     
1676   default: assert(0 && "Error: unknown intrinsics should have been lowered!");
1677   }
1678 }
1679
1680 /// visitSimpleBinary - Implement simple binary operators for integral types...
1681 /// OperatorClass is one of: 0 for Add, 1 for Sub, 2 for And, 3 for Or, 4 for
1682 /// Xor.
1683 ///
1684 void ISel::visitSimpleBinary(BinaryOperator &B, unsigned OperatorClass) {
1685   unsigned DestReg = getReg(B);
1686   MachineBasicBlock::iterator MI = BB->end();
1687   Value *Op0 = B.getOperand(0), *Op1 = B.getOperand(1);
1688   unsigned Class = getClassB(B.getType());
1689
1690   emitSimpleBinaryOperation(BB, MI, Op0, Op1, OperatorClass, DestReg);
1691 }
1692
1693 /// emitBinaryFPOperation - This method handles emission of floating point
1694 /// Add (0), Sub (1), Mul (2), and Div (3) operations.
1695 void ISel::emitBinaryFPOperation(MachineBasicBlock *BB,
1696                                  MachineBasicBlock::iterator IP,
1697                                  Value *Op0, Value *Op1,
1698                                  unsigned OperatorClass, unsigned DestReg) {
1699
1700   // Special case: op Reg, <const fp>
1701   if (ConstantFP *Op1C = dyn_cast<ConstantFP>(Op1)) {
1702     // Create a constant pool entry for this constant.
1703     MachineConstantPool *CP = F->getConstantPool();
1704     unsigned CPI = CP->getConstantPoolIndex(Op1C);
1705     const Type *Ty = Op1->getType();
1706     assert(Ty == Type::FloatTy || Ty == Type::DoubleTy && "Unknown FP type!");
1707
1708     static const unsigned OpcodeTab[][4] = {
1709       { PPC32::FADDS, PPC32::FSUBS, PPC32::FMULS, PPC32::FDIVS },  // Float
1710       { PPC32::FADD,  PPC32::FSUB,  PPC32::FMUL,  PPC32::FDIV },   // Double
1711     };
1712
1713     unsigned Opcode = OpcodeTab[Ty != Type::FloatTy][OperatorClass];
1714     unsigned Op1Reg = getReg(Op1C, BB, IP);
1715     unsigned Op0r = getReg(Op0, BB, IP);
1716     BuildMI(*BB, IP, Opcode, 2, DestReg).addReg(Op0r).addReg(Op1Reg);
1717     return;
1718   }
1719   
1720   // Special case: R1 = op <const fp>, R2
1721   if (ConstantFP *Op0C = dyn_cast<ConstantFP>(Op0))
1722     if (Op0C->isExactlyValue(-0.0) && OperatorClass == 1) {
1723       // -0.0 - X === -X
1724       unsigned op1Reg = getReg(Op1, BB, IP);
1725       BuildMI(*BB, IP, PPC32::FNEG, 1, DestReg).addReg(op1Reg);
1726       return;
1727     } else {
1728       // R1 = op CST, R2  -->  R1 = opr R2, CST
1729
1730       // Create a constant pool entry for this constant.
1731       MachineConstantPool *CP = F->getConstantPool();
1732       unsigned CPI = CP->getConstantPoolIndex(Op0C);
1733       const Type *Ty = Op0C->getType();
1734       assert(Ty == Type::FloatTy || Ty == Type::DoubleTy && "Unknown FP type!");
1735
1736       static const unsigned OpcodeTab[][4] = {
1737         { PPC32::FADDS, PPC32::FSUBS, PPC32::FMULS, PPC32::FDIVS },  // Float
1738         { PPC32::FADD,  PPC32::FSUB,  PPC32::FMUL,  PPC32::FDIV },   // Double
1739       };
1740
1741       unsigned Opcode = OpcodeTab[Ty != Type::FloatTy][OperatorClass];
1742       unsigned Op0Reg = getReg(Op0C, BB, IP);
1743       unsigned Op1Reg = getReg(Op1, BB, IP);
1744       BuildMI(*BB, IP, Opcode, 2, DestReg).addReg(Op0Reg).addReg(Op1Reg);
1745       return;
1746     }
1747
1748   // General case.
1749   static const unsigned OpcodeTab[] = {
1750     PPC32::FADD, PPC32::FSUB, PPC32::FMUL, PPC32::FDIV
1751   };
1752
1753   unsigned Opcode = OpcodeTab[OperatorClass];
1754   unsigned Op0r = getReg(Op0, BB, IP);
1755   unsigned Op1r = getReg(Op1, BB, IP);
1756   BuildMI(*BB, IP, Opcode, 2, DestReg).addReg(Op0r).addReg(Op1r);
1757 }
1758
1759 /// emitSimpleBinaryOperation - Implement simple binary operators for integral
1760 /// types...  OperatorClass is one of: 0 for Add, 1 for Sub, 2 for And, 3 for
1761 /// Or, 4 for Xor.
1762 ///
1763 /// emitSimpleBinaryOperation - Common code shared between visitSimpleBinary
1764 /// and constant expression support.
1765 ///
1766 void ISel::emitSimpleBinaryOperation(MachineBasicBlock *MBB,
1767                                      MachineBasicBlock::iterator IP,
1768                                      Value *Op0, Value *Op1,
1769                                      unsigned OperatorClass, unsigned DestReg) {
1770   unsigned Class = getClassB(Op0->getType());
1771
1772   // Arithmetic and Bitwise operators
1773   static const unsigned OpcodeTab[] = {
1774     PPC32::ADD, PPC32::SUB, PPC32::AND, PPC32::OR, PPC32::XOR
1775   };
1776   static const unsigned ImmOpcodeTab[] = {
1777     PPC32::ADDI, PPC32::SUBI, PPC32::ANDIo, PPC32::ORI, PPC32::XORI
1778   };
1779
1780   // Otherwise, code generate the full operation with a constant.
1781   static const unsigned BottomTab[] = {
1782     PPC32::ADDC, PPC32::SUBC, PPC32::AND, PPC32::OR, PPC32::XOR
1783   };
1784   static const unsigned TopTab[] = {
1785     PPC32::ADDE, PPC32::SUBFE, PPC32::AND, PPC32::OR, PPC32::XOR
1786   };
1787   
1788   if (Class == cFP32 || Class == cFP64) {
1789     assert(OperatorClass < 2 && "No logical ops for FP!");
1790     emitBinaryFPOperation(MBB, IP, Op0, Op1, OperatorClass, DestReg);
1791     return;
1792   }
1793
1794   if (Op0->getType() == Type::BoolTy) {
1795     if (OperatorClass == 3)
1796       // If this is an or of two isnan's, emit an FP comparison directly instead
1797       // of or'ing two isnan's together.
1798       if (Value *LHS = dyncastIsNan(Op0))
1799         if (Value *RHS = dyncastIsNan(Op1)) {
1800           unsigned Op0Reg = getReg(RHS, MBB, IP), Op1Reg = getReg(LHS, MBB, IP);
1801           unsigned TmpReg = makeAnotherReg(Type::IntTy);
1802           emitUCOM(MBB, IP, Op0Reg, Op1Reg);
1803           BuildMI(*MBB, IP, PPC32::MFCR, TmpReg);
1804           BuildMI(*MBB, IP, PPC32::RLWINM, 4, DestReg).addReg(TmpReg).addImm(4)
1805             .addImm(31).addImm(31);
1806           return;
1807         }
1808   }
1809
1810   // sub 0, X -> neg X
1811   if (ConstantInt *CI = dyn_cast<ConstantInt>(Op0)) {
1812     if (OperatorClass == 1 && CI->isNullValue()) {
1813       unsigned Op1r = getReg(Op1, MBB, IP);
1814
1815       if (Class == cLong) {
1816         BuildMI(*MBB, IP, PPC32::SUBFIC, 2, DestReg+1).addReg(Op1r+1).addSImm(0);
1817         BuildMI(*MBB, IP, PPC32::SUBFZE, 1, DestReg).addReg(Op1r);
1818       } else {
1819         BuildMI(*MBB, IP, PPC32::NEG, 1, DestReg).addReg(Op1r);
1820       }
1821       return;
1822     }
1823   }
1824
1825   // Special case: op Reg, <const int>
1826   if (ConstantInt *Op1C = dyn_cast<ConstantInt>(Op1)) {
1827     unsigned Op0r = getReg(Op0, MBB, IP);
1828
1829     // xor X, -1 -> not X
1830     if (OperatorClass == 4 && Op1C->isAllOnesValue()) {
1831       BuildMI(*MBB, IP, PPC32::NOR, 2, DestReg).addReg(Op0r).addReg(Op0r);
1832       if (Class == cLong)  // Invert the low part too
1833         BuildMI(*MBB, IP, PPC32::NOR, 2, DestReg+1).addReg(Op0r+1)
1834           .addReg(Op0r+1);
1835       return;
1836     }
1837     
1838     // FIXME: We're not handling ANDI right now since it could trash the CR
1839     if (Class != cLong) {
1840       if (canUseAsImmediateForOpcode(Op1C, OperatorClass)) {
1841         int immediate = Op1C->getRawValue() & 0xFFFF;
1842         
1843         if (OperatorClass < 2)
1844           BuildMI(*MBB, IP, ImmOpcodeTab[OperatorClass], 2, DestReg).addReg(Op0r)
1845             .addSImm(immediate);
1846         else
1847           BuildMI(*MBB, IP, ImmOpcodeTab[OperatorClass], 2, DestReg).addReg(Op0r)
1848             .addZImm(immediate);
1849       } else {
1850         unsigned Op1r = getReg(Op1, MBB, IP);
1851         BuildMI(*MBB, IP, OpcodeTab[OperatorClass], 2, DestReg).addReg(Op0r)
1852           .addReg(Op1r);
1853       }
1854       return;
1855     }
1856
1857     unsigned Op1r = getReg(Op1, MBB, IP);
1858
1859     BuildMI(*MBB, IP, BottomTab[OperatorClass], 2, DestReg+1).addReg(Op0r+1)
1860       .addReg(Op1r+1);
1861     BuildMI(*MBB, IP, TopTab[OperatorClass], 2, DestReg).addReg(Op0r)
1862       .addReg(Op1r);
1863     return;
1864   }
1865
1866   unsigned Op0r = getReg(Op0, MBB, IP);
1867   unsigned Op1r = getReg(Op1, MBB, IP);
1868
1869   if (Class != cLong) {
1870     unsigned Opcode = OpcodeTab[OperatorClass];
1871     BuildMI(*MBB, IP, Opcode, 2, DestReg).addReg(Op0r).addReg(Op1r);
1872   } else {
1873     BuildMI(*MBB, IP, BottomTab[OperatorClass], 2, DestReg+1).addReg(Op0r+1)
1874       .addReg(Op1r+1);
1875     BuildMI(*MBB, IP, TopTab[OperatorClass], 2, DestReg).addReg(Op0r)
1876       .addReg(Op1r);
1877   }
1878   return;
1879 }
1880
1881 // ExactLog2 - This function solves for (Val == 1 << (N-1)) and returns N.  It
1882 // returns zero when the input is not exactly a power of two.
1883 static unsigned ExactLog2(unsigned Val) {
1884   if (Val == 0 || (Val & (Val-1))) return 0;
1885   unsigned Count = 0;
1886   while (Val != 1) {
1887     Val >>= 1;
1888     ++Count;
1889   }
1890   return Count;
1891 }
1892
1893 /// doMultiply - Emit appropriate instructions to multiply together the
1894 /// Values Op0 and Op1, and put the result in DestReg.
1895 ///
1896 void ISel::doMultiply(MachineBasicBlock *MBB,
1897                       MachineBasicBlock::iterator IP,
1898                       unsigned DestReg, Value *Op0, Value *Op1) {
1899   unsigned Class0 = getClass(Op0->getType());
1900   unsigned Class1 = getClass(Op1->getType());
1901   
1902   unsigned Op0r = getReg(Op0, MBB, IP);
1903   unsigned Op1r = getReg(Op1, MBB, IP);
1904   
1905   // 64 x 64 -> 64
1906   if (Class0 == cLong && Class1 == cLong) {
1907     unsigned Tmp1 = makeAnotherReg(Type::IntTy);
1908     unsigned Tmp2 = makeAnotherReg(Type::IntTy);
1909     unsigned Tmp3 = makeAnotherReg(Type::IntTy);
1910     unsigned Tmp4 = makeAnotherReg(Type::IntTy);
1911     BuildMI(*MBB, IP, PPC32::MULHWU, 2, Tmp1).addReg(Op0r+1).addReg(Op1r+1);
1912     BuildMI(*MBB, IP, PPC32::MULLW, 2, DestReg+1).addReg(Op0r+1).addReg(Op1r+1);
1913     BuildMI(*MBB, IP, PPC32::MULLW, 2, Tmp2).addReg(Op0r+1).addReg(Op1r);
1914     BuildMI(*MBB, IP, PPC32::ADD, 2, Tmp3).addReg(Tmp1).addReg(Tmp2);
1915     BuildMI(*MBB, IP, PPC32::MULLW, 2, Tmp4).addReg(Op0r).addReg(Op1r+1);
1916     BuildMI(*MBB, IP, PPC32::ADD, 2, DestReg).addReg(Tmp3).addReg(Tmp4);
1917     return;
1918   }
1919   
1920   // 64 x 32 or less, promote 32 to 64 and do a 64 x 64
1921   if (Class0 == cLong && Class1 <= cInt) {
1922     unsigned Tmp0 = makeAnotherReg(Type::IntTy);
1923     unsigned Tmp1 = makeAnotherReg(Type::IntTy);
1924     unsigned Tmp2 = makeAnotherReg(Type::IntTy);
1925     unsigned Tmp3 = makeAnotherReg(Type::IntTy);
1926     unsigned Tmp4 = makeAnotherReg(Type::IntTy);
1927     if (Op1->getType()->isSigned())
1928       BuildMI(*MBB, IP, PPC32::SRAWI, 2, Tmp0).addReg(Op1r).addImm(31);
1929     else
1930       BuildMI(*MBB, IP, PPC32::LI, 2, Tmp0).addSImm(0);
1931     BuildMI(*MBB, IP, PPC32::MULHWU, 2, Tmp1).addReg(Op0r+1).addReg(Op1r);
1932     BuildMI(*MBB, IP, PPC32::MULLW, 2, DestReg+1).addReg(Op0r+1).addReg(Op1r);
1933     BuildMI(*MBB, IP, PPC32::MULLW, 2, Tmp2).addReg(Op0r+1).addReg(Tmp0);
1934     BuildMI(*MBB, IP, PPC32::ADD, 2, Tmp3).addReg(Tmp1).addReg(Tmp2);
1935     BuildMI(*MBB, IP, PPC32::MULLW, 2, Tmp4).addReg(Op0r).addReg(Op1r);
1936     BuildMI(*MBB, IP, PPC32::ADD, 2, DestReg).addReg(Tmp3).addReg(Tmp4);
1937     return;
1938   }
1939   
1940   // 32 x 32 -> 32
1941   if (Class0 <= cInt && Class1 <= cInt) {
1942     BuildMI(*MBB, IP, PPC32::MULLW, 2, DestReg).addReg(Op0r).addReg(Op1r);
1943     return;
1944   }
1945   
1946   assert(0 && "doMultiply cannot operate on unknown type!");
1947 }
1948
1949 /// doMultiplyConst - This method will multiply the value in Op0 by the
1950 /// value of the ContantInt *CI
1951 void ISel::doMultiplyConst(MachineBasicBlock *MBB,
1952                            MachineBasicBlock::iterator IP,
1953                            unsigned DestReg, Value *Op0, ConstantInt *CI) {
1954   unsigned Class = getClass(Op0->getType());
1955
1956   // Mul op0, 0 ==> 0
1957   if (CI->isNullValue()) {
1958     BuildMI(*MBB, IP, PPC32::LI, 1, DestReg).addSImm(0);
1959     if (Class == cLong)
1960       BuildMI(*MBB, IP, PPC32::LI, 1, DestReg+1).addSImm(0);
1961     return;
1962   }
1963   
1964   // Mul op0, 1 ==> op0
1965   if (CI->equalsInt(1)) {
1966     unsigned Op0r = getReg(Op0, MBB, IP);
1967     BuildMI(*MBB, IP, PPC32::OR, 2, DestReg).addReg(Op0r).addReg(Op0r);
1968     if (Class == cLong)
1969       BuildMI(*MBB, IP, PPC32::OR, 2, DestReg+1).addReg(Op0r+1).addReg(Op0r+1);
1970     return;
1971   }
1972
1973   // If the element size is exactly a power of 2, use a shift to get it.
1974   if (unsigned Shift = ExactLog2(CI->getRawValue())) {
1975     ConstantUInt *ShiftCI = ConstantUInt::get(Type::UByteTy, Shift);
1976     emitShiftOperation(MBB, IP, Op0, ShiftCI, true, Op0->getType(), DestReg);
1977     return;
1978   }
1979   
1980   // If 32 bits or less and immediate is in right range, emit mul by immediate
1981   if (Class == cByte || Class == cShort || Class == cInt)
1982   {
1983     if (canUseAsImmediateForOpcode(CI, 0)) {
1984       unsigned Op0r = getReg(Op0, MBB, IP);
1985       unsigned imm = CI->getRawValue() & 0xFFFF;
1986       BuildMI(*MBB, IP, PPC32::MULLI, 2, DestReg).addReg(Op0r).addSImm(imm);
1987       return;
1988     }
1989   }
1990   
1991   doMultiply(MBB, IP, DestReg, Op0, CI);
1992 }
1993
1994 void ISel::visitMul(BinaryOperator &I) {
1995   unsigned ResultReg = getReg(I);
1996
1997   Value *Op0 = I.getOperand(0);
1998   Value *Op1 = I.getOperand(1);
1999
2000   MachineBasicBlock::iterator IP = BB->end();
2001   emitMultiply(BB, IP, Op0, Op1, ResultReg);
2002 }
2003
2004 void ISel::emitMultiply(MachineBasicBlock *MBB, MachineBasicBlock::iterator IP,
2005                         Value *Op0, Value *Op1, unsigned DestReg) {
2006   TypeClass Class = getClass(Op0->getType());
2007
2008   switch (Class) {
2009   case cByte:
2010   case cShort:
2011   case cInt:
2012   case cLong:
2013     if (ConstantInt *CI = dyn_cast<ConstantInt>(Op1)) {
2014       doMultiplyConst(MBB, IP, DestReg, Op0, CI);
2015     } else {
2016       doMultiply(MBB, IP, DestReg, Op0, Op1);
2017     }
2018     return;
2019   case cFP32:
2020   case cFP64:
2021     emitBinaryFPOperation(MBB, IP, Op0, Op1, 2, DestReg);
2022     return;
2023     break;
2024   }
2025 }
2026
2027
2028 /// visitDivRem - Handle division and remainder instructions... these
2029 /// instruction both require the same instructions to be generated, they just
2030 /// select the result from a different register.  Note that both of these
2031 /// instructions work differently for signed and unsigned operands.
2032 ///
2033 void ISel::visitDivRem(BinaryOperator &I) {
2034   unsigned ResultReg = getReg(I);
2035   Value *Op0 = I.getOperand(0), *Op1 = I.getOperand(1);
2036
2037   MachineBasicBlock::iterator IP = BB->end();
2038   emitDivRemOperation(BB, IP, Op0, Op1, I.getOpcode() == Instruction::Div,
2039                       ResultReg);
2040 }
2041
2042 void ISel::emitDivRemOperation(MachineBasicBlock *BB,
2043                                MachineBasicBlock::iterator IP,
2044                                Value *Op0, Value *Op1, bool isDiv,
2045                                unsigned ResultReg) {
2046   const Type *Ty = Op0->getType();
2047   unsigned Class = getClass(Ty);
2048   switch (Class) {
2049   case cFP32:
2050     if (isDiv) {
2051       // Floating point divide...
2052       emitBinaryFPOperation(BB, IP, Op0, Op1, 3, ResultReg);
2053       return;
2054     } else {
2055       // Floating point remainder via fmodf(float x, float y);
2056       unsigned Op0Reg = getReg(Op0, BB, IP);
2057       unsigned Op1Reg = getReg(Op1, BB, IP);
2058       MachineInstr *TheCall =
2059         BuildMI(PPC32::CALLpcrel, 1).addGlobalAddress(fmodfFn, true);
2060       std::vector<ValueRecord> Args;
2061       Args.push_back(ValueRecord(Op0Reg, Type::FloatTy));
2062       Args.push_back(ValueRecord(Op1Reg, Type::FloatTy));
2063       doCall(ValueRecord(ResultReg, Type::FloatTy), TheCall, Args, false);
2064     }
2065     return;
2066   case cFP64:
2067     if (isDiv) {
2068       // Floating point divide...
2069       emitBinaryFPOperation(BB, IP, Op0, Op1, 3, ResultReg);
2070       return;
2071     } else {               
2072       // Floating point remainder via fmod(double x, double y);
2073       unsigned Op0Reg = getReg(Op0, BB, IP);
2074       unsigned Op1Reg = getReg(Op1, BB, IP);
2075       MachineInstr *TheCall =
2076         BuildMI(PPC32::CALLpcrel, 1).addGlobalAddress(fmodFn, true);
2077       std::vector<ValueRecord> Args;
2078       Args.push_back(ValueRecord(Op0Reg, Type::DoubleTy));
2079       Args.push_back(ValueRecord(Op1Reg, Type::DoubleTy));
2080       doCall(ValueRecord(ResultReg, Type::DoubleTy), TheCall, Args, false);
2081     }
2082     return;
2083   case cLong: {
2084     static Function* const Funcs[] =
2085       { __moddi3Fn, __divdi3Fn, __umoddi3Fn, __udivdi3Fn };
2086     unsigned Op0Reg = getReg(Op0, BB, IP);
2087     unsigned Op1Reg = getReg(Op1, BB, IP);
2088     unsigned NameIdx = Ty->isUnsigned()*2 + isDiv;
2089     MachineInstr *TheCall =
2090       BuildMI(PPC32::CALLpcrel, 1).addGlobalAddress(Funcs[NameIdx], true);
2091
2092     std::vector<ValueRecord> Args;
2093     Args.push_back(ValueRecord(Op0Reg, Type::LongTy));
2094     Args.push_back(ValueRecord(Op1Reg, Type::LongTy));
2095     doCall(ValueRecord(ResultReg, Type::LongTy), TheCall, Args, false);
2096     return;
2097   }
2098   case cByte: case cShort: case cInt:
2099     break;          // Small integrals, handled below...
2100   default: assert(0 && "Unknown class!");
2101   }
2102
2103   // Special case signed division by power of 2.
2104   if (isDiv)
2105     if (ConstantSInt *CI = dyn_cast<ConstantSInt>(Op1)) {
2106       assert(Class != cLong && "This doesn't handle 64-bit divides!");
2107       int V = CI->getValue();
2108
2109       if (V == 1) {       // X /s 1 => X
2110         unsigned Op0Reg = getReg(Op0, BB, IP);
2111         BuildMI(*BB, IP, PPC32::OR, 2, ResultReg).addReg(Op0Reg).addReg(Op0Reg);
2112         return;
2113       }
2114
2115       if (V == -1) {      // X /s -1 => -X
2116         unsigned Op0Reg = getReg(Op0, BB, IP);
2117         BuildMI(*BB, IP, PPC32::NEG, 1, ResultReg).addReg(Op0Reg);
2118         return;
2119       }
2120
2121       unsigned log2V = ExactLog2(V);
2122       if (log2V != 0 && Ty->isSigned()) {
2123         unsigned Op0Reg = getReg(Op0, BB, IP);
2124         unsigned TmpReg = makeAnotherReg(Op0->getType());
2125         
2126         BuildMI(*BB, IP, PPC32::SRAWI, 2, TmpReg).addReg(Op0Reg).addImm(log2V);
2127         BuildMI(*BB, IP, PPC32::ADDZE, 1, ResultReg).addReg(TmpReg);
2128         return;
2129       }
2130     }
2131
2132   unsigned Op0Reg = getReg(Op0, BB, IP);
2133   unsigned Op1Reg = getReg(Op1, BB, IP);
2134   unsigned Opcode = Ty->isSigned() ? PPC32::DIVW : PPC32::DIVWU;
2135   
2136   if (isDiv) {
2137     BuildMI(*BB, IP, Opcode, 2, ResultReg).addReg(Op0Reg).addReg(Op1Reg);
2138   } else { // Remainder
2139     unsigned TmpReg1 = makeAnotherReg(Op0->getType());
2140     unsigned TmpReg2 = makeAnotherReg(Op0->getType());
2141     
2142     BuildMI(*BB, IP, Opcode, 2, TmpReg1).addReg(Op0Reg).addReg(Op1Reg);
2143     BuildMI(*BB, IP, PPC32::MULLW, 2, TmpReg2).addReg(TmpReg1).addReg(Op1Reg);
2144     BuildMI(*BB, IP, PPC32::SUBF, 2, ResultReg).addReg(TmpReg2).addReg(Op0Reg);
2145   }
2146 }
2147
2148
2149 /// Shift instructions: 'shl', 'sar', 'shr' - Some special cases here
2150 /// for constant immediate shift values, and for constant immediate
2151 /// shift values equal to 1. Even the general case is sort of special,
2152 /// because the shift amount has to be in CL, not just any old register.
2153 ///
2154 void ISel::visitShiftInst(ShiftInst &I) {
2155   MachineBasicBlock::iterator IP = BB->end ();
2156   emitShiftOperation(BB, IP, I.getOperand (0), I.getOperand (1),
2157                      I.getOpcode () == Instruction::Shl, I.getType (),
2158                      getReg (I));
2159 }
2160
2161 /// emitShiftOperation - Common code shared between visitShiftInst and
2162 /// constant expression support.
2163 ///
2164 void ISel::emitShiftOperation(MachineBasicBlock *MBB,
2165                               MachineBasicBlock::iterator IP,
2166                               Value *Op, Value *ShiftAmount, bool isLeftShift,
2167                               const Type *ResultTy, unsigned DestReg) {
2168   unsigned SrcReg = getReg (Op, MBB, IP);
2169   bool isSigned = ResultTy->isSigned ();
2170   unsigned Class = getClass (ResultTy);
2171   
2172   // Longs, as usual, are handled specially...
2173   if (Class == cLong) {
2174     // If we have a constant shift, we can generate much more efficient code
2175     // than otherwise...
2176     //
2177     if (ConstantUInt *CUI = dyn_cast<ConstantUInt>(ShiftAmount)) {
2178       unsigned Amount = CUI->getValue();
2179       if (Amount < 32) {
2180         if (isLeftShift) {
2181           // FIXME: RLWIMI is a use-and-def of DestReg+1, but that violates SSA
2182           BuildMI(*MBB, IP, PPC32::RLWINM, 4, DestReg).addReg(SrcReg)
2183             .addImm(Amount).addImm(0).addImm(31-Amount);
2184           BuildMI(*MBB, IP, PPC32::RLWIMI, 5).addReg(DestReg).addReg(SrcReg+1)
2185             .addImm(Amount).addImm(32-Amount).addImm(31);
2186           BuildMI(*MBB, IP, PPC32::RLWINM, 4, DestReg+1).addReg(SrcReg+1)
2187             .addImm(Amount).addImm(0).addImm(31-Amount);
2188         } else {
2189           // FIXME: RLWIMI is a use-and-def of DestReg, but that violates SSA
2190           BuildMI(*MBB, IP, PPC32::RLWINM, 4, DestReg+1).addReg(SrcReg+1)
2191             .addImm(32-Amount).addImm(Amount).addImm(31);
2192           BuildMI(*MBB, IP, PPC32::RLWIMI, 5).addReg(DestReg+1).addReg(SrcReg)
2193             .addImm(32-Amount).addImm(0).addImm(Amount-1);
2194           BuildMI(*MBB, IP, PPC32::RLWINM, 4, DestReg).addReg(SrcReg)
2195             .addImm(32-Amount).addImm(Amount).addImm(31);
2196         }
2197       } else {                 // Shifting more than 32 bits
2198         Amount -= 32;
2199         if (isLeftShift) {
2200           if (Amount != 0) {
2201             BuildMI(*MBB, IP, PPC32::RLWINM, 4, DestReg).addReg(SrcReg+1)
2202               .addImm(Amount).addImm(0).addImm(31-Amount);
2203           } else {
2204             BuildMI(*MBB, IP, PPC32::OR, 2, DestReg).addReg(SrcReg+1)
2205               .addReg(SrcReg+1);
2206           }
2207           BuildMI(*MBB, IP, PPC32::LI, 1, DestReg+1).addSImm(0);
2208         } else {
2209           if (Amount != 0) {
2210             if (isSigned)
2211               BuildMI(*MBB, IP, PPC32::SRAWI, 2, DestReg+1).addReg(SrcReg)
2212                 .addImm(Amount);
2213             else
2214               BuildMI(*MBB, IP, PPC32::RLWINM, 4, DestReg+1).addReg(SrcReg)
2215                 .addImm(32-Amount).addImm(Amount).addImm(31);
2216           } else {
2217             BuildMI(*MBB, IP, PPC32::OR, 2, DestReg+1).addReg(SrcReg)
2218               .addReg(SrcReg);
2219           }
2220           BuildMI(*MBB, IP,PPC32::LI, 1, DestReg).addSImm(0);
2221         }
2222       }
2223     } else {
2224       unsigned TmpReg1 = makeAnotherReg(Type::IntTy);
2225       unsigned TmpReg2 = makeAnotherReg(Type::IntTy);
2226       unsigned TmpReg3 = makeAnotherReg(Type::IntTy);
2227       unsigned TmpReg4 = makeAnotherReg(Type::IntTy);
2228       unsigned TmpReg5 = makeAnotherReg(Type::IntTy);
2229       unsigned TmpReg6 = makeAnotherReg(Type::IntTy);
2230       unsigned ShiftAmountReg = getReg (ShiftAmount, MBB, IP);
2231       
2232       if (isLeftShift) {
2233         BuildMI(*MBB, IP, PPC32::SUBFIC, 2, TmpReg1).addReg(ShiftAmountReg)
2234           .addSImm(32);
2235         BuildMI(*MBB, IP, PPC32::SLW, 2, TmpReg2).addReg(SrcReg)
2236           .addReg(ShiftAmountReg);
2237         BuildMI(*MBB, IP, PPC32::SRW, 2, TmpReg3).addReg(SrcReg+1).addReg(TmpReg1);
2238         BuildMI(*MBB, IP, PPC32::OR, 2, TmpReg4).addReg(TmpReg2).addReg(TmpReg3);
2239         BuildMI(*MBB, IP, PPC32::ADDI, 2, TmpReg5).addReg(ShiftAmountReg)
2240           .addSImm(-32);
2241         BuildMI(*MBB, IP, PPC32::SLW, 2, TmpReg6).addReg(SrcReg+1).addReg(TmpReg5);
2242         BuildMI(*MBB, IP, PPC32::OR, 2, DestReg).addReg(TmpReg4)
2243           .addReg(TmpReg6);
2244         BuildMI(*MBB, IP, PPC32::SLW, 2, DestReg+1).addReg(SrcReg+1)
2245           .addReg(ShiftAmountReg);
2246       } else {
2247         if (isSigned) {
2248           // FIXME: Unimplemented
2249           // Page C-3 of the PowerPC 32bit Programming Environments Manual
2250           std::cerr << "Unimplemented: signed right shift\n";
2251           abort();
2252         } else {
2253           BuildMI(*MBB, IP, PPC32::SUBFIC, 2, TmpReg1).addReg(ShiftAmountReg)
2254             .addSImm(32);
2255           BuildMI(*MBB, IP, PPC32::SRW, 2, TmpReg2).addReg(SrcReg+1)
2256             .addReg(ShiftAmountReg);
2257           BuildMI(*MBB, IP, PPC32::SLW, 2, TmpReg3).addReg(SrcReg)
2258             .addReg(TmpReg1);
2259           BuildMI(*MBB, IP, PPC32::OR, 2, TmpReg4).addReg(TmpReg2)
2260             .addReg(TmpReg3);
2261           BuildMI(*MBB, IP, PPC32::ADDI, 2, TmpReg5).addReg(ShiftAmountReg)
2262             .addSImm(-32);
2263           BuildMI(*MBB, IP, PPC32::SRW, 2, TmpReg6).addReg(SrcReg)
2264             .addReg(TmpReg5);
2265           BuildMI(*MBB, IP, PPC32::OR, 2, DestReg+1).addReg(TmpReg4)
2266             .addReg(TmpReg6);
2267           BuildMI(*MBB, IP, PPC32::SRW, 2, DestReg).addReg(SrcReg)
2268             .addReg(ShiftAmountReg);
2269         }
2270       }
2271     }
2272     return;
2273   }
2274
2275   if (ConstantUInt *CUI = dyn_cast<ConstantUInt>(ShiftAmount)) {
2276     // The shift amount is constant, guaranteed to be a ubyte. Get its value.
2277     assert(CUI->getType() == Type::UByteTy && "Shift amount not a ubyte?");
2278     unsigned Amount = CUI->getValue();
2279
2280     if (isLeftShift) {
2281       BuildMI(*MBB, IP, PPC32::RLWINM, 4, DestReg).addReg(SrcReg)
2282         .addImm(Amount).addImm(0).addImm(31-Amount);
2283     } else {
2284       if (isSigned) {
2285         BuildMI(*MBB, IP, PPC32::SRAWI,2,DestReg).addReg(SrcReg).addImm(Amount);
2286       } else {
2287         BuildMI(*MBB, IP, PPC32::RLWINM, 4, DestReg).addReg(SrcReg)
2288           .addImm(32-Amount).addImm(Amount).addImm(31);
2289       }
2290     }
2291   } else {                  // The shift amount is non-constant.
2292     unsigned ShiftAmountReg = getReg (ShiftAmount, MBB, IP);
2293
2294     if (isLeftShift) {
2295       BuildMI(*MBB, IP, PPC32::SLW, 2, DestReg).addReg(SrcReg)
2296         .addReg(ShiftAmountReg);
2297     } else {
2298       BuildMI(*MBB, IP, isSigned ? PPC32::SRAW : PPC32::SRW, 2, DestReg)
2299         .addReg(SrcReg).addReg(ShiftAmountReg);
2300     }
2301   }
2302 }
2303
2304
2305 /// visitLoadInst - Implement LLVM load instructions
2306 ///
2307 void ISel::visitLoadInst(LoadInst &I) {
2308   static const unsigned Opcodes[] = { 
2309     PPC32::LBZ, PPC32::LHZ, PPC32::LWZ, PPC32::LFS 
2310   };
2311   unsigned Class = getClassB(I.getType());
2312   unsigned Opcode = Opcodes[Class];
2313   if (I.getType() == Type::DoubleTy) Opcode = PPC32::LFD;
2314
2315   unsigned DestReg = getReg(I);
2316
2317   if (AllocaInst *AI = dyn_castFixedAlloca(I.getOperand(0))) {
2318     unsigned FI = getFixedSizedAllocaFI(AI);
2319     if (Class == cLong) {
2320       addFrameReference(BuildMI(BB, PPC32::LWZ, 2, DestReg), FI);
2321       addFrameReference(BuildMI(BB, PPC32::LWZ, 2, DestReg+1), FI, 4);
2322     } else {
2323       addFrameReference(BuildMI(BB, Opcode, 2, DestReg), FI);
2324     }
2325   } else {
2326     unsigned SrcAddrReg = getReg(I.getOperand(0));
2327     
2328     if (Class == cLong) {
2329       BuildMI(BB, PPC32::LWZ, 2, DestReg).addSImm(0).addReg(SrcAddrReg);
2330       BuildMI(BB, PPC32::LWZ, 2, DestReg+1).addSImm(4).addReg(SrcAddrReg);
2331     } else {
2332       BuildMI(BB, Opcode, 2, DestReg).addSImm(0).addReg(SrcAddrReg);
2333     }
2334   }
2335 }
2336
2337 /// visitStoreInst - Implement LLVM store instructions
2338 ///
2339 void ISel::visitStoreInst(StoreInst &I) {
2340   unsigned ValReg      = getReg(I.getOperand(0));
2341   unsigned AddressReg  = getReg(I.getOperand(1));
2342  
2343   const Type *ValTy = I.getOperand(0)->getType();
2344   unsigned Class = getClassB(ValTy);
2345
2346   if (Class == cLong) {
2347     BuildMI(BB, PPC32::STW, 3).addReg(ValReg).addSImm(0).addReg(AddressReg);
2348     BuildMI(BB, PPC32::STW, 3).addReg(ValReg+1).addSImm(4).addReg(AddressReg);
2349     return;
2350   }
2351
2352   static const unsigned Opcodes[] = {
2353     PPC32::STB, PPC32::STH, PPC32::STW, PPC32::STFS
2354   };
2355   unsigned Opcode = Opcodes[Class];
2356   if (ValTy == Type::DoubleTy) Opcode = PPC32::STFD;
2357   BuildMI(BB, Opcode, 3).addReg(ValReg).addSImm(0).addReg(AddressReg);
2358 }
2359
2360
2361 /// visitCastInst - Here we have various kinds of copying with or without sign
2362 /// extension going on.
2363 ///
2364 void ISel::visitCastInst(CastInst &CI) {
2365   Value *Op = CI.getOperand(0);
2366
2367   unsigned SrcClass = getClassB(Op->getType());
2368   unsigned DestClass = getClassB(CI.getType());
2369   // Noop casts are not emitted: getReg will return the source operand as the
2370   // register to use for any uses of the noop cast.
2371   if (DestClass == SrcClass)
2372     return;
2373
2374   // If this is a cast from a 32-bit integer to a Long type, and the only uses
2375   // of the case are GEP instructions, then the cast does not need to be
2376   // generated explicitly, it will be folded into the GEP.
2377   if (DestClass == cLong && SrcClass == cInt) {
2378     bool AllUsesAreGEPs = true;
2379     for (Value::use_iterator I = CI.use_begin(), E = CI.use_end(); I != E; ++I)
2380       if (!isa<GetElementPtrInst>(*I)) {
2381         AllUsesAreGEPs = false;
2382         break;
2383       }        
2384
2385     // No need to codegen this cast if all users are getelementptr instrs...
2386     if (AllUsesAreGEPs) return;
2387   }
2388
2389   unsigned DestReg = getReg(CI);
2390   MachineBasicBlock::iterator MI = BB->end();
2391   emitCastOperation(BB, MI, Op, CI.getType(), DestReg);
2392 }
2393
2394 /// emitCastOperation - Common code shared between visitCastInst and constant
2395 /// expression cast support.
2396 ///
2397 void ISel::emitCastOperation(MachineBasicBlock *MBB,
2398                              MachineBasicBlock::iterator IP,
2399                              Value *Src, const Type *DestTy,
2400                              unsigned DestReg) {
2401   const Type *SrcTy = Src->getType();
2402   unsigned SrcClass = getClassB(SrcTy);
2403   unsigned DestClass = getClassB(DestTy);
2404   unsigned SrcReg = getReg(Src, MBB, IP);
2405
2406   // Implement casts to bool by using compare on the operand followed by set if
2407   // not zero on the result.
2408   if (DestTy == Type::BoolTy) {
2409     switch (SrcClass) {
2410     case cByte:
2411     case cShort:
2412     case cInt: {
2413       unsigned TmpReg = makeAnotherReg(Type::IntTy);
2414       BuildMI(*MBB, IP, PPC32::ADDIC, 2, TmpReg).addReg(SrcReg).addSImm(-1);
2415       BuildMI(*MBB, IP, PPC32::SUBFE, 2, DestReg).addReg(TmpReg).addReg(SrcReg);
2416       break;
2417     }
2418     case cLong: {
2419       unsigned TmpReg = makeAnotherReg(Type::IntTy);
2420       unsigned SrcReg2 = makeAnotherReg(Type::IntTy);
2421       BuildMI(*MBB, IP, PPC32::OR, 2, SrcReg2).addReg(SrcReg).addReg(SrcReg+1);
2422       BuildMI(*MBB, IP, PPC32::ADDIC, 2, TmpReg).addReg(SrcReg2).addSImm(-1);
2423       BuildMI(*MBB, IP, PPC32::SUBFE, 2, DestReg).addReg(TmpReg)
2424         .addReg(SrcReg2);
2425       break;
2426     }
2427     case cFP32:
2428     case cFP64:
2429       // FSEL perhaps?
2430       std::cerr << "Cast fp-to-bool not implemented!";
2431       abort();
2432     }
2433     return;
2434   }
2435
2436   // Implement casts between values of the same type class (as determined by
2437   // getClass) by using a register-to-register move.
2438   if (SrcClass == DestClass) {
2439     if (SrcClass <= cInt) {
2440       BuildMI(*MBB, IP, PPC32::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
2441     } else if (SrcClass == cFP32 || SrcClass == cFP64) {
2442       BuildMI(*MBB, IP, PPC32::FMR, 1, DestReg).addReg(SrcReg);
2443     } else if (SrcClass == cLong) {
2444       BuildMI(*MBB, IP, PPC32::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
2445       BuildMI(*MBB, IP, PPC32::OR, 2, DestReg+1).addReg(SrcReg+1)
2446         .addReg(SrcReg+1);
2447     } else {
2448       assert(0 && "Cannot handle this type of cast instruction!");
2449       abort();
2450     }
2451     return;
2452   }
2453   
2454   // Handle cast of Float -> Double
2455   if (SrcClass == cFP32 && DestClass == cFP64) {
2456     BuildMI(*MBB, IP, PPC32::FMR, 1, DestReg).addReg(SrcReg);
2457     return;
2458   }
2459   
2460   // Handle cast of Double -> Float
2461   if (SrcClass == cFP64 && DestClass == cFP32) {
2462     BuildMI(*MBB, IP, PPC32::FRSP, 1, DestReg).addReg(SrcReg);
2463     return;
2464   }
2465   
2466   // Handle cast of SMALLER int to LARGER int using a move with sign extension
2467   // or zero extension, depending on whether the source type was signed.
2468   if (SrcClass <= cInt && (DestClass <= cInt || DestClass == cLong) &&
2469       SrcClass < DestClass) {
2470     bool isLong = DestClass == cLong;
2471     if (isLong) {
2472       DestClass = cInt;
2473       ++DestReg;
2474     }
2475     
2476     bool isUnsigned = SrcTy->isUnsigned() || SrcTy == Type::BoolTy;
2477     if (SrcClass < cInt) {
2478       if (isUnsigned) {
2479         unsigned shift = (SrcClass == cByte) ? 24 : 16;
2480         BuildMI(*BB, IP, PPC32::RLWINM, 4, DestReg).addReg(SrcReg).addZImm(0)
2481           .addImm(shift).addImm(31);
2482       } else {
2483         BuildMI(*BB, IP, (SrcClass == cByte) ? PPC32::EXTSB : PPC32::EXTSH, 
2484                 1, DestReg).addReg(SrcReg);
2485       }
2486     } else {
2487       BuildMI(*BB, IP, PPC32::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
2488     }
2489
2490     if (isLong) {  // Handle upper 32 bits as appropriate...
2491       --DestReg;
2492       if (isUnsigned)     // Zero out top bits...
2493         BuildMI(*BB, IP, PPC32::LI, 1, DestReg).addSImm(0);
2494       else                // Sign extend bottom half...
2495         BuildMI(*BB, IP, PPC32::SRAWI, 2, DestReg).addReg(DestReg).addImm(31);
2496     }
2497     return;
2498   }
2499
2500   // Special case long -> int ...
2501   if (SrcClass == cLong && DestClass == cInt) {
2502     BuildMI(*BB, IP, PPC32::OR, 2, DestReg).addReg(SrcReg+1).addReg(SrcReg+1);
2503     return;
2504   }
2505   
2506   // Handle cast of LARGER int to SMALLER int with a clear or sign extend
2507   if ((SrcClass <= cInt || SrcClass == cLong) && DestClass <= cInt
2508       && SrcClass > DestClass) {
2509     bool isUnsigned = SrcTy->isUnsigned() || SrcTy == Type::BoolTy;
2510     unsigned source = (SrcClass == cLong) ? SrcReg+1 : SrcReg;
2511     
2512     if (isUnsigned) {
2513       unsigned shift = (SrcClass == cByte) ? 24 : 16;
2514       BuildMI(*BB, IP, PPC32::RLWINM, 4, DestReg).addReg(source).addZImm(0)
2515         .addImm(shift).addImm(31);
2516     } else {
2517       BuildMI(*BB, IP, (SrcClass == cByte) ? PPC32::EXTSB : PPC32::EXTSH, 1, 
2518               DestReg).addReg(source);
2519     }
2520     return;
2521   }
2522
2523   // Handle casts from integer to floating point now...
2524   if (DestClass == cFP32 || DestClass == cFP64) {
2525
2526     // Emit a library call for long to float conversion
2527     if (SrcClass == cLong) {
2528       std::vector<ValueRecord> Args;
2529       Args.push_back(ValueRecord(SrcReg, SrcTy));
2530       Function *floatFn = (DestClass == cFP32) ? __floatdisfFn : __floatdidfFn;
2531       MachineInstr *TheCall =
2532         BuildMI(PPC32::CALLpcrel, 1).addGlobalAddress(floatFn, true);
2533       doCall(ValueRecord(DestReg, DestTy), TheCall, Args, false);
2534       return;
2535     }
2536     
2537     // Make sure we're dealing with a full 32 bits
2538     unsigned TmpReg = makeAnotherReg(Type::IntTy);
2539     promote32(TmpReg, ValueRecord(SrcReg, SrcTy));
2540
2541     SrcReg = TmpReg;
2542     
2543     // Spill the integer to memory and reload it from there.
2544     // Also spill room for a special conversion constant
2545     int ConstantFrameIndex = 
2546       F->getFrameInfo()->CreateStackObject(Type::DoubleTy, TM.getTargetData());
2547     int ValueFrameIdx =
2548       F->getFrameInfo()->CreateStackObject(Type::DoubleTy, TM.getTargetData());
2549
2550     unsigned constantHi = makeAnotherReg(Type::IntTy);
2551     unsigned constantLo = makeAnotherReg(Type::IntTy);
2552     unsigned ConstF = makeAnotherReg(Type::DoubleTy);
2553     unsigned TempF = makeAnotherReg(Type::DoubleTy);
2554     
2555     if (!SrcTy->isSigned()) {
2556       BuildMI(*BB, IP, PPC32::LIS, 1, constantHi).addSImm(0x4330);
2557       BuildMI(*BB, IP, PPC32::LI, 1, constantLo).addSImm(0);
2558       addFrameReference(BuildMI(*BB, IP, PPC32::STW, 3).addReg(constantHi), 
2559                         ConstantFrameIndex);
2560       addFrameReference(BuildMI(*BB, IP, PPC32::STW, 3).addReg(constantLo), 
2561                         ConstantFrameIndex, 4);
2562       addFrameReference(BuildMI(*BB, IP, PPC32::STW, 3).addReg(constantHi), 
2563                         ValueFrameIdx);
2564       addFrameReference(BuildMI(*BB, IP, PPC32::STW, 3).addReg(SrcReg), 
2565                         ValueFrameIdx, 4);
2566       addFrameReference(BuildMI(*BB, IP, PPC32::LFD, 2, ConstF), 
2567                         ConstantFrameIndex);
2568       addFrameReference(BuildMI(*BB, IP, PPC32::LFD, 2, TempF), ValueFrameIdx);
2569       BuildMI(*BB, IP, PPC32::FSUB, 2, DestReg).addReg(TempF).addReg(ConstF);
2570     } else {
2571       unsigned TempLo = makeAnotherReg(Type::IntTy);
2572       BuildMI(*BB, IP, PPC32::LIS, 1, constantHi).addSImm(0x4330);
2573       BuildMI(*BB, IP, PPC32::LIS, 1, constantLo).addSImm(0x8000);
2574       addFrameReference(BuildMI(*BB, IP, PPC32::STW, 3).addReg(constantHi), 
2575                         ConstantFrameIndex);
2576       addFrameReference(BuildMI(*BB, IP, PPC32::STW, 3).addReg(constantLo), 
2577                         ConstantFrameIndex, 4);
2578       addFrameReference(BuildMI(*BB, IP, PPC32::STW, 3).addReg(constantHi), 
2579                         ValueFrameIdx);
2580       BuildMI(*BB, IP, PPC32::XORIS, 2, TempLo).addReg(SrcReg).addImm(0x8000);
2581       addFrameReference(BuildMI(*BB, IP, PPC32::STW, 3).addReg(TempLo), 
2582                         ValueFrameIdx, 4);
2583       addFrameReference(BuildMI(*BB, IP, PPC32::LFD, 2, ConstF), 
2584                         ConstantFrameIndex);
2585       addFrameReference(BuildMI(*BB, IP, PPC32::LFD, 2, TempF), ValueFrameIdx);
2586       BuildMI(*BB, IP, PPC32::FSUB, 2, DestReg).addReg(TempF ).addReg(ConstF);
2587     }
2588     return;
2589   }
2590
2591   // Handle casts from floating point to integer now...
2592   if (SrcClass == cFP32 || SrcClass == cFP64) {
2593     // emit library call
2594     if (DestClass == cLong) {
2595       std::vector<ValueRecord> Args;
2596       Args.push_back(ValueRecord(SrcReg, SrcTy));
2597       Function *floatFn = (DestClass == cFP32) ? __fixsfdiFn : __fixdfdiFn;
2598       MachineInstr *TheCall =
2599         BuildMI(PPC32::CALLpcrel, 1).addGlobalAddress(floatFn, true);
2600       doCall(ValueRecord(DestReg, DestTy), TheCall, Args, false);
2601       return;
2602     }
2603
2604     int ValueFrameIdx =
2605       F->getFrameInfo()->CreateStackObject(SrcTy, TM.getTargetData());
2606
2607     if (DestTy->isSigned()) {
2608         unsigned LoadOp = (DestClass == cShort) ? PPC32::LHA : PPC32::LWZ;
2609         unsigned TempReg = makeAnotherReg(Type::DoubleTy);
2610         
2611         // Convert to integer in the FP reg and store it to a stack slot
2612         BuildMI(*BB, IP, PPC32::FCTIWZ, 1, TempReg).addReg(SrcReg);
2613         addFrameReference(BuildMI(*BB, IP, PPC32::STFD, 3)
2614                             .addReg(TempReg), ValueFrameIdx);
2615         
2616         // There is no load signed byte opcode, so we must emit a sign extend
2617         if (DestClass == cByte) {
2618           unsigned TempReg2 = makeAnotherReg(DestTy);
2619           addFrameReference(BuildMI(*BB, IP, LoadOp, 2, TempReg2), 
2620                             ValueFrameIdx, 4);
2621           BuildMI(*MBB, IP, PPC32::EXTSB, DestReg).addReg(TempReg2);
2622         } else {
2623           addFrameReference(BuildMI(*BB, IP, LoadOp, 2, DestReg), 
2624                             ValueFrameIdx, 4);
2625         }
2626     } else {
2627       std::cerr << "Cast fp-to-unsigned not implemented!";
2628       abort();
2629     }
2630     return;
2631   }
2632
2633   // Anything we haven't handled already, we can't (yet) handle at all.
2634   assert(0 && "Unhandled cast instruction!");
2635   abort();
2636 }
2637
2638 /// visitVANextInst - Implement the va_next instruction...
2639 ///
2640 void ISel::visitVANextInst(VANextInst &I) {
2641   unsigned VAList = getReg(I.getOperand(0));
2642   unsigned DestReg = getReg(I);
2643
2644   unsigned Size;
2645   switch (I.getArgType()->getTypeID()) {
2646   default:
2647     std::cerr << I;
2648     assert(0 && "Error: bad type for va_next instruction!");
2649     return;
2650   case Type::PointerTyID:
2651   case Type::UIntTyID:
2652   case Type::IntTyID:
2653     Size = 4;
2654     break;
2655   case Type::ULongTyID:
2656   case Type::LongTyID:
2657   case Type::DoubleTyID:
2658     Size = 8;
2659     break;
2660   }
2661
2662   // Increment the VAList pointer...
2663   BuildMI(BB, PPC32::ADDI, 2, DestReg).addReg(VAList).addSImm(Size);
2664 }
2665
2666 void ISel::visitVAArgInst(VAArgInst &I) {
2667   unsigned VAList = getReg(I.getOperand(0));
2668   unsigned DestReg = getReg(I);
2669
2670   switch (I.getType()->getTypeID()) {
2671   default:
2672     std::cerr << I;
2673     assert(0 && "Error: bad type for va_next instruction!");
2674     return;
2675   case Type::PointerTyID:
2676   case Type::UIntTyID:
2677   case Type::IntTyID:
2678     BuildMI(BB, PPC32::LWZ, 2, DestReg).addSImm(0).addReg(VAList);
2679     break;
2680   case Type::ULongTyID:
2681   case Type::LongTyID:
2682     BuildMI(BB, PPC32::LWZ, 2, DestReg).addSImm(0).addReg(VAList);
2683     BuildMI(BB, PPC32::LWZ, 2, DestReg+1).addSImm(4).addReg(VAList);
2684     break;
2685   case Type::DoubleTyID:
2686     BuildMI(BB, PPC32::LFD, 2, DestReg).addSImm(0).addReg(VAList);
2687     break;
2688   }
2689 }
2690
2691 /// visitGetElementPtrInst - instruction-select GEP instructions
2692 ///
2693 void ISel::visitGetElementPtrInst(GetElementPtrInst &I) {
2694   unsigned outputReg = getReg(I);
2695   emitGEPOperation(BB, BB->end(), I.getOperand(0), I.op_begin()+1, I.op_end(), 
2696                    outputReg);
2697 }
2698
2699 /// emitGEPOperation - Common code shared between visitGetElementPtrInst and
2700 /// constant expression GEP support.
2701 ///
2702 void ISel::emitGEPOperation(MachineBasicBlock *MBB,
2703                             MachineBasicBlock::iterator IP,
2704                             Value *Src, User::op_iterator IdxBegin,
2705                             User::op_iterator IdxEnd, unsigned TargetReg) {
2706   const TargetData &TD = TM.getTargetData ();
2707   const Type *Ty = Src->getType ();
2708   unsigned basePtrReg = getReg (Src, MBB, IP);
2709
2710   // GEPs have zero or more indices; we must perform a struct access
2711   // or array access for each one.
2712   for (GetElementPtrInst::op_iterator oi = IdxBegin, oe = IdxEnd; oi != oe;
2713        ++oi) {
2714     Value *idx = *oi;
2715     unsigned nextBasePtrReg = makeAnotherReg (Type::UIntTy);
2716     if (const StructType *StTy = dyn_cast<StructType> (Ty)) {
2717       // It's a struct access.  idx is the index into the structure,
2718       // which names the field. Use the TargetData structure to
2719       // pick out what the layout of the structure is in memory.
2720       // Use the (constant) structure index's value to find the
2721       // right byte offset from the StructLayout class's list of
2722       // structure member offsets.
2723       unsigned fieldIndex = cast<ConstantUInt> (idx)->getValue ();
2724       unsigned memberOffset =
2725         TD.getStructLayout (StTy)->MemberOffsets[fieldIndex];
2726       // Emit an ADDI to add memberOffset to the basePtr.
2727       BuildMI (*MBB, IP, PPC32::ADDI, 2, nextBasePtrReg).addReg(basePtrReg)
2728         .addSImm(memberOffset);
2729       // The next type is the member of the structure selected by the
2730       // index.
2731       Ty = StTy->getElementType (fieldIndex);
2732     } else if (const SequentialType *SqTy = dyn_cast<SequentialType> (Ty)) {
2733       // Many GEP instructions use a [cast (int/uint) to LongTy] as their
2734       // operand.  Handle this case directly now...
2735       if (CastInst *CI = dyn_cast<CastInst>(idx))
2736         if (CI->getOperand(0)->getType() == Type::IntTy ||
2737             CI->getOperand(0)->getType() == Type::UIntTy)
2738           idx = CI->getOperand(0);
2739
2740       Ty = SqTy->getElementType();
2741       unsigned elementSize = TD.getTypeSize (Ty);
2742       
2743       if (idx == Constant::getNullValue(idx->getType())) {
2744         // GEP with idx 0 is a no-op
2745         nextBasePtrReg = basePtrReg;
2746       } else if (elementSize == 1) {
2747         // If the element size is 1, we don't have to multiply, just add
2748         unsigned idxReg = getReg(idx, MBB, IP);
2749         BuildMI(*MBB, IP, PPC32::ADD, 2, nextBasePtrReg).addReg(basePtrReg)
2750           .addReg(idxReg);
2751       } else {
2752         // It's an array or pointer access: [ArraySize x ElementType].
2753         // We want to add basePtrReg to (idxReg * sizeof ElementType). First, we
2754         // must find the size of the pointed-to type (Not coincidentally, the next
2755         // type is the type of the elements in the array).
2756         unsigned OffsetReg = makeAnotherReg(idx->getType());
2757         ConstantUInt *CUI = ConstantUInt::get(Type::UIntTy, elementSize);
2758         doMultiplyConst(MBB, IP, OffsetReg, idx, CUI);
2759
2760         // Deal with long indices
2761         if (getClass(idx->getType()) == cLong) ++OffsetReg;
2762       
2763         // Emit an ADD to add OffsetReg to the basePtr.
2764         BuildMI (*MBB, IP, PPC32::ADD, 2, nextBasePtrReg).addReg(basePtrReg)
2765           .addReg(OffsetReg);
2766       }
2767     }
2768     basePtrReg = nextBasePtrReg;
2769   }
2770   // After we have processed all the indices, the result is left in
2771   // basePtrReg.  Move it to the register where we were expected to
2772   // put the answer.
2773   BuildMI (BB, PPC32::OR, 2, TargetReg).addReg(basePtrReg).addReg(basePtrReg);
2774 }
2775
2776 /// visitAllocaInst - If this is a fixed size alloca, allocate space from the
2777 /// frame manager, otherwise do it the hard way.
2778 ///
2779 void ISel::visitAllocaInst(AllocaInst &I) {
2780   // If this is a fixed size alloca in the entry block for the function, we
2781   // statically stack allocate the space, so we don't need to do anything here.
2782   //
2783   if (dyn_castFixedAlloca(&I)) return;
2784   
2785   // Find the data size of the alloca inst's getAllocatedType.
2786   const Type *Ty = I.getAllocatedType();
2787   unsigned TySize = TM.getTargetData().getTypeSize(Ty);
2788
2789   // Create a register to hold the temporary result of multiplying the type size
2790   // constant by the variable amount.
2791   unsigned TotalSizeReg = makeAnotherReg(Type::UIntTy);
2792   
2793   // TotalSizeReg = mul <numelements>, <TypeSize>
2794   MachineBasicBlock::iterator MBBI = BB->end();
2795   ConstantUInt *CUI = ConstantUInt::get(Type::UIntTy, TySize);
2796   doMultiplyConst(BB, MBBI, TotalSizeReg, I.getArraySize(), CUI);
2797
2798   // AddedSize = add <TotalSizeReg>, 15
2799   unsigned AddedSizeReg = makeAnotherReg(Type::UIntTy);
2800   BuildMI(BB, PPC32::ADDI, 2, AddedSizeReg).addReg(TotalSizeReg).addSImm(15);
2801
2802   // AlignedSize = and <AddedSize>, ~15
2803   unsigned AlignedSize = makeAnotherReg(Type::UIntTy);
2804   BuildMI(BB, PPC32::RLWNM, 4, AlignedSize).addReg(AddedSizeReg).addImm(0)
2805     .addImm(0).addImm(27);
2806   
2807   // Subtract size from stack pointer, thereby allocating some space.
2808   BuildMI(BB, PPC32::SUB, 2, PPC32::R1).addReg(PPC32::R1).addReg(AlignedSize);
2809
2810   // Put a pointer to the space into the result register, by copying
2811   // the stack pointer.
2812   BuildMI(BB, PPC32::OR, 2, getReg(I)).addReg(PPC32::R1).addReg(PPC32::R1);
2813
2814   // Inform the Frame Information that we have just allocated a variable-sized
2815   // object.
2816   F->getFrameInfo()->CreateVariableSizedObject();
2817 }
2818
2819 /// visitMallocInst - Malloc instructions are code generated into direct calls
2820 /// to the library malloc.
2821 ///
2822 void ISel::visitMallocInst(MallocInst &I) {
2823   unsigned AllocSize = TM.getTargetData().getTypeSize(I.getAllocatedType());
2824   unsigned Arg;
2825
2826   if (ConstantUInt *C = dyn_cast<ConstantUInt>(I.getOperand(0))) {
2827     Arg = getReg(ConstantUInt::get(Type::UIntTy, C->getValue() * AllocSize));
2828   } else {
2829     Arg = makeAnotherReg(Type::UIntTy);
2830     MachineBasicBlock::iterator MBBI = BB->end();
2831     ConstantUInt *CUI = ConstantUInt::get(Type::UIntTy, AllocSize);
2832     doMultiplyConst(BB, MBBI, Arg, I.getOperand(0), CUI);
2833   }
2834
2835   std::vector<ValueRecord> Args;
2836   Args.push_back(ValueRecord(Arg, Type::UIntTy));
2837   MachineInstr *TheCall = 
2838     BuildMI(PPC32::CALLpcrel, 1).addGlobalAddress(mallocFn, true);
2839   doCall(ValueRecord(getReg(I), I.getType()), TheCall, Args, false);
2840 }
2841
2842
2843 /// visitFreeInst - Free instructions are code gen'd to call the free libc
2844 /// function.
2845 ///
2846 void ISel::visitFreeInst(FreeInst &I) {
2847   std::vector<ValueRecord> Args;
2848   Args.push_back(ValueRecord(I.getOperand(0)));
2849   MachineInstr *TheCall = 
2850     BuildMI(PPC32::CALLpcrel, 1).addGlobalAddress(freeFn, true);
2851   doCall(ValueRecord(0, Type::VoidTy), TheCall, Args, false);
2852 }
2853    
2854 /// createPPC32SimpleInstructionSelector - This pass converts an LLVM function
2855 /// into a machine code representation is a very simple peep-hole fashion.  The
2856 /// generated code sucks but the implementation is nice and simple.
2857 ///
2858 FunctionPass *llvm::createPPCSimpleInstructionSelector(TargetMachine &TM) {
2859   return new ISel(TM);
2860 }