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