Start allocating condition registers. Almost all explicit uses of CR0 are
[oota-llvm.git] / lib / Target / PowerPC / PPC32ISelSimple.cpp
1 //===-- PPC32ISelSimple.cpp - A simple instruction selector PowerPC32 -----===//
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 "PPC32TargetMachine.h"
15 #include "llvm/Constants.h"
16 #include "llvm/DerivedTypes.h"
17 #include "llvm/Function.h"
18 #include "llvm/Instructions.h"
19 #include "llvm/Pass.h"
20 #include "llvm/CodeGen/IntrinsicLowering.h"
21 #include "llvm/CodeGen/MachineConstantPool.h"
22 #include "llvm/CodeGen/MachineFrameInfo.h"
23 #include "llvm/CodeGen/MachineFunction.h"
24 #include "llvm/CodeGen/SSARegMap.h"
25 #include "llvm/Target/MRegisterInfo.h"
26 #include "llvm/Target/TargetMachine.h"
27 #include "llvm/Support/GetElementPtrTypeIterator.h"
28 #include "llvm/Support/InstVisitor.h"
29 #include "llvm/Support/Debug.h"
30 #include "llvm/ADT/Statistic.h"
31 #include <vector>
32 using namespace llvm;
33
34 namespace {
35   /// TypeClass - Used by the PowerPC backend to group LLVM types by their basic
36   /// PPC Representation.
37   ///
38   enum TypeClass {
39     cByte, cShort, cInt, cFP32, cFP64, cLong
40   };
41 }
42
43 /// getClass - Turn a primitive type into a "class" number which is based on the
44 /// size of the type, and whether or not it is floating point.
45 ///
46 static inline TypeClass getClass(const Type *Ty) {
47   switch (Ty->getTypeID()) {
48   case Type::SByteTyID:
49   case Type::UByteTyID:   return cByte;      // Byte operands are class #0
50   case Type::ShortTyID:
51   case Type::UShortTyID:  return cShort;     // Short operands are class #1
52   case Type::IntTyID:
53   case Type::UIntTyID:
54   case Type::PointerTyID: return cInt;       // Ints and pointers are class #2
55
56   case Type::FloatTyID:   return cFP32;      // Single float is #3
57   case Type::DoubleTyID:  return cFP64;      // Double Point is #4
58
59   case Type::LongTyID:
60   case Type::ULongTyID:   return cLong;      // Longs are class #5
61   default:
62     assert(0 && "Invalid type to getClass!");
63     return cByte;  // not reached
64   }
65 }
66
67 // getClassB - Just like getClass, but treat boolean values as ints.
68 static inline TypeClass getClassB(const Type *Ty) {
69   if (Ty == Type::BoolTy) return cByte;
70   return getClass(Ty);
71 }
72
73 namespace {
74   struct PPC32ISel : public FunctionPass, InstVisitor<PPC32ISel> {
75     PPC32TargetMachine &TM;
76     MachineFunction *F;                 // The function we are compiling into
77     MachineBasicBlock *BB;              // The current MBB we are compiling
78     int VarArgsFrameIndex;              // FrameIndex for start of varargs area
79     
80     /// CollapsedGepOp - This struct is for recording the intermediate results 
81     /// used to calculate the base, index, and offset of a GEP instruction.
82     struct CollapsedGepOp {
83       ConstantSInt *offset; // the current offset into the struct/array
84       Value *index;         // the index of the array element
85       ConstantUInt *size;   // the size of each array element
86       CollapsedGepOp(ConstantSInt *o, Value *i, ConstantUInt *s) :
87         offset(o), index(i), size(s) {}
88     };
89
90     /// FoldedGEP - This struct is for recording the necessary information to 
91     /// emit the GEP in a load or store instruction, used by emitGEPOperation.
92     struct FoldedGEP {
93       unsigned base;
94       unsigned index;
95       ConstantSInt *offset;
96       FoldedGEP() : base(0), index(0), offset(0) {}
97       FoldedGEP(unsigned b, unsigned i, ConstantSInt *o) : 
98         base(b), index(i), offset(o) {}
99     };
100     
101     /// RlwimiRec - This struct is for recording the arguments to a PowerPC 
102     /// rlwimi instruction to be output for a particular Instruction::Or when
103     /// we recognize the pattern for rlwimi, starting with a shift or and.
104     struct RlwimiRec { 
105       Value *Target, *Insert;
106       unsigned Shift, MB, ME;
107       RlwimiRec() : Target(0), Insert(0), Shift(0), MB(0), ME(0) {}
108       RlwimiRec(Value *tgt, Value *ins, unsigned s, unsigned b, unsigned e) :
109         Target(tgt), Insert(ins), Shift(s), MB(b), ME(e) {}
110     };
111     
112     // External functions we may use in compiling the Module
113     Function *fmodfFn, *fmodFn, *__cmpdi2Fn, *__moddi3Fn, *__divdi3Fn, 
114       *__umoddi3Fn,  *__udivdi3Fn, *__fixsfdiFn, *__fixdfdiFn, *__fixunssfdiFn,
115       *__fixunsdfdiFn, *__floatdisfFn, *__floatdidfFn, *mallocFn, *freeFn;
116
117     // Mapping between Values and SSA Regs
118     std::map<Value*, unsigned> RegMap;
119
120     // MBBMap - Mapping between LLVM BB -> Machine BB
121     std::map<const BasicBlock*, MachineBasicBlock*> MBBMap;
122
123     // AllocaMap - Mapping from fixed sized alloca instructions to the
124     // FrameIndex for the alloca.
125     std::map<AllocaInst*, unsigned> AllocaMap;
126
127     // GEPMap - Mapping between basic blocks and GEP definitions
128     std::map<GetElementPtrInst*, FoldedGEP> GEPMap;
129     
130     // RlwimiMap  - Mapping between BinaryOperand (Or) instructions and info
131     // needed to properly emit a rlwimi instruction in its place.
132     std::map<Instruction *, RlwimiRec> InsertMap;
133
134     // A rlwimi instruction is the combination of at least three instructions.
135     // Keep a vector of instructions to skip around so that we do not try to
136     // emit instructions that were folded into a rlwimi.
137     std::vector<Instruction *> SkipList;
138
139     // A Reg to hold the base address used for global loads and stores, and a
140     // flag to set whether or not we need to emit it for this function.
141     unsigned GlobalBaseReg;
142     bool GlobalBaseInitialized;
143     
144     PPC32ISel(TargetMachine &tm):TM(reinterpret_cast<PPC32TargetMachine&>(tm)),
145       F(0), BB(0) {}
146
147     bool doInitialization(Module &M) {
148       // Add external functions that we may call
149       Type *i = Type::IntTy;
150       Type *d = Type::DoubleTy;
151       Type *f = Type::FloatTy;
152       Type *l = Type::LongTy;
153       Type *ul = Type::ULongTy;
154       Type *voidPtr = PointerType::get(Type::SByteTy);
155       // float fmodf(float, float);
156       fmodfFn = M.getOrInsertFunction("fmodf", f, f, f, 0);
157       // double fmod(double, double);
158       fmodFn = M.getOrInsertFunction("fmod", d, d, d, 0);
159       // int __cmpdi2(long, long);
160       __cmpdi2Fn = M.getOrInsertFunction("__cmpdi2", i, l, l, 0);
161       // long __moddi3(long, long);
162       __moddi3Fn = M.getOrInsertFunction("__moddi3", l, l, l, 0);
163       // long __divdi3(long, long);
164       __divdi3Fn = M.getOrInsertFunction("__divdi3", l, l, l, 0);
165       // unsigned long __umoddi3(unsigned long, unsigned long);
166       __umoddi3Fn = M.getOrInsertFunction("__umoddi3", ul, ul, ul, 0);
167       // unsigned long __udivdi3(unsigned long, unsigned long);
168       __udivdi3Fn = M.getOrInsertFunction("__udivdi3", ul, ul, ul, 0);
169       // long __fixsfdi(float)
170       __fixsfdiFn = M.getOrInsertFunction("__fixsfdi", l, f, 0);
171       // long __fixdfdi(double)
172       __fixdfdiFn = M.getOrInsertFunction("__fixdfdi", l, d, 0);
173       // unsigned long __fixunssfdi(float)
174       __fixunssfdiFn = M.getOrInsertFunction("__fixunssfdi", ul, f, 0);
175       // unsigned long __fixunsdfdi(double)
176       __fixunsdfdiFn = M.getOrInsertFunction("__fixunsdfdi", ul, d, 0);
177       // float __floatdisf(long)
178       __floatdisfFn = M.getOrInsertFunction("__floatdisf", f, l, 0);
179       // double __floatdidf(long)
180       __floatdidfFn = M.getOrInsertFunction("__floatdidf", d, l, 0);
181       // void* malloc(size_t)
182       mallocFn = M.getOrInsertFunction("malloc", voidPtr, Type::UIntTy, 0);
183       // void free(void*)
184       freeFn = M.getOrInsertFunction("free", Type::VoidTy, voidPtr, 0);
185       return true;
186     }
187
188     /// runOnFunction - Top level implementation of instruction selection for
189     /// the entire function.
190     ///
191     bool runOnFunction(Function &Fn) {
192       // First pass over the function, lower any unknown intrinsic functions
193       // with the IntrinsicLowering class.
194       LowerUnknownIntrinsicFunctionCalls(Fn);
195
196       F = &MachineFunction::construct(&Fn, TM);
197
198       // Create all of the machine basic blocks for the function...
199       for (Function::iterator I = Fn.begin(), E = Fn.end(); I != E; ++I)
200         F->getBasicBlockList().push_back(MBBMap[I] = new MachineBasicBlock(I));
201
202       BB = &F->front();
203
204       // Make sure we re-emit a set of the global base reg if necessary
205       GlobalBaseInitialized = false;
206
207       // Copy incoming arguments off of the stack...
208       LoadArgumentsToVirtualRegs(Fn);
209
210       // Instruction select everything except PHI nodes
211       visit(Fn);
212
213       // Select the PHI nodes
214       SelectPHINodes();
215
216       GEPMap.clear();
217       RegMap.clear();
218       MBBMap.clear();
219       InsertMap.clear();
220       AllocaMap.clear();
221       SkipList.clear();
222       F = 0;
223       // We always build a machine code representation for the function
224       return true;
225     }
226
227     virtual const char *getPassName() const {
228       return "PowerPC Simple Instruction Selection";
229     }
230
231     /// visitBasicBlock - This method is called when we are visiting a new basic
232     /// block.  This simply creates a new MachineBasicBlock to emit code into
233     /// and adds it to the current MachineFunction.  Subsequent visit* for
234     /// instructions will be invoked for all instructions in the basic block.
235     ///
236     void visitBasicBlock(BasicBlock &LLVM_BB) {
237       BB = MBBMap[&LLVM_BB];
238     }
239
240     /// LowerUnknownIntrinsicFunctionCalls - This performs a prepass over the
241     /// function, lowering any calls to unknown intrinsic functions into the
242     /// equivalent LLVM code.
243     ///
244     void LowerUnknownIntrinsicFunctionCalls(Function &F);
245
246     /// LoadArgumentsToVirtualRegs - Load all of the arguments to this function
247     /// from the stack into virtual registers.
248     ///
249     void LoadArgumentsToVirtualRegs(Function &F);
250
251     /// SelectPHINodes - Insert machine code to generate phis.  This is tricky
252     /// because we have to generate our sources into the source basic blocks,
253     /// not the current one.
254     ///
255     void SelectPHINodes();
256
257     // Visitation methods for various instructions.  These methods simply emit
258     // fixed PowerPC code for each instruction.
259
260     // Control flow operators.
261     void visitReturnInst(ReturnInst &RI);
262     void visitBranchInst(BranchInst &BI);
263     void visitUnreachableInst(UnreachableInst &UI) {}
264
265     struct ValueRecord {
266       Value *Val;
267       unsigned Reg;
268       const Type *Ty;
269       ValueRecord(unsigned R, const Type *T) : Val(0), Reg(R), Ty(T) {}
270       ValueRecord(Value *V) : Val(V), Reg(0), Ty(V->getType()) {}
271     };
272
273     void doCall(const ValueRecord &Ret, MachineInstr *CallMI,
274                 const std::vector<ValueRecord> &Args, bool isVarArg);
275     void visitCallInst(CallInst &I);
276     void visitIntrinsicCall(Intrinsic::ID ID, CallInst &I);
277
278     // Arithmetic operators
279     void visitSimpleBinary(BinaryOperator &B, unsigned OpcodeClass);
280     void visitAdd(BinaryOperator &B) { visitSimpleBinary(B, 0); }
281     void visitSub(BinaryOperator &B) { visitSimpleBinary(B, 1); }
282     void visitMul(BinaryOperator &B);
283
284     void visitDiv(BinaryOperator &B) { visitDivRem(B); }
285     void visitRem(BinaryOperator &B) { visitDivRem(B); }
286     void visitDivRem(BinaryOperator &B);
287
288     // Bitwise operators
289     void visitAnd(BinaryOperator &B) { visitSimpleBinary(B, 2); }
290     void visitOr (BinaryOperator &B) { visitSimpleBinary(B, 3); }
291     void visitXor(BinaryOperator &B) { visitSimpleBinary(B, 4); }
292
293     // Comparison operators...
294     void visitSetCondInst(SetCondInst &I);
295     void EmitComparison(unsigned OpNum, Value *Op0, Value *Op1,
296                         MachineBasicBlock *MBB,
297                         MachineBasicBlock::iterator MBBI);
298     void visitSelectInst(SelectInst &SI);
299     
300     
301     // Memory Instructions
302     void visitLoadInst(LoadInst &I);
303     void visitStoreInst(StoreInst &I);
304     void visitGetElementPtrInst(GetElementPtrInst &I);
305     void visitAllocaInst(AllocaInst &I);
306     void visitMallocInst(MallocInst &I);
307     void visitFreeInst(FreeInst &I);
308     
309     // Other operators
310     void visitShiftInst(ShiftInst &I);
311     void visitPHINode(PHINode &I) {}      // PHI nodes handled by second pass
312     void visitCastInst(CastInst &I);
313     void visitVANextInst(VANextInst &I);
314     void visitVAArgInst(VAArgInst &I);
315
316     void visitInstruction(Instruction &I) {
317       std::cerr << "Cannot instruction select: " << I;
318       abort();
319     }
320
321     unsigned ExtendOrClear(MachineBasicBlock *MBB,
322                            MachineBasicBlock::iterator IP,
323                            Value *Op0);
324
325     /// promote32 - Make a value 32-bits wide, and put it somewhere.
326     ///
327     void promote32(unsigned targetReg, const ValueRecord &VR);
328
329     /// emitGEPOperation - Common code shared between visitGetElementPtrInst and
330     /// constant expression GEP support.
331     ///
332     void emitGEPOperation(MachineBasicBlock *BB, MachineBasicBlock::iterator IP,
333                           GetElementPtrInst *GEPI, bool foldGEP);
334
335     /// emitCastOperation - Common code shared between visitCastInst and
336     /// constant expression cast support.
337     ///
338     void emitCastOperation(MachineBasicBlock *BB,MachineBasicBlock::iterator IP,
339                            Value *Src, const Type *DestTy, unsigned TargetReg);
340
341
342     /// emitBitfieldInsert - return true if we were able to fold the sequence of
343     /// instructions into a bitfield insert (rlwimi).
344     bool emitBitfieldInsert(User *OpUser, unsigned DestReg);
345                                   
346     /// emitBitfieldExtract - return true if we were able to fold the sequence
347     /// of instructions into a bitfield extract (rlwinm).
348     bool emitBitfieldExtract(MachineBasicBlock *MBB, 
349                              MachineBasicBlock::iterator IP,
350                              User *OpUser, unsigned DestReg);
351
352     /// emitBinaryConstOperation - Used by several functions to emit simple
353     /// arithmetic and logical operations with constants on a register rather
354     /// than a Value.
355     ///
356     void emitBinaryConstOperation(MachineBasicBlock *MBB, 
357                                   MachineBasicBlock::iterator IP,
358                                   unsigned Op0Reg, ConstantInt *Op1, 
359                                   unsigned Opcode, unsigned DestReg);
360
361     /// emitSimpleBinaryOperation - Implement simple binary operators for 
362     /// integral types.  OperatorClass is one of: 0 for Add, 1 for Sub, 
363     /// 2 for And, 3 for Or, 4 for Xor.
364     ///
365     void emitSimpleBinaryOperation(MachineBasicBlock *BB,
366                                    MachineBasicBlock::iterator IP,
367                                    BinaryOperator *BO, Value *Op0, Value *Op1,
368                                    unsigned OperatorClass, unsigned TargetReg);
369
370     /// emitBinaryFPOperation - This method handles emission of floating point
371     /// Add (0), Sub (1), Mul (2), and Div (3) operations.
372     void emitBinaryFPOperation(MachineBasicBlock *BB,
373                                MachineBasicBlock::iterator IP,
374                                Value *Op0, Value *Op1,
375                                unsigned OperatorClass, unsigned TargetReg);
376
377     void emitMultiply(MachineBasicBlock *BB, MachineBasicBlock::iterator IP,
378                       Value *Op0, Value *Op1, unsigned TargetReg);
379
380     void doMultiply(MachineBasicBlock *MBB,
381                     MachineBasicBlock::iterator IP,
382                     unsigned DestReg, Value *Op0, Value *Op1);
383   
384     /// doMultiplyConst - This method will multiply the value in Op0Reg by the
385     /// value of the ContantInt *CI
386     void doMultiplyConst(MachineBasicBlock *MBB, 
387                          MachineBasicBlock::iterator IP,
388                          unsigned DestReg, Value *Op0, ConstantInt *CI);
389
390     void emitDivRemOperation(MachineBasicBlock *BB,
391                              MachineBasicBlock::iterator IP,
392                              Value *Op0, Value *Op1, bool isDiv,
393                              unsigned TargetReg);
394
395     /// emitSetCCOperation - Common code shared between visitSetCondInst and
396     /// constant expression support.
397     ///
398     void emitSetCCOperation(MachineBasicBlock *BB,
399                             MachineBasicBlock::iterator IP,
400                             Value *Op0, Value *Op1, unsigned Opcode,
401                             unsigned TargetReg);
402
403     /// emitShiftOperation - Common code shared between visitShiftInst and
404     /// constant expression support.
405     ///
406     void emitShiftOperation(MachineBasicBlock *MBB,
407                             MachineBasicBlock::iterator IP,
408                             Value *Op, Value *ShiftAmount, bool isLeftShift,
409                             const Type *ResultTy, ShiftInst *SI, 
410                             unsigned DestReg);
411       
412     /// emitSelectOperation - Common code shared between visitSelectInst and the
413     /// constant expression support.
414     ///
415     void emitSelectOperation(MachineBasicBlock *MBB,
416                              MachineBasicBlock::iterator IP,
417                              Value *Cond, Value *TrueVal, Value *FalseVal,
418                              unsigned DestReg);
419
420     /// getGlobalBaseReg - Output the instructions required to put the
421     /// base address to use for accessing globals into a register.  Returns the
422     /// register containing the base address.
423     ///
424     unsigned getGlobalBaseReg();
425
426     /// copyConstantToRegister - Output the instructions required to put the
427     /// specified constant into the specified register.
428     ///
429     void copyConstantToRegister(MachineBasicBlock *MBB,
430                                 MachineBasicBlock::iterator MBBI,
431                                 Constant *C, unsigned Reg);
432
433     void emitUCOM(MachineBasicBlock *MBB, MachineBasicBlock::iterator MBBI,
434                    unsigned LHS, unsigned RHS);
435
436     /// makeAnotherReg - This method returns the next register number we haven't
437     /// yet used.
438     ///
439     /// Long values are handled somewhat specially.  They are always allocated
440     /// as pairs of 32 bit integer values.  The register number returned is the
441     /// high 32 bits of the long value, and the regNum+1 is the low 32 bits.
442     ///
443     unsigned makeAnotherReg(const Type *Ty) {
444       assert(dynamic_cast<const PPC32RegisterInfo*>(TM.getRegisterInfo()) &&
445              "Current target doesn't have PPC reg info??");
446       const PPC32RegisterInfo *PPCRI =
447         static_cast<const PPC32RegisterInfo*>(TM.getRegisterInfo());
448       if (Ty == Type::LongTy || Ty == Type::ULongTy) {
449         const TargetRegisterClass *RC = PPCRI->getRegClassForType(Type::IntTy);
450         // Create the upper part
451         F->getSSARegMap()->createVirtualRegister(RC);
452         // Create the lower part.
453         return F->getSSARegMap()->createVirtualRegister(RC)-1;
454       }
455
456       // Add the mapping of regnumber => reg class to MachineFunction
457       const TargetRegisterClass *RC = PPCRI->getRegClassForType(Ty);
458       return F->getSSARegMap()->createVirtualRegister(RC);
459     }
460
461     /// getReg - This method turns an LLVM value into a register number.
462     ///
463     unsigned getReg(Value &V) { return getReg(&V); }  // Allow references
464     unsigned getReg(Value *V) {
465       // Just append to the end of the current bb.
466       MachineBasicBlock::iterator It = BB->end();
467       return getReg(V, BB, It);
468     }
469     unsigned getReg(Value *V, MachineBasicBlock *MBB,
470                     MachineBasicBlock::iterator IPt);
471     
472     /// canUseAsImmediateForOpcode - This method returns whether a ConstantInt
473     /// is okay to use as an immediate argument to a certain binary operation
474     bool canUseAsImmediateForOpcode(ConstantInt *CI, unsigned Opcode,
475                                     bool Shifted);
476
477     /// getFixedSizedAllocaFI - Return the frame index for a fixed sized alloca
478     /// that is to be statically allocated with the initial stack frame
479     /// adjustment.
480     unsigned getFixedSizedAllocaFI(AllocaInst *AI);
481   };
482 }
483
484 /// dyn_castFixedAlloca - If the specified value is a fixed size alloca
485 /// instruction in the entry block, return it.  Otherwise, return a null
486 /// pointer.
487 static AllocaInst *dyn_castFixedAlloca(Value *V) {
488   if (AllocaInst *AI = dyn_cast<AllocaInst>(V)) {
489     BasicBlock *BB = AI->getParent();
490     if (isa<ConstantUInt>(AI->getArraySize()) && BB ==&BB->getParent()->front())
491       return AI;
492   }
493   return 0;
494 }
495
496 /// getReg - This method turns an LLVM value into a register number.
497 ///
498 unsigned PPC32ISel::getReg(Value *V, MachineBasicBlock *MBB,
499                            MachineBasicBlock::iterator IPt) {
500   if (Constant *C = dyn_cast<Constant>(V)) {
501     unsigned Reg = makeAnotherReg(V->getType());
502     copyConstantToRegister(MBB, IPt, C, Reg);
503     return Reg;
504   } else if (CastInst *CI = dyn_cast<CastInst>(V)) {
505     // Do not emit noop casts at all, unless it's a double -> float cast.
506     if (getClassB(CI->getType()) == getClassB(CI->getOperand(0)->getType()))
507       return getReg(CI->getOperand(0), MBB, IPt);
508   } else if (AllocaInst *AI = dyn_castFixedAlloca(V)) {
509     unsigned Reg = makeAnotherReg(V->getType());
510     unsigned FI = getFixedSizedAllocaFI(AI);
511     addFrameReference(BuildMI(*MBB, IPt, PPC::ADDI, 2, Reg), FI, 0, false);
512     return Reg;
513   }
514
515   unsigned &Reg = RegMap[V];
516   if (Reg == 0) {
517     Reg = makeAnotherReg(V->getType());
518     RegMap[V] = Reg;
519   }
520
521   return Reg;
522 }
523
524 /// canUseAsImmediateForOpcode - This method returns whether a ConstantInt
525 /// is okay to use as an immediate argument to a certain binary operator.
526 /// The shifted argument determines if the immediate is suitable to be used with
527 /// the PowerPC instructions such as addis which concatenate 16 bits of the
528 /// immediate with 16 bits of zeroes.
529 ///
530 bool PPC32ISel::canUseAsImmediateForOpcode(ConstantInt *CI, unsigned Opcode,
531                                            bool Shifted) {
532   ConstantSInt *Op1Cs;
533   ConstantUInt *Op1Cu;
534
535   // For shifted immediates, any value with the low halfword cleared may be used
536   if (Shifted) {
537     if (((int32_t)CI->getRawValue() & 0x0000FFFF) == 0)
538       return true;
539     else
540       return false;
541   }
542
543   // Treat subfic like addi for the purposes of constant validation
544   if (Opcode == 5) Opcode = 0;
545       
546   // addi, subfic, compare, and non-indexed load take SIMM
547   bool cond1 = (Opcode < 2)
548     && ((int32_t)CI->getRawValue() <= 32767)
549     && ((int32_t)CI->getRawValue() >= -32768);
550
551   // ANDIo, ORI, and XORI take unsigned values
552   bool cond2 = (Opcode >= 2)
553     && (Op1Cs = dyn_cast<ConstantSInt>(CI))
554     && (Op1Cs->getValue() >= 0)
555     && (Op1Cs->getValue() <= 65535);
556
557   // ANDIo, ORI, and XORI take UIMMs, so they can be larger
558   bool cond3 = (Opcode >= 2)
559     && (Op1Cu = dyn_cast<ConstantUInt>(CI))
560     && (Op1Cu->getValue() <= 65535);
561
562   if (cond1 || cond2 || cond3)
563     return true;
564
565   return false;
566 }
567
568 /// getFixedSizedAllocaFI - Return the frame index for a fixed sized alloca
569 /// that is to be statically allocated with the initial stack frame
570 /// adjustment.
571 unsigned PPC32ISel::getFixedSizedAllocaFI(AllocaInst *AI) {
572   // Already computed this?
573   std::map<AllocaInst*, unsigned>::iterator I = AllocaMap.lower_bound(AI);
574   if (I != AllocaMap.end() && I->first == AI) return I->second;
575
576   const Type *Ty = AI->getAllocatedType();
577   ConstantUInt *CUI = cast<ConstantUInt>(AI->getArraySize());
578   unsigned TySize = TM.getTargetData().getTypeSize(Ty);
579   TySize *= CUI->getValue();   // Get total allocated size...
580   unsigned Alignment = TM.getTargetData().getTypeAlignment(Ty);
581       
582   // Create a new stack object using the frame manager...
583   int FrameIdx = F->getFrameInfo()->CreateStackObject(TySize, Alignment);
584   AllocaMap.insert(I, std::make_pair(AI, FrameIdx));
585   return FrameIdx;
586 }
587
588
589 /// getGlobalBaseReg - Output the instructions required to put the
590 /// base address to use for accessing globals into a register.
591 ///
592 unsigned PPC32ISel::getGlobalBaseReg() {
593   if (!GlobalBaseInitialized) {
594     // Insert the set of GlobalBaseReg into the first MBB of the function
595     MachineBasicBlock &FirstMBB = F->front();
596     MachineBasicBlock::iterator MBBI = FirstMBB.begin();
597     GlobalBaseReg = makeAnotherReg(Type::IntTy);
598     BuildMI(FirstMBB, MBBI, PPC::MovePCtoLR, 0, PPC::LR);
599     BuildMI(FirstMBB, MBBI, PPC::MFLR, 1, GlobalBaseReg).addReg(PPC::LR);
600     GlobalBaseInitialized = true;
601   }
602   return GlobalBaseReg;
603 }
604
605 /// copyConstantToRegister - Output the instructions required to put the
606 /// specified constant into the specified register.
607 ///
608 void PPC32ISel::copyConstantToRegister(MachineBasicBlock *MBB,
609                                        MachineBasicBlock::iterator IP,
610                                        Constant *C, unsigned R) {
611   if (isa<UndefValue>(C)) {
612     BuildMI(*MBB, IP, PPC::IMPLICIT_DEF, 0, R);
613     if (getClassB(C->getType()) == cLong)
614       BuildMI(*MBB, IP, PPC::IMPLICIT_DEF, 0, R+1);
615     return;
616   }
617   if (C->getType()->isIntegral()) {
618     unsigned Class = getClassB(C->getType());
619
620     if (Class == cLong) {
621       if (ConstantUInt *CUI = dyn_cast<ConstantUInt>(C)) {
622         uint64_t uval = CUI->getValue();
623         unsigned hiUVal = uval >> 32;
624         unsigned loUVal = uval;
625         ConstantUInt *CUHi = ConstantUInt::get(Type::UIntTy, hiUVal);
626         ConstantUInt *CULo = ConstantUInt::get(Type::UIntTy, loUVal);
627         copyConstantToRegister(MBB, IP, CUHi, R);
628         copyConstantToRegister(MBB, IP, CULo, R+1);
629         return;
630       } else if (ConstantSInt *CSI = dyn_cast<ConstantSInt>(C)) {
631         int64_t sval = CSI->getValue();
632         int hiSVal = sval >> 32;
633         int loSVal = sval;
634         ConstantSInt *CSHi = ConstantSInt::get(Type::IntTy, hiSVal);
635         ConstantSInt *CSLo = ConstantSInt::get(Type::IntTy, loSVal);
636         copyConstantToRegister(MBB, IP, CSHi, R);
637         copyConstantToRegister(MBB, IP, CSLo, R+1);
638         return;
639       } else {
640         std::cerr << "Unhandled long constant type!\n";
641         abort();
642       }
643     }
644     
645     assert(Class <= cInt && "Type not handled yet!");
646
647     // Handle bool
648     if (C->getType() == Type::BoolTy) {
649       BuildMI(*MBB, IP, PPC::LI, 1, R).addSImm(C == ConstantBool::True);
650       return;
651     }
652     
653     // Handle int
654     if (ConstantUInt *CUI = dyn_cast<ConstantUInt>(C)) {
655       unsigned uval = CUI->getValue();
656       if (uval < 32768) {
657         BuildMI(*MBB, IP, PPC::LI, 1, R).addSImm(uval);
658       } else {
659         unsigned Temp = makeAnotherReg(Type::IntTy);
660         BuildMI(*MBB, IP, PPC::LIS, 1, Temp).addSImm(uval >> 16);
661         BuildMI(*MBB, IP, PPC::ORI, 2, R).addReg(Temp).addImm(uval & 0xFFFF);
662       }
663       return;
664     } else if (ConstantSInt *CSI = dyn_cast<ConstantSInt>(C)) {
665       int sval = CSI->getValue();
666       if (sval < 32768 && sval >= -32768) {
667         BuildMI(*MBB, IP, PPC::LI, 1, R).addSImm(sval);
668       } else {
669         unsigned Temp = makeAnotherReg(Type::IntTy);
670         BuildMI(*MBB, IP, PPC::LIS, 1, Temp).addSImm(sval >> 16);
671         BuildMI(*MBB, IP, PPC::ORI, 2, R).addReg(Temp).addImm(sval & 0xFFFF);
672       }
673       return;
674     }
675     std::cerr << "Unhandled integer constant!\n";
676     abort();
677   } else if (ConstantFP *CFP = dyn_cast<ConstantFP>(C)) {
678     // We need to spill the constant to memory...
679     MachineConstantPool *CP = F->getConstantPool();
680     unsigned CPI = CP->getConstantPoolIndex(CFP);
681     const Type *Ty = CFP->getType();
682
683     assert(Ty == Type::FloatTy || Ty == Type::DoubleTy && "Unknown FP type!");
684
685     // Load addr of constant to reg; constant is located at base + distance
686     unsigned Reg1 = makeAnotherReg(Type::IntTy);
687     unsigned Opcode = (Ty == Type::FloatTy) ? PPC::LFS : PPC::LFD;
688     // Move value at base + distance into return reg
689     BuildMI(*MBB, IP, PPC::LOADHiAddr, 2, Reg1)
690       .addReg(getGlobalBaseReg()).addConstantPoolIndex(CPI);
691     BuildMI(*MBB, IP, Opcode, 2, R).addConstantPoolIndex(CPI).addReg(Reg1);
692   } else if (isa<ConstantPointerNull>(C)) {
693     // Copy zero (null pointer) to the register.
694     BuildMI(*MBB, IP, PPC::LI, 1, R).addSImm(0);
695   } else if (GlobalValue *GV = dyn_cast<GlobalValue>(C)) {
696     // GV is located at base + distance
697     unsigned TmpReg = makeAnotherReg(GV->getType());
698     
699     // Move value at base + distance into return reg
700     BuildMI(*MBB, IP, PPC::LOADHiAddr, 2, TmpReg)
701       .addReg(getGlobalBaseReg()).addGlobalAddress(GV);
702
703     if (GV->hasWeakLinkage() || GV->isExternal()) {
704       BuildMI(*MBB, IP, PPC::LWZ, 2, R).addGlobalAddress(GV).addReg(TmpReg);
705     } else {
706       BuildMI(*MBB, IP, PPC::LA, 2, R).addReg(TmpReg).addGlobalAddress(GV);
707     }
708   } else {
709     std::cerr << "Offending constant: " << *C << "\n";
710     assert(0 && "Type not handled yet!");
711   }
712 }
713
714 /// LoadArgumentsToVirtualRegs - Load all of the arguments to this function from
715 /// the stack into virtual registers.
716 void PPC32ISel::LoadArgumentsToVirtualRegs(Function &Fn) {
717   unsigned ArgOffset = 24;
718   unsigned GPR_remaining = 8;
719   unsigned FPR_remaining = 13;
720   unsigned GPR_idx = 0, FPR_idx = 0;
721   static const unsigned GPR[] = { 
722     PPC::R3, PPC::R4, PPC::R5, PPC::R6,
723     PPC::R7, PPC::R8, PPC::R9, PPC::R10,
724   };
725   static const unsigned FPR[] = {
726     PPC::F1, PPC::F2, PPC::F3, PPC::F4, PPC::F5, PPC::F6, PPC::F7,
727     PPC::F8, PPC::F9, PPC::F10, PPC::F11, PPC::F12, PPC::F13
728   };
729     
730   MachineFrameInfo *MFI = F->getFrameInfo();
731  
732   for (Function::arg_iterator I = Fn.arg_begin(), E = Fn.arg_end();
733        I != E; ++I) {
734     bool ArgLive = !I->use_empty();
735     unsigned Reg = ArgLive ? getReg(*I) : 0;
736     int FI;          // Frame object index
737
738     switch (getClassB(I->getType())) {
739     case cByte:
740       if (ArgLive) {
741         FI = MFI->CreateFixedObject(4, ArgOffset);
742         if (GPR_remaining > 0) {
743           F->addLiveIn(GPR[GPR_idx]);
744           BuildMI(BB, PPC::OR, 2, Reg).addReg(GPR[GPR_idx])
745             .addReg(GPR[GPR_idx]);
746         } else {
747           addFrameReference(BuildMI(BB, PPC::LBZ, 2, Reg), FI);
748         }
749       }
750       break;
751     case cShort:
752       if (ArgLive) {
753         FI = MFI->CreateFixedObject(4, ArgOffset);
754         if (GPR_remaining > 0) {
755           F->addLiveIn(GPR[GPR_idx]);
756           BuildMI(BB, PPC::OR, 2, Reg).addReg(GPR[GPR_idx])
757             .addReg(GPR[GPR_idx]);
758         } else {
759           addFrameReference(BuildMI(BB, PPC::LHZ, 2, Reg), FI);
760         }
761       }
762       break;
763     case cInt:
764       if (ArgLive) {
765         FI = MFI->CreateFixedObject(4, ArgOffset);
766         if (GPR_remaining > 0) {
767           F->addLiveIn(GPR[GPR_idx]);
768           BuildMI(BB, PPC::OR, 2, Reg).addReg(GPR[GPR_idx])
769             .addReg(GPR[GPR_idx]);
770         } else {
771           addFrameReference(BuildMI(BB, PPC::LWZ, 2, Reg), FI);
772         }
773       }
774       break;
775     case cLong:
776       if (ArgLive) {
777         FI = MFI->CreateFixedObject(8, ArgOffset);
778         if (GPR_remaining > 1) {
779           F->addLiveIn(GPR[GPR_idx]);
780           F->addLiveIn(GPR[GPR_idx+1]);
781           BuildMI(BB, PPC::OR, 2, Reg).addReg(GPR[GPR_idx])
782             .addReg(GPR[GPR_idx]);
783           BuildMI(BB, PPC::OR, 2, Reg+1).addReg(GPR[GPR_idx+1])
784             .addReg(GPR[GPR_idx+1]);
785         } else {
786           addFrameReference(BuildMI(BB, PPC::LWZ, 2, Reg), FI);
787           addFrameReference(BuildMI(BB, PPC::LWZ, 2, Reg+1), FI, 4);
788         }
789       }
790       // longs require 4 additional bytes and use 2 GPRs
791       ArgOffset += 4;
792       if (GPR_remaining > 1) {
793         GPR_remaining--;
794         GPR_idx++;
795       }
796       break;
797     case cFP32:
798      if (ArgLive) {
799         FI = MFI->CreateFixedObject(4, ArgOffset);
800
801         if (FPR_remaining > 0) {
802           F->addLiveIn(FPR[FPR_idx]);
803           BuildMI(BB, PPC::FMR, 1, Reg).addReg(FPR[FPR_idx]);
804           FPR_remaining--;
805           FPR_idx++;
806         } else {
807           addFrameReference(BuildMI(BB, PPC::LFS, 2, Reg), FI);
808         }
809       }
810       break;
811     case cFP64:
812       if (ArgLive) {
813         FI = MFI->CreateFixedObject(8, ArgOffset);
814
815         if (FPR_remaining > 0) {
816           F->addLiveIn(FPR[FPR_idx]);
817           BuildMI(BB, PPC::FMR, 1, Reg).addReg(FPR[FPR_idx]);
818           FPR_remaining--;
819           FPR_idx++;
820         } else {
821           addFrameReference(BuildMI(BB, PPC::LFD, 2, Reg), FI);
822         }
823       }
824
825       // doubles require 4 additional bytes and use 2 GPRs of param space
826       ArgOffset += 4;   
827       if (GPR_remaining > 0) {
828         GPR_remaining--;
829         GPR_idx++;
830       }
831       break;
832     default:
833       assert(0 && "Unhandled argument type!");
834     }
835     ArgOffset += 4;  // Each argument takes at least 4 bytes on the stack...
836     if (GPR_remaining > 0) {
837       GPR_remaining--;    // uses up 2 GPRs
838       GPR_idx++;
839     }
840   }
841
842   // If the function takes variable number of arguments, add a frame offset for
843   // the start of the first vararg value... this is used to expand
844   // llvm.va_start.
845   if (Fn.getFunctionType()->isVarArg())
846     VarArgsFrameIndex = MFI->CreateFixedObject(4, ArgOffset);
847
848   if (Fn.getReturnType() != Type::VoidTy)
849     switch (getClassB(Fn.getReturnType())) {
850     case cByte:
851     case cShort:
852     case cInt:
853       F->addLiveOut(PPC::R3);
854       break;
855     case cLong:
856       F->addLiveOut(PPC::R3);
857       F->addLiveOut(PPC::R4);
858       break;
859     case cFP32:
860     case cFP64:
861       F->addLiveOut(PPC::F1);
862       break;
863     }
864 }
865
866
867 /// SelectPHINodes - Insert machine code to generate phis.  This is tricky
868 /// because we have to generate our sources into the source basic blocks, not
869 /// the current one.
870 ///
871 void PPC32ISel::SelectPHINodes() {
872   const TargetInstrInfo &TII = *TM.getInstrInfo();
873   const Function &LF = *F->getFunction();  // The LLVM function...
874
875   MachineBasicBlock::iterator MFLRIt = F->begin()->begin();
876   if (GlobalBaseInitialized) {
877     // If we emitted a MFLR for the global base reg, get an iterator to an
878     // instruction after it.
879     while (MFLRIt->getOpcode() != PPC::MFLR)
880       ++MFLRIt;
881     ++MFLRIt;  // step one MI past it.
882   }
883
884   for (Function::const_iterator I = LF.begin(), E = LF.end(); I != E; ++I) {
885     const BasicBlock *BB = I;
886     MachineBasicBlock &MBB = *MBBMap[I];
887
888     // Loop over all of the PHI nodes in the LLVM basic block...
889     MachineBasicBlock::iterator PHIInsertPoint = MBB.begin();
890     for (BasicBlock::const_iterator I = BB->begin();
891          PHINode *PN = const_cast<PHINode*>(dyn_cast<PHINode>(I)); ++I) {
892
893       // Create a new machine instr PHI node, and insert it.
894       unsigned PHIReg = getReg(*PN);
895       MachineInstr *PhiMI = BuildMI(MBB, PHIInsertPoint,
896                                     PPC::PHI, PN->getNumOperands(), PHIReg);
897
898       MachineInstr *LongPhiMI = 0;
899       if (PN->getType() == Type::LongTy || PN->getType() == Type::ULongTy)
900         LongPhiMI = BuildMI(MBB, PHIInsertPoint,
901                             PPC::PHI, PN->getNumOperands(), PHIReg+1);
902
903       // PHIValues - Map of blocks to incoming virtual registers.  We use this
904       // so that we only initialize one incoming value for a particular block,
905       // even if the block has multiple entries in the PHI node.
906       //
907       std::map<MachineBasicBlock*, unsigned> PHIValues;
908
909       for (unsigned i = 0, e = PN->getNumIncomingValues(); i != e; ++i) {
910         MachineBasicBlock *PredMBB = 0;
911         for (MachineBasicBlock::pred_iterator PI = MBB.pred_begin (),
912              PE = MBB.pred_end (); PI != PE; ++PI)
913           if (PN->getIncomingBlock(i) == (*PI)->getBasicBlock()) {
914             PredMBB = *PI;
915             break;
916           }
917         assert (PredMBB && "Couldn't find incoming machine-cfg edge for phi");
918
919         unsigned ValReg;
920         std::map<MachineBasicBlock*, unsigned>::iterator EntryIt =
921           PHIValues.lower_bound(PredMBB);
922
923         if (EntryIt != PHIValues.end() && EntryIt->first == PredMBB) {
924           // We already inserted an initialization of the register for this
925           // predecessor.  Recycle it.
926           ValReg = EntryIt->second;
927         } else {
928           // Get the incoming value into a virtual register.
929           //
930           Value *Val = PN->getIncomingValue(i);
931
932           // If this is a constant or GlobalValue, we may have to insert code
933           // into the basic block to compute it into a virtual register.
934           if ((isa<Constant>(Val) && !isa<ConstantExpr>(Val)) ||
935               isa<GlobalValue>(Val)) {
936             // Simple constants get emitted at the end of the basic block,
937             // before any terminator instructions.  We "know" that the code to
938             // move a constant into a register will never clobber any flags.
939             ValReg = getReg(Val, PredMBB, PredMBB->getFirstTerminator());
940           } else {
941             // Because we don't want to clobber any values which might be in
942             // physical registers with the computation of this constant (which
943             // might be arbitrarily complex if it is a constant expression),
944             // just insert the computation at the top of the basic block.
945             MachineBasicBlock::iterator PI = PredMBB->begin();
946
947             // Skip over any PHI nodes though!
948             while (PI != PredMBB->end() && PI->getOpcode() == PPC::PHI)
949               ++PI;
950
951             // If this is the entry block, and if the entry block contains a
952             // MFLR instruction, emit this operation after it.  This is needed
953             // because global addresses use it.
954             if (PredMBB == F->begin())
955               PI = MFLRIt;
956
957             ValReg = getReg(Val, PredMBB, PI);
958           }
959
960           // Remember that we inserted a value for this PHI for this predecessor
961           PHIValues.insert(EntryIt, std::make_pair(PredMBB, ValReg));
962         }
963
964         PhiMI->addRegOperand(ValReg);
965         PhiMI->addMachineBasicBlockOperand(PredMBB);
966         if (LongPhiMI) {
967           LongPhiMI->addRegOperand(ValReg+1);
968           LongPhiMI->addMachineBasicBlockOperand(PredMBB);
969         }
970       }
971
972       // Now that we emitted all of the incoming values for the PHI node, make
973       // sure to reposition the InsertPoint after the PHI that we just added.
974       // This is needed because we might have inserted a constant into this
975       // block, right after the PHI's which is before the old insert point!
976       PHIInsertPoint = LongPhiMI ? LongPhiMI : PhiMI;
977       ++PHIInsertPoint;
978     }
979   }
980 }
981
982
983 // canFoldSetCCIntoBranchOrSelect - Return the setcc instruction if we can fold
984 // it into the conditional branch or select instruction which is the only user
985 // of the cc instruction.  This is the case if the conditional branch is the
986 // only user of the setcc, and if the setcc is in the same basic block as the
987 // conditional branch.
988 //
989 static SetCondInst *canFoldSetCCIntoBranchOrSelect(Value *V) {
990   if (SetCondInst *SCI = dyn_cast<SetCondInst>(V))
991     if (SCI->hasOneUse()) {
992       Instruction *User = cast<Instruction>(SCI->use_back());
993       if ((isa<BranchInst>(User) ||
994            (isa<SelectInst>(User) && User->getOperand(0) == V)) &&
995           SCI->getParent() == User->getParent())
996         return SCI;
997     }
998   return 0;
999 }
1000
1001 // canFoldGEPIntoLoadOrStore - Return the GEP instruction if we can fold it into
1002 // the load or store instruction that is the only user of the GEP.
1003 //
1004 static GetElementPtrInst *canFoldGEPIntoLoadOrStore(Value *V) {
1005   if (GetElementPtrInst *GEPI = dyn_cast<GetElementPtrInst>(V)) {
1006     bool AllUsesAreMem = true;
1007     for (Value::use_iterator I = GEPI->use_begin(), E = GEPI->use_end(); 
1008          I != E; ++I) {
1009       Instruction *User = cast<Instruction>(*I);
1010
1011       // If the GEP is the target of a store, but not the source, then we are ok
1012       // to fold it.
1013       if (isa<StoreInst>(User) &&
1014           GEPI->getParent() == User->getParent() &&
1015           User->getOperand(0) != GEPI &&
1016           User->getOperand(1) == GEPI)
1017         continue;
1018
1019       // If the GEP is the source of a load, then we're always ok to fold it
1020       if (isa<LoadInst>(User) &&
1021           GEPI->getParent() == User->getParent() &&
1022           User->getOperand(0) == GEPI)
1023         continue;
1024
1025       // if we got to this point, than the instruction was not a load or store
1026       // that we are capable of folding the GEP into.
1027       AllUsesAreMem = false;
1028       break;
1029     }
1030     if (AllUsesAreMem)
1031       return GEPI;
1032   }
1033   return 0;
1034 }
1035
1036
1037 // Return a fixed numbering for setcc instructions which does not depend on the
1038 // order of the opcodes.
1039 //
1040 static unsigned getSetCCNumber(unsigned Opcode) {
1041   switch (Opcode) {
1042   default: assert(0 && "Unknown setcc instruction!");
1043   case Instruction::SetEQ: return 0;
1044   case Instruction::SetNE: return 1;
1045   case Instruction::SetLT: return 2;
1046   case Instruction::SetGE: return 3;
1047   case Instruction::SetGT: return 4;
1048   case Instruction::SetLE: return 5;
1049   }
1050 }
1051
1052 static unsigned getPPCOpcodeForSetCCOpcode(unsigned Opcode) {
1053   switch (Opcode) {
1054   default: assert(0 && "Unknown setcc instruction!");
1055   case Instruction::SetEQ: return PPC::BEQ;
1056   case Instruction::SetNE: return PPC::BNE;
1057   case Instruction::SetLT: return PPC::BLT;
1058   case Instruction::SetGE: return PPC::BGE;
1059   case Instruction::SetGT: return PPC::BGT;
1060   case Instruction::SetLE: return PPC::BLE;
1061   }
1062 }
1063
1064 /// emitUCOM - emits an unordered FP compare.
1065 void PPC32ISel::emitUCOM(MachineBasicBlock *MBB, MachineBasicBlock::iterator IP,
1066                          unsigned LHS, unsigned RHS) {
1067     BuildMI(*MBB, IP, PPC::FCMPU, 2, PPC::CR0).addReg(LHS).addReg(RHS);
1068 }
1069
1070 unsigned PPC32ISel::ExtendOrClear(MachineBasicBlock *MBB,
1071                                   MachineBasicBlock::iterator IP,
1072                                   Value *Op0) {
1073   const Type *CompTy = Op0->getType();
1074   unsigned Reg = getReg(Op0, MBB, IP);
1075   unsigned Class = getClassB(CompTy);
1076
1077   // Since we know that boolean values will be either zero or one, we don't
1078   // have to extend or clear them.
1079   if (CompTy == Type::BoolTy)
1080     return Reg;
1081
1082   // Before we do a comparison or SetCC, we have to make sure that we truncate
1083   // the source registers appropriately.
1084   if (Class == cByte) {
1085     unsigned TmpReg = makeAnotherReg(CompTy);
1086     if (CompTy->isSigned())
1087       BuildMI(*MBB, IP, PPC::EXTSB, 1, TmpReg).addReg(Reg);
1088     else
1089       BuildMI(*MBB, IP, PPC::RLWINM, 4, TmpReg).addReg(Reg).addImm(0)
1090         .addImm(24).addImm(31);
1091     Reg = TmpReg;
1092   } else if (Class == cShort) {
1093     unsigned TmpReg = makeAnotherReg(CompTy);
1094     if (CompTy->isSigned())
1095       BuildMI(*MBB, IP, PPC::EXTSH, 1, TmpReg).addReg(Reg);
1096     else
1097       BuildMI(*MBB, IP, PPC::RLWINM, 4, TmpReg).addReg(Reg).addImm(0)
1098         .addImm(16).addImm(31);
1099     Reg = TmpReg;
1100   }
1101   return Reg;
1102 }
1103
1104 /// EmitComparison - emits a comparison of the two operands. The result is in
1105 /// CR0.
1106 ///
1107 void PPC32ISel::EmitComparison(unsigned OpNum, Value *Op0, Value *Op1,
1108                                MachineBasicBlock *MBB,
1109                                MachineBasicBlock::iterator IP) {
1110   // The arguments are already supposed to be of the same type.
1111   const Type *CompTy = Op0->getType();
1112   unsigned Class = getClassB(CompTy);
1113   unsigned Op0r = ExtendOrClear(MBB, IP, Op0);
1114   
1115   // Use crand for lt, gt and crandc for le, ge
1116   unsigned CROpcode = (OpNum == 2 || OpNum == 4) ? PPC::CRAND : PPC::CRANDC;
1117   // ? cr1[lt] : cr1[gt]
1118   unsigned CR1field = (OpNum == 2 || OpNum == 3) ? 4 : 5;
1119   // ? cr0[lt] : cr0[gt]
1120   unsigned CR0field = (OpNum == 2 || OpNum == 5) ? 0 : 1;
1121   unsigned Opcode = CompTy->isSigned() ? PPC::CMPW : PPC::CMPLW;
1122   unsigned OpcodeImm = CompTy->isSigned() ? PPC::CMPWI : PPC::CMPLWI;
1123
1124   // Special case handling of: cmp R, i
1125   if (ConstantInt *CI = dyn_cast<ConstantInt>(Op1)) {
1126     if (Class == cByte || Class == cShort || Class == cInt) {
1127       unsigned Op1v = CI->getRawValue() & 0xFFFF;
1128       unsigned OpClass = (CompTy->isSigned()) ? 0 : 2;
1129       
1130       // Treat compare like ADDI for the purposes of immediate suitability
1131       if (canUseAsImmediateForOpcode(CI, OpClass, false)) {
1132         BuildMI(*MBB, IP, OpcodeImm, 2, PPC::CR0).addReg(Op0r).addSImm(Op1v);
1133       } else {
1134         unsigned Op1r = getReg(Op1, MBB, IP);
1135         BuildMI(*MBB, IP, Opcode, 2, PPC::CR0).addReg(Op0r).addReg(Op1r);
1136       }
1137       return;
1138     } else {
1139       assert(Class == cLong && "Unknown integer class!");
1140       unsigned LowCst = CI->getRawValue();
1141       unsigned HiCst = CI->getRawValue() >> 32;
1142       if (OpNum < 2) {    // seteq, setne
1143         unsigned LoLow = makeAnotherReg(Type::IntTy);
1144         unsigned LoTmp = makeAnotherReg(Type::IntTy);
1145         unsigned HiLow = makeAnotherReg(Type::IntTy);
1146         unsigned HiTmp = makeAnotherReg(Type::IntTy);
1147         unsigned FinalTmp = makeAnotherReg(Type::IntTy);
1148
1149         BuildMI(*MBB, IP, PPC::XORI, 2, LoLow).addReg(Op0r+1)
1150           .addImm(LowCst & 0xFFFF);
1151         BuildMI(*MBB, IP, PPC::XORIS, 2, LoTmp).addReg(LoLow)
1152           .addImm(LowCst >> 16);
1153         BuildMI(*MBB, IP, PPC::XORI, 2, HiLow).addReg(Op0r)
1154           .addImm(HiCst & 0xFFFF);
1155         BuildMI(*MBB, IP, PPC::XORIS, 2, HiTmp).addReg(HiLow)
1156           .addImm(HiCst >> 16);
1157         BuildMI(*MBB, IP, PPC::ORo, 2, FinalTmp).addReg(LoTmp).addReg(HiTmp);
1158         return;
1159       } else {
1160         unsigned ConstReg = makeAnotherReg(CompTy);
1161         copyConstantToRegister(MBB, IP, CI, ConstReg);
1162
1163         // cr0 = r3 ccOpcode r5 or (r3 == r5 AND r4 ccOpcode r6)
1164         BuildMI(*MBB, IP, Opcode, 2, PPC::CR0).addReg(Op0r)
1165           .addReg(ConstReg);
1166         BuildMI(*MBB, IP, Opcode, 2, PPC::CR1).addReg(Op0r+1)
1167           .addReg(ConstReg+1);
1168         BuildMI(*MBB, IP, PPC::CRAND, 3).addImm(2).addImm(2).addImm(CR1field);
1169         BuildMI(*MBB, IP, PPC::CROR, 3).addImm(CR0field).addImm(CR0field)
1170           .addImm(2);
1171         return;
1172       }
1173     }
1174   }
1175
1176   unsigned Op1r = getReg(Op1, MBB, IP);
1177
1178   switch (Class) {
1179   default: assert(0 && "Unknown type class!");
1180   case cByte:
1181   case cShort:
1182   case cInt:
1183     BuildMI(*MBB, IP, Opcode, 2, PPC::CR0).addReg(Op0r).addReg(Op1r);
1184     break;
1185
1186   case cFP32:
1187   case cFP64:
1188     emitUCOM(MBB, IP, Op0r, Op1r);
1189     break;
1190
1191   case cLong:
1192     if (OpNum < 2) {    // seteq, setne
1193       unsigned LoTmp = makeAnotherReg(Type::IntTy);
1194       unsigned HiTmp = makeAnotherReg(Type::IntTy);
1195       unsigned FinalTmp = makeAnotherReg(Type::IntTy);
1196       BuildMI(*MBB, IP, PPC::XOR, 2, HiTmp).addReg(Op0r).addReg(Op1r);
1197       BuildMI(*MBB, IP, PPC::XOR, 2, LoTmp).addReg(Op0r+1).addReg(Op1r+1);
1198       BuildMI(*MBB, IP, PPC::ORo,  2, FinalTmp).addReg(LoTmp).addReg(HiTmp);
1199       break;  // Allow the sete or setne to be generated from flags set by OR
1200     } else {
1201       unsigned TmpReg1 = makeAnotherReg(Type::IntTy);
1202       unsigned TmpReg2 = makeAnotherReg(Type::IntTy);
1203
1204       // cr0 = r3 ccOpcode r5 or (r3 == r5 AND r4 ccOpcode r6)
1205       BuildMI(*MBB, IP, Opcode, 2, PPC::CR0).addReg(Op0r).addReg(Op1r);
1206       BuildMI(*MBB, IP, Opcode, 2, PPC::CR1).addReg(Op0r+1).addReg(Op1r+1);
1207       BuildMI(*MBB, IP, PPC::CRAND, 3).addImm(2).addImm(2).addImm(CR1field);
1208       BuildMI(*MBB, IP, PPC::CROR, 3).addImm(CR0field).addImm(CR0field)
1209         .addImm(2);
1210       return;
1211     }
1212   }
1213   return;
1214 }
1215
1216 /// visitSetCondInst - emit code to calculate the condition via
1217 /// EmitComparison(), and possibly store a 0 or 1 to a register as a result
1218 ///
1219 void PPC32ISel::visitSetCondInst(SetCondInst &I) {
1220   if (canFoldSetCCIntoBranchOrSelect(&I))
1221     return;
1222
1223   MachineBasicBlock::iterator MI = BB->end();
1224   Value *Op0 = I.getOperand(0), *Op1 = I.getOperand(1);
1225   const Type *Ty = Op0->getType();
1226   unsigned Class = getClassB(Ty);
1227   unsigned Opcode = I.getOpcode();
1228   unsigned OpNum = getSetCCNumber(Opcode);      
1229   unsigned DestReg = getReg(I);
1230
1231   // If the comparison type is byte, short, or int, then we can emit a
1232   // branchless version of the SetCC that puts 0 (false) or 1 (true) in the
1233   // destination register.
1234   if (Class <= cInt) {
1235     ConstantInt *CI = dyn_cast<ConstantInt>(Op1);
1236
1237     if (CI && CI->getRawValue() == 0) {
1238       unsigned Op0Reg = ExtendOrClear(BB, MI, Op0);
1239     
1240       // comparisons against constant zero and negative one often have shorter
1241       // and/or faster sequences than the set-and-branch general case, handled
1242       // below.
1243       switch(OpNum) {
1244       case 0: { // eq0
1245         unsigned TempReg = makeAnotherReg(Type::IntTy);
1246         BuildMI(*BB, MI, PPC::CNTLZW, 1, TempReg).addReg(Op0Reg);
1247         BuildMI(*BB, MI, PPC::RLWINM, 4, DestReg).addReg(TempReg).addImm(27)
1248           .addImm(5).addImm(31);
1249         break;
1250         } 
1251       case 1: { // ne0
1252         unsigned TempReg = makeAnotherReg(Type::IntTy);
1253         BuildMI(*BB, MI, PPC::ADDIC, 2, TempReg).addReg(Op0Reg).addSImm(-1);
1254         BuildMI(*BB, MI, PPC::SUBFE, 2, DestReg).addReg(TempReg).addReg(Op0Reg);
1255         break;
1256         } 
1257       case 2: { // lt0, always false if unsigned
1258         if (Ty->isSigned())
1259           BuildMI(*BB, MI, PPC::RLWINM, 4, DestReg).addReg(Op0Reg).addImm(1)
1260             .addImm(31).addImm(31);
1261         else
1262           BuildMI(*BB, MI, PPC::LI, 1, DestReg).addSImm(0);
1263         break;
1264         }
1265       case 3: { // ge0, always true if unsigned
1266         if (Ty->isSigned()) { 
1267           unsigned TempReg = makeAnotherReg(Type::IntTy);
1268           BuildMI(*BB, MI, PPC::RLWINM, 4, TempReg).addReg(Op0Reg).addImm(1)
1269             .addImm(31).addImm(31);
1270           BuildMI(*BB, MI, PPC::XORI, 2, DestReg).addReg(TempReg).addImm(1);
1271         } else {
1272           BuildMI(*BB, MI, PPC::LI, 1, DestReg).addSImm(1);
1273         }
1274         break;
1275         }
1276       case 4: { // gt0, equivalent to ne0 if unsigned
1277         unsigned Temp1 = makeAnotherReg(Type::IntTy);
1278         unsigned Temp2 = makeAnotherReg(Type::IntTy);
1279         if (Ty->isSigned()) { 
1280           BuildMI(*BB, MI, PPC::NEG, 2, Temp1).addReg(Op0Reg);
1281           BuildMI(*BB, MI, PPC::ANDC, 2, Temp2).addReg(Temp1).addReg(Op0Reg);
1282           BuildMI(*BB, MI, PPC::RLWINM, 4, DestReg).addReg(Temp2).addImm(1)
1283             .addImm(31).addImm(31);
1284         } else {
1285           BuildMI(*BB, MI, PPC::ADDIC, 2, Temp1).addReg(Op0Reg).addSImm(-1);
1286           BuildMI(*BB, MI, PPC::SUBFE, 2, DestReg).addReg(Temp1).addReg(Op0Reg);
1287         }
1288         break;
1289         }
1290       case 5: { // le0, equivalent to eq0 if unsigned
1291         unsigned Temp1 = makeAnotherReg(Type::IntTy);
1292         unsigned Temp2 = makeAnotherReg(Type::IntTy);
1293         if (Ty->isSigned()) { 
1294           BuildMI(*BB, MI, PPC::NEG, 2, Temp1).addReg(Op0Reg);
1295           BuildMI(*BB, MI, PPC::ORC, 2, Temp2).addReg(Op0Reg).addReg(Temp1);
1296           BuildMI(*BB, MI, PPC::RLWINM, 4, DestReg).addReg(Temp2).addImm(1)
1297             .addImm(31).addImm(31);
1298         } else {
1299           BuildMI(*BB, MI, PPC::CNTLZW, 1, Temp1).addReg(Op0Reg);
1300           BuildMI(*BB, MI, PPC::RLWINM, 4, DestReg).addReg(Temp1).addImm(27)
1301             .addImm(5).addImm(31);
1302         }
1303         break;
1304         }
1305       } // switch
1306       return;
1307         }
1308   }
1309   unsigned PPCOpcode = getPPCOpcodeForSetCCOpcode(Opcode);
1310
1311   // Create an iterator with which to insert the MBB for copying the false value
1312   // and the MBB to hold the PHI instruction for this SetCC.
1313   MachineBasicBlock *thisMBB = BB;
1314   const BasicBlock *LLVM_BB = BB->getBasicBlock();
1315   ilist<MachineBasicBlock>::iterator It = BB;
1316   ++It;
1317   
1318   //  thisMBB:
1319   //  ...
1320   //   cmpTY cr0, r1, r2
1321   //   %TrueValue = li 1
1322   //   bCC sinkMBB
1323   EmitComparison(OpNum, Op0, Op1, BB, BB->end());
1324   unsigned TrueValue = makeAnotherReg(I.getType());
1325   BuildMI(BB, PPC::LI, 1, TrueValue).addSImm(1);
1326   MachineBasicBlock *copy0MBB = new MachineBasicBlock(LLVM_BB);
1327   MachineBasicBlock *sinkMBB = new MachineBasicBlock(LLVM_BB);
1328   BuildMI(BB, PPCOpcode, 2).addReg(PPC::CR0).addMBB(sinkMBB);
1329   F->getBasicBlockList().insert(It, copy0MBB);
1330   F->getBasicBlockList().insert(It, sinkMBB);
1331   // Update machine-CFG edges
1332   BB->addSuccessor(copy0MBB);
1333   BB->addSuccessor(sinkMBB);
1334
1335   //  copy0MBB:
1336   //   %FalseValue = li 0
1337   //   fallthrough
1338   BB = copy0MBB;
1339   unsigned FalseValue = makeAnotherReg(I.getType());
1340   BuildMI(BB, PPC::LI, 1, FalseValue).addSImm(0);
1341   // Update machine-CFG edges
1342   BB->addSuccessor(sinkMBB);
1343
1344   //  sinkMBB:
1345   //   %Result = phi [ %FalseValue, copy0MBB ], [ %TrueValue, thisMBB ]
1346   //  ...
1347   BB = sinkMBB;
1348   BuildMI(BB, PPC::PHI, 4, DestReg).addReg(FalseValue)
1349     .addMBB(copy0MBB).addReg(TrueValue).addMBB(thisMBB);
1350 }
1351
1352 void PPC32ISel::visitSelectInst(SelectInst &SI) {
1353   unsigned DestReg = getReg(SI);
1354   MachineBasicBlock::iterator MII = BB->end();
1355   emitSelectOperation(BB, MII, SI.getCondition(), SI.getTrueValue(),
1356                       SI.getFalseValue(), DestReg);
1357 }
1358  
1359 /// emitSelect - Common code shared between visitSelectInst and the constant
1360 /// expression support.
1361 void PPC32ISel::emitSelectOperation(MachineBasicBlock *MBB,
1362                                     MachineBasicBlock::iterator IP,
1363                                     Value *Cond, Value *TrueVal, 
1364                                     Value *FalseVal, unsigned DestReg) {
1365   unsigned SelectClass = getClassB(TrueVal->getType());
1366   unsigned Opcode;
1367
1368   // See if we can fold the setcc into the select instruction, or if we have
1369   // to get the register of the Cond value
1370   if (SetCondInst *SCI = canFoldSetCCIntoBranchOrSelect(Cond)) {
1371     // We successfully folded the setcc into the select instruction.
1372     unsigned OpNum = getSetCCNumber(SCI->getOpcode());
1373     if (OpNum >= 2 && OpNum <= 5) {
1374       unsigned SetCondClass = getClassB(SCI->getOperand(0)->getType());
1375       if ((SetCondClass == cFP32 || SetCondClass == cFP64) &&
1376           (SelectClass == cFP32 || SelectClass == cFP64)) {
1377         unsigned CondReg = getReg(SCI->getOperand(0), MBB, IP);
1378         unsigned TrueReg = getReg(TrueVal, MBB, IP);
1379         unsigned FalseReg = getReg(FalseVal, MBB, IP);
1380         // if the comparison of the floating point value used to for the select
1381         // is against 0, then we can emit an fsel without subtraction.
1382         ConstantFP *Op1C = dyn_cast<ConstantFP>(SCI->getOperand(1));
1383         if (Op1C && (Op1C->isExactlyValue(-0.0) || Op1C->isExactlyValue(0.0))) {
1384           switch(OpNum) {
1385           case 2:   // LT
1386             BuildMI(*MBB, IP, PPC::FSEL, 3, DestReg).addReg(CondReg)
1387               .addReg(FalseReg).addReg(TrueReg);
1388             break;
1389           case 3:   // GE == !LT
1390             BuildMI(*MBB, IP, PPC::FSEL, 3, DestReg).addReg(CondReg)
1391               .addReg(TrueReg).addReg(FalseReg);
1392             break;
1393           case 4: {  // GT
1394             unsigned NegatedReg = makeAnotherReg(SCI->getOperand(0)->getType());
1395             BuildMI(*MBB, IP, PPC::FNEG, 1, NegatedReg).addReg(CondReg);
1396             BuildMI(*MBB, IP, PPC::FSEL, 3, DestReg).addReg(NegatedReg)
1397               .addReg(FalseReg).addReg(TrueReg);
1398             }
1399             break;
1400           case 5: {  // LE == !GT
1401             unsigned NegatedReg = makeAnotherReg(SCI->getOperand(0)->getType());
1402             BuildMI(*MBB, IP, PPC::FNEG, 1, NegatedReg).addReg(CondReg);
1403             BuildMI(*MBB, IP, PPC::FSEL, 3, DestReg).addReg(NegatedReg)
1404               .addReg(TrueReg).addReg(FalseReg);
1405             }
1406             break;
1407           default:
1408             assert(0 && "Invalid SetCC opcode to fsel");
1409             abort();
1410             break;
1411           }
1412         } else {
1413           unsigned OtherCondReg = getReg(SCI->getOperand(1), MBB, IP);
1414           unsigned SelectReg = makeAnotherReg(SCI->getOperand(0)->getType());
1415           switch(OpNum) {
1416           case 2:   // LT
1417             BuildMI(*MBB, IP, PPC::FSUB, 2, SelectReg).addReg(CondReg)
1418               .addReg(OtherCondReg);
1419             BuildMI(*MBB, IP, PPC::FSEL, 3, DestReg).addReg(SelectReg)
1420               .addReg(FalseReg).addReg(TrueReg);
1421             break;
1422           case 3:   // GE == !LT
1423             BuildMI(*MBB, IP, PPC::FSUB, 2, SelectReg).addReg(CondReg)
1424               .addReg(OtherCondReg);
1425             BuildMI(*MBB, IP, PPC::FSEL, 3, DestReg).addReg(SelectReg)
1426               .addReg(TrueReg).addReg(FalseReg);
1427             break;
1428           case 4:   // GT
1429             BuildMI(*MBB, IP, PPC::FSUB, 2, SelectReg).addReg(OtherCondReg)
1430               .addReg(CondReg);
1431             BuildMI(*MBB, IP, PPC::FSEL, 3, DestReg).addReg(SelectReg)
1432               .addReg(FalseReg).addReg(TrueReg);
1433             break;
1434           case 5:   // LE == !GT
1435             BuildMI(*MBB, IP, PPC::FSUB, 2, SelectReg).addReg(OtherCondReg)
1436               .addReg(CondReg);
1437             BuildMI(*MBB, IP, PPC::FSEL, 3, DestReg).addReg(SelectReg)
1438               .addReg(TrueReg).addReg(FalseReg);
1439             break;
1440           default:
1441             assert(0 && "Invalid SetCC opcode to fsel");
1442             abort();
1443             break;
1444           }
1445         }
1446         return;
1447       }
1448     }
1449     EmitComparison(OpNum, SCI->getOperand(0),SCI->getOperand(1),MBB,IP);
1450     Opcode = getPPCOpcodeForSetCCOpcode(SCI->getOpcode());
1451   } else {
1452     unsigned CondReg = getReg(Cond, MBB, IP);
1453     BuildMI(*MBB, IP, PPC::CMPWI, 2, PPC::CR0).addReg(CondReg).addSImm(0);
1454     Opcode = getPPCOpcodeForSetCCOpcode(Instruction::SetNE);
1455   }
1456
1457   MachineBasicBlock *thisMBB = BB;
1458   const BasicBlock *LLVM_BB = BB->getBasicBlock();
1459   ilist<MachineBasicBlock>::iterator It = BB;
1460   ++It;
1461
1462   //  thisMBB:
1463   //  ...
1464   //   TrueVal = ...
1465   //   cmpTY cr0, r1, r2
1466   //   bCC copy1MBB
1467   //   fallthrough --> copy0MBB
1468   MachineBasicBlock *copy0MBB = new MachineBasicBlock(LLVM_BB);
1469   MachineBasicBlock *sinkMBB = new MachineBasicBlock(LLVM_BB);
1470   unsigned TrueValue = getReg(TrueVal);
1471   BuildMI(BB, Opcode, 2).addReg(PPC::CR0).addMBB(sinkMBB);
1472   F->getBasicBlockList().insert(It, copy0MBB);
1473   F->getBasicBlockList().insert(It, sinkMBB);
1474   // Update machine-CFG edges
1475   BB->addSuccessor(copy0MBB);
1476   BB->addSuccessor(sinkMBB);
1477
1478   //  copy0MBB:
1479   //   %FalseValue = ...
1480   //   # fallthrough to sinkMBB
1481   BB = copy0MBB;
1482   unsigned FalseValue = getReg(FalseVal);
1483   // Update machine-CFG edges
1484   BB->addSuccessor(sinkMBB);
1485
1486   //  sinkMBB:
1487   //   %Result = phi [ %FalseValue, copy0MBB ], [ %TrueValue, thisMBB ]
1488   //  ...
1489   BB = sinkMBB;
1490   BuildMI(BB, PPC::PHI, 4, DestReg).addReg(FalseValue)
1491     .addMBB(copy0MBB).addReg(TrueValue).addMBB(thisMBB);
1492     
1493   // For a register pair representing a long value, define the top part.
1494   if (getClassB(TrueVal->getType()) == cLong)
1495     BuildMI(BB, PPC::PHI, 4, DestReg+1).addReg(FalseValue+1)
1496       .addMBB(copy0MBB).addReg(TrueValue+1).addMBB(thisMBB);
1497 }
1498
1499
1500
1501 /// promote32 - Emit instructions to turn a narrow operand into a 32-bit-wide
1502 /// operand, in the specified target register.
1503 ///
1504 void PPC32ISel::promote32(unsigned targetReg, const ValueRecord &VR) {
1505   bool isUnsigned = VR.Ty->isUnsigned() || VR.Ty == Type::BoolTy;
1506
1507   Value *Val = VR.Val;
1508   const Type *Ty = VR.Ty;
1509   if (Val) {
1510     if (Constant *C = dyn_cast<Constant>(Val)) {
1511       Val = ConstantExpr::getCast(C, Type::IntTy);
1512       if (isa<ConstantExpr>(Val))   // Could not fold
1513         Val = C;
1514       else
1515         Ty = Type::IntTy;           // Folded!
1516     }
1517
1518     // If this is a simple constant, just emit a load directly to avoid the copy
1519     if (ConstantInt *CI = dyn_cast<ConstantInt>(Val)) {
1520       copyConstantToRegister(BB, BB->end(), CI, targetReg);
1521       return;
1522     }
1523   }
1524
1525   // Make sure we have the register number for this value...
1526   unsigned Reg = Val ? getReg(Val) : VR.Reg;
1527   switch (getClassB(Ty)) {
1528   case cByte:
1529     // Extend value into target register (8->32)
1530     if (Ty == Type::BoolTy)
1531       BuildMI(BB, PPC::OR, 2, targetReg).addReg(Reg).addReg(Reg);
1532     else if (isUnsigned)
1533       BuildMI(BB, PPC::RLWINM, 4, targetReg).addReg(Reg).addZImm(0)
1534         .addZImm(24).addZImm(31);
1535     else
1536       BuildMI(BB, PPC::EXTSB, 1, targetReg).addReg(Reg);
1537     break;
1538   case cShort:
1539     // Extend value into target register (16->32)
1540     if (isUnsigned)
1541       BuildMI(BB, PPC::RLWINM, 4, targetReg).addReg(Reg).addZImm(0)
1542         .addZImm(16).addZImm(31);
1543     else
1544       BuildMI(BB, PPC::EXTSH, 1, targetReg).addReg(Reg);
1545     break;
1546   case cInt:
1547     // Move value into target register (32->32)
1548     BuildMI(BB, PPC::OR, 2, targetReg).addReg(Reg).addReg(Reg);
1549     break;
1550   default:
1551     assert(0 && "Unpromotable operand class in promote32");
1552   }
1553 }
1554
1555 /// visitReturnInst - implemented with BLR
1556 ///
1557 void PPC32ISel::visitReturnInst(ReturnInst &I) {
1558   // Only do the processing if this is a non-void return
1559   if (I.getNumOperands() > 0) {
1560     Value *RetVal = I.getOperand(0);
1561     switch (getClassB(RetVal->getType())) {
1562     case cByte:   // integral return values: extend or move into r3 and return
1563     case cShort:
1564     case cInt:
1565       promote32(PPC::R3, ValueRecord(RetVal));
1566       break;
1567     case cFP32:
1568     case cFP64: {   // Floats & Doubles: Return in f1
1569       unsigned RetReg = getReg(RetVal);
1570       BuildMI(BB, PPC::FMR, 1, PPC::F1).addReg(RetReg);
1571       break;
1572     }
1573     case cLong: {
1574       unsigned RetReg = getReg(RetVal);
1575       BuildMI(BB, PPC::OR, 2, PPC::R3).addReg(RetReg).addReg(RetReg);
1576       BuildMI(BB, PPC::OR, 2, PPC::R4).addReg(RetReg+1).addReg(RetReg+1);
1577       break;
1578     }
1579     default:
1580       visitInstruction(I);
1581     }
1582   }
1583   BuildMI(BB, PPC::BLR, 1).addImm(0);
1584 }
1585
1586 // getBlockAfter - Return the basic block which occurs lexically after the
1587 // specified one.
1588 static inline BasicBlock *getBlockAfter(BasicBlock *BB) {
1589   Function::iterator I = BB; ++I;  // Get iterator to next block
1590   return I != BB->getParent()->end() ? &*I : 0;
1591 }
1592
1593 /// visitBranchInst - Handle conditional and unconditional branches here.  Note
1594 /// that since code layout is frozen at this point, that if we are trying to
1595 /// jump to a block that is the immediate successor of the current block, we can
1596 /// just make a fall-through (but we don't currently).
1597 ///
1598 void PPC32ISel::visitBranchInst(BranchInst &BI) {
1599   // Update machine-CFG edges
1600   BB->addSuccessor(MBBMap[BI.getSuccessor(0)]);
1601   if (BI.isConditional())
1602     BB->addSuccessor(MBBMap[BI.getSuccessor(1)]);
1603   
1604   BasicBlock *NextBB = getBlockAfter(BI.getParent());  // BB after current one
1605
1606   if (!BI.isConditional()) {  // Unconditional branch?
1607     if (BI.getSuccessor(0) != NextBB) 
1608       BuildMI(BB, PPC::B, 1).addMBB(MBBMap[BI.getSuccessor(0)]);
1609     return;
1610   }
1611   
1612   // See if we can fold the setcc into the branch itself...
1613   SetCondInst *SCI = canFoldSetCCIntoBranchOrSelect(BI.getCondition());
1614   if (SCI == 0) {
1615     // Nope, cannot fold setcc into this branch.  Emit a branch on a condition
1616     // computed some other way...
1617     unsigned condReg = getReg(BI.getCondition());
1618     BuildMI(BB, PPC::CMPLI, 3, PPC::CR0).addImm(0).addReg(condReg)
1619       .addImm(0);
1620     if (BI.getSuccessor(1) == NextBB) {
1621       if (BI.getSuccessor(0) != NextBB)
1622         BuildMI(BB, PPC::COND_BRANCH, 4).addReg(PPC::CR0).addImm(PPC::BNE)
1623           .addMBB(MBBMap[BI.getSuccessor(0)])
1624           .addMBB(MBBMap[BI.getSuccessor(1)]);
1625     } else {
1626       BuildMI(BB, PPC::COND_BRANCH, 4).addReg(PPC::CR0).addImm(PPC::BEQ)
1627         .addMBB(MBBMap[BI.getSuccessor(1)])
1628         .addMBB(MBBMap[BI.getSuccessor(0)]);
1629       if (BI.getSuccessor(0) != NextBB)
1630         BuildMI(BB, PPC::B, 1).addMBB(MBBMap[BI.getSuccessor(0)]);
1631     }
1632     return;
1633   }
1634
1635   unsigned OpNum = getSetCCNumber(SCI->getOpcode());
1636   unsigned Opcode = getPPCOpcodeForSetCCOpcode(SCI->getOpcode());
1637   MachineBasicBlock::iterator MII = BB->end();
1638   EmitComparison(OpNum, SCI->getOperand(0), SCI->getOperand(1), BB,MII);
1639   
1640   if (BI.getSuccessor(0) != NextBB) {
1641     BuildMI(BB, PPC::COND_BRANCH, 4).addReg(PPC::CR0).addImm(Opcode)
1642       .addMBB(MBBMap[BI.getSuccessor(0)])
1643       .addMBB(MBBMap[BI.getSuccessor(1)]);
1644     if (BI.getSuccessor(1) != NextBB)
1645       BuildMI(BB, PPC::B, 1).addMBB(MBBMap[BI.getSuccessor(1)]);
1646   } else {
1647     // Change to the inverse condition...
1648     if (BI.getSuccessor(1) != NextBB) {
1649       Opcode = PPC32InstrInfo::invertPPCBranchOpcode(Opcode);
1650       BuildMI(BB, PPC::COND_BRANCH, 4).addReg(PPC::CR0).addImm(Opcode)
1651         .addMBB(MBBMap[BI.getSuccessor(1)])
1652         .addMBB(MBBMap[BI.getSuccessor(0)]);
1653     }
1654   }
1655 }
1656
1657 /// doCall - This emits an abstract call instruction, setting up the arguments
1658 /// and the return value as appropriate.  For the actual function call itself,
1659 /// it inserts the specified CallMI instruction into the stream.
1660 ///
1661 /// FIXME: See Documentation at the following URL for "correct" behavior
1662 /// <http://developer.apple.com/documentation/DeveloperTools/Conceptual/MachORuntime/PowerPCConventions/chapter_3_section_5.html>
1663 void PPC32ISel::doCall(const ValueRecord &Ret, MachineInstr *CallMI,
1664                        const std::vector<ValueRecord> &Args, bool isVarArg) {
1665   // Count how many bytes are to be pushed on the stack, including the linkage
1666   // area, and parameter passing area.
1667   unsigned NumBytes = 24;
1668   unsigned ArgOffset = 24;
1669
1670   if (!Args.empty()) {
1671     for (unsigned i = 0, e = Args.size(); i != e; ++i)
1672       switch (getClassB(Args[i].Ty)) {
1673       case cByte: case cShort: case cInt:
1674         NumBytes += 4; break;
1675       case cLong:
1676         NumBytes += 8; break;
1677       case cFP32:
1678         NumBytes += 4; break;
1679       case cFP64:
1680         NumBytes += 8; break;
1681         break;
1682       default: assert(0 && "Unknown class!");
1683       }
1684
1685     // Just to be safe, we'll always reserve the full 24 bytes of linkage area 
1686     // plus 32 bytes of argument space in case any called code gets funky on us.
1687     if (NumBytes < 56) NumBytes = 56;
1688
1689     // Adjust the stack pointer for the new arguments...
1690     // These operations are automatically eliminated by the prolog/epilog pass
1691     BuildMI(BB, PPC::ADJCALLSTACKDOWN, 1).addImm(NumBytes);
1692
1693     // Arguments go on the stack in reverse order, as specified by the ABI.
1694     // Offset to the paramater area on the stack is 24.
1695     int GPR_remaining = 8, FPR_remaining = 13;
1696     unsigned GPR_idx = 0, FPR_idx = 0;
1697     static const unsigned GPR[] = { 
1698       PPC::R3, PPC::R4, PPC::R5, PPC::R6,
1699       PPC::R7, PPC::R8, PPC::R9, PPC::R10,
1700     };
1701     static const unsigned FPR[] = {
1702       PPC::F1, PPC::F2, PPC::F3, PPC::F4, PPC::F5, PPC::F6, 
1703       PPC::F7, PPC::F8, PPC::F9, PPC::F10, PPC::F11, PPC::F12, 
1704       PPC::F13
1705     };
1706     
1707     for (unsigned i = 0, e = Args.size(); i != e; ++i) {
1708       unsigned ArgReg;
1709       switch (getClassB(Args[i].Ty)) {
1710       case cByte:
1711       case cShort:
1712         // Promote arg to 32 bits wide into a temporary register...
1713         ArgReg = makeAnotherReg(Type::UIntTy);
1714         promote32(ArgReg, Args[i]);
1715           
1716         // Reg or stack?
1717         if (GPR_remaining > 0) {
1718           BuildMI(BB, PPC::OR, 2, GPR[GPR_idx]).addReg(ArgReg)
1719             .addReg(ArgReg);
1720           CallMI->addRegOperand(GPR[GPR_idx], MachineOperand::Use);
1721         }
1722         if (GPR_remaining <= 0 || isVarArg) {
1723           BuildMI(BB, PPC::STW, 3).addReg(ArgReg).addSImm(ArgOffset)
1724             .addReg(PPC::R1);
1725         }
1726         break;
1727       case cInt:
1728         ArgReg = Args[i].Val ? getReg(Args[i].Val) : Args[i].Reg;
1729
1730         // Reg or stack?
1731         if (GPR_remaining > 0) {
1732           BuildMI(BB, PPC::OR, 2, GPR[GPR_idx]).addReg(ArgReg)
1733             .addReg(ArgReg);
1734           CallMI->addRegOperand(GPR[GPR_idx], MachineOperand::Use);
1735         }
1736         if (GPR_remaining <= 0 || isVarArg) {
1737           BuildMI(BB, PPC::STW, 3).addReg(ArgReg).addSImm(ArgOffset)
1738             .addReg(PPC::R1);
1739         }
1740         break;
1741       case cLong:
1742         ArgReg = Args[i].Val ? getReg(Args[i].Val) : Args[i].Reg;
1743
1744         // Reg or stack?  Note that PPC calling conventions state that long args
1745         // are passed rN = hi, rN+1 = lo, opposite of LLVM.
1746         if (GPR_remaining > 1) {
1747           BuildMI(BB, PPC::OR, 2, GPR[GPR_idx]).addReg(ArgReg)
1748             .addReg(ArgReg);
1749           BuildMI(BB, PPC::OR, 2, GPR[GPR_idx+1]).addReg(ArgReg+1)
1750             .addReg(ArgReg+1);
1751           CallMI->addRegOperand(GPR[GPR_idx], MachineOperand::Use);
1752           CallMI->addRegOperand(GPR[GPR_idx+1], MachineOperand::Use);
1753         }
1754         if (GPR_remaining <= 1 || isVarArg) {
1755           BuildMI(BB, PPC::STW, 3).addReg(ArgReg).addSImm(ArgOffset)
1756             .addReg(PPC::R1);
1757           BuildMI(BB, PPC::STW, 3).addReg(ArgReg+1).addSImm(ArgOffset+4)
1758             .addReg(PPC::R1);
1759         }
1760
1761         ArgOffset += 4;        // 8 byte entry, not 4.
1762         GPR_remaining -= 1;    // uses up 2 GPRs
1763         GPR_idx += 1;
1764         break;
1765       case cFP32:
1766         ArgReg = Args[i].Val ? getReg(Args[i].Val) : Args[i].Reg;
1767         // Reg or stack?
1768         if (FPR_remaining > 0) {
1769           BuildMI(BB, PPC::FMR, 1, FPR[FPR_idx]).addReg(ArgReg);
1770           CallMI->addRegOperand(FPR[FPR_idx], MachineOperand::Use);
1771           FPR_remaining--;
1772           FPR_idx++;
1773           
1774           // If this is a vararg function, and there are GPRs left, also
1775           // pass the float in an int.  Otherwise, put it on the stack.
1776           if (isVarArg) {
1777             BuildMI(BB, PPC::STFS, 3).addReg(ArgReg).addSImm(ArgOffset)
1778             .addReg(PPC::R1);
1779             if (GPR_remaining > 0) {
1780               BuildMI(BB, PPC::LWZ, 2, GPR[GPR_idx])
1781               .addSImm(ArgOffset).addReg(PPC::R1);
1782               CallMI->addRegOperand(GPR[GPR_idx], MachineOperand::Use);
1783             }
1784           }
1785         } else {
1786           BuildMI(BB, PPC::STFS, 3).addReg(ArgReg).addSImm(ArgOffset)
1787           .addReg(PPC::R1);
1788         }
1789         break;
1790       case cFP64:
1791         ArgReg = Args[i].Val ? getReg(Args[i].Val) : Args[i].Reg;
1792         // Reg or stack?
1793         if (FPR_remaining > 0) {
1794           BuildMI(BB, PPC::FMR, 1, FPR[FPR_idx]).addReg(ArgReg);
1795           CallMI->addRegOperand(FPR[FPR_idx], MachineOperand::Use);
1796           FPR_remaining--;
1797           FPR_idx++;
1798           // For vararg functions, must pass doubles via int regs as well
1799           if (isVarArg) {
1800             BuildMI(BB, PPC::STFD, 3).addReg(ArgReg).addSImm(ArgOffset)
1801             .addReg(PPC::R1);
1802             
1803             // Doubles can be split across reg + stack for varargs
1804             if (GPR_remaining > 0) {
1805               BuildMI(BB, PPC::LWZ, 2, GPR[GPR_idx]).addSImm(ArgOffset)
1806               .addReg(PPC::R1);
1807               CallMI->addRegOperand(GPR[GPR_idx], MachineOperand::Use);
1808             }
1809             if (GPR_remaining > 1) {
1810               BuildMI(BB, PPC::LWZ, 2, GPR[GPR_idx+1])
1811                 .addSImm(ArgOffset+4).addReg(PPC::R1);
1812               CallMI->addRegOperand(GPR[GPR_idx+1], MachineOperand::Use);
1813             }
1814           }
1815         } else {
1816           BuildMI(BB, PPC::STFD, 3).addReg(ArgReg).addSImm(ArgOffset)
1817           .addReg(PPC::R1);
1818         }
1819         // Doubles use 8 bytes, and 2 GPRs worth of param space
1820         ArgOffset += 4;
1821         GPR_remaining--;
1822         GPR_idx++;
1823         break;
1824         
1825       default: assert(0 && "Unknown class!");
1826       }
1827       ArgOffset += 4;
1828       GPR_remaining--;
1829       GPR_idx++;
1830     }
1831   } else {
1832     BuildMI(BB, PPC::ADJCALLSTACKDOWN, 1).addImm(NumBytes);
1833   }
1834   
1835   BuildMI(BB, PPC::IMPLICIT_DEF, 0, PPC::LR);
1836   BB->push_back(CallMI);
1837   
1838   // These functions are automatically eliminated by the prolog/epilog pass
1839   BuildMI(BB, PPC::ADJCALLSTACKUP, 1).addImm(NumBytes);
1840
1841   // If there is a return value, scavenge the result from the location the call
1842   // leaves it in...
1843   //
1844   if (Ret.Ty != Type::VoidTy) {
1845     unsigned DestClass = getClassB(Ret.Ty);
1846     switch (DestClass) {
1847     case cByte:
1848     case cShort:
1849     case cInt:
1850       // Integral results are in r3
1851       BuildMI(BB, PPC::OR, 2, Ret.Reg).addReg(PPC::R3).addReg(PPC::R3);
1852       break;
1853     case cFP32:   // Floating-point return values live in f1
1854     case cFP64:
1855       BuildMI(BB, PPC::FMR, 1, Ret.Reg).addReg(PPC::F1);
1856       break;
1857     case cLong:   // Long values are in r3:r4
1858       BuildMI(BB, PPC::OR, 2, Ret.Reg).addReg(PPC::R3).addReg(PPC::R3);
1859       BuildMI(BB, PPC::OR, 2, Ret.Reg+1).addReg(PPC::R4).addReg(PPC::R4);
1860       break;
1861     default: assert(0 && "Unknown class!");
1862     }
1863   }
1864 }
1865
1866
1867 /// visitCallInst - Push args on stack and do a procedure call instruction.
1868 void PPC32ISel::visitCallInst(CallInst &CI) {
1869   MachineInstr *TheCall;
1870   Function *F = CI.getCalledFunction();
1871   if (F) {
1872     // Is it an intrinsic function call?
1873     if (Intrinsic::ID ID = (Intrinsic::ID)F->getIntrinsicID()) {
1874       visitIntrinsicCall(ID, CI);   // Special intrinsics are not handled here
1875       return;
1876     }
1877     // Emit a CALL instruction with PC-relative displacement.
1878     TheCall = BuildMI(PPC::CALLpcrel, 1).addGlobalAddress(F, true);
1879   } else {  // Emit an indirect call through the CTR
1880     unsigned Reg = getReg(CI.getCalledValue());
1881     BuildMI(BB, PPC::OR, 2, PPC::R12).addReg(Reg).addReg(Reg);
1882     BuildMI(BB, PPC::MTCTR, 1).addReg(PPC::R12);
1883     TheCall = BuildMI(PPC::CALLindirect, 3).addZImm(20).addZImm(0)
1884       .addReg(PPC::R12);
1885   }
1886
1887   std::vector<ValueRecord> Args;
1888   for (unsigned i = 1, e = CI.getNumOperands(); i != e; ++i)
1889     Args.push_back(ValueRecord(CI.getOperand(i)));
1890
1891   unsigned DestReg = CI.getType() != Type::VoidTy ? getReg(CI) : 0;
1892   bool isVarArg = F ? F->getFunctionType()->isVarArg() : true;
1893   doCall(ValueRecord(DestReg, CI.getType()), TheCall, Args, isVarArg);
1894 }         
1895
1896
1897 /// dyncastIsNan - Return the operand of an isnan operation if this is an isnan.
1898 ///
1899 static Value *dyncastIsNan(Value *V) {
1900   if (CallInst *CI = dyn_cast<CallInst>(V))
1901     if (Function *F = CI->getCalledFunction())
1902       if (F->getIntrinsicID() == Intrinsic::isunordered)
1903         return CI->getOperand(1);
1904   return 0;
1905 }
1906
1907 /// isOnlyUsedByUnorderedComparisons - Return true if this value is only used by
1908 /// or's whos operands are all calls to the isnan predicate.
1909 static bool isOnlyUsedByUnorderedComparisons(Value *V) {
1910   assert(dyncastIsNan(V) && "The value isn't an isnan call!");
1911
1912   // Check all uses, which will be or's of isnans if this predicate is true.
1913   for (Value::use_iterator UI = V->use_begin(), E = V->use_end(); UI != E;++UI){
1914     Instruction *I = cast<Instruction>(*UI);
1915     if (I->getOpcode() != Instruction::Or) return false;
1916     if (I->getOperand(0) != V && !dyncastIsNan(I->getOperand(0))) return false;
1917     if (I->getOperand(1) != V && !dyncastIsNan(I->getOperand(1))) return false;
1918   }
1919
1920   return true;
1921 }
1922
1923 /// LowerUnknownIntrinsicFunctionCalls - This performs a prepass over the
1924 /// function, lowering any calls to unknown intrinsic functions into the
1925 /// equivalent LLVM code.
1926 ///
1927 void PPC32ISel::LowerUnknownIntrinsicFunctionCalls(Function &F) {
1928   for (Function::iterator BB = F.begin(), E = F.end(); BB != E; ++BB)
1929     for (BasicBlock::iterator I = BB->begin(), E = BB->end(); I != E; )
1930       if (CallInst *CI = dyn_cast<CallInst>(I++))
1931         if (Function *F = CI->getCalledFunction())
1932           switch (F->getIntrinsicID()) {
1933           case Intrinsic::not_intrinsic:
1934           case Intrinsic::vastart:
1935           case Intrinsic::vacopy:
1936           case Intrinsic::vaend:
1937           case Intrinsic::returnaddress:
1938           case Intrinsic::frameaddress:
1939             // FIXME: should lower these ourselves
1940             // case Intrinsic::isunordered:
1941             // case Intrinsic::memcpy: -> doCall().  system memcpy almost
1942             // guaranteed to be faster than anything we generate ourselves
1943             // We directly implement these intrinsics
1944             break;
1945           case Intrinsic::readio: {
1946             // On PPC, memory operations are in-order.  Lower this intrinsic
1947             // into a volatile load.
1948             LoadInst * LI = new LoadInst(CI->getOperand(1), "", true, CI);
1949             CI->replaceAllUsesWith(LI);
1950             BB->getInstList().erase(CI);
1951             break;
1952           }
1953           case Intrinsic::writeio: {
1954             // On PPC, memory operations are in-order.  Lower this intrinsic
1955             // into a volatile store.
1956             StoreInst *SI = new StoreInst(CI->getOperand(1),
1957                                           CI->getOperand(2), true, CI);
1958             CI->replaceAllUsesWith(SI);
1959             BB->getInstList().erase(CI);
1960             break;
1961           }
1962           default: {
1963             // All other intrinsic calls we must lower.
1964             BasicBlock::iterator me(CI);
1965             bool atBegin(BB->begin() == me);
1966             if (!atBegin)
1967               --me;
1968             TM.getIntrinsicLowering().LowerIntrinsicCall(CI);
1969             // Move iterator to instruction after call
1970             I = atBegin ? BB->begin() : ++me;
1971           }
1972           }
1973 }
1974
1975 void PPC32ISel::visitIntrinsicCall(Intrinsic::ID ID, CallInst &CI) {
1976   unsigned TmpReg1, TmpReg2, TmpReg3;
1977   switch (ID) {
1978   case Intrinsic::vastart:
1979     // Get the address of the first vararg value...
1980     TmpReg1 = getReg(CI);
1981     addFrameReference(BuildMI(BB, PPC::ADDI, 2, TmpReg1), VarArgsFrameIndex, 
1982                       0, false);
1983     return;
1984
1985   case Intrinsic::vacopy:
1986     TmpReg1 = getReg(CI);
1987     TmpReg2 = getReg(CI.getOperand(1));
1988     BuildMI(BB, PPC::OR, 2, TmpReg1).addReg(TmpReg2).addReg(TmpReg2);
1989     return;
1990   case Intrinsic::vaend: return;
1991
1992   case Intrinsic::returnaddress:
1993     TmpReg1 = getReg(CI);
1994     if (cast<Constant>(CI.getOperand(1))->isNullValue()) {
1995       MachineFrameInfo *MFI = F->getFrameInfo();
1996       unsigned NumBytes = MFI->getStackSize();
1997       
1998       BuildMI(BB, PPC::LWZ, 2, TmpReg1).addSImm(NumBytes+8)
1999         .addReg(PPC::R1);
2000     } else {
2001       // Values other than zero are not implemented yet.
2002       BuildMI(BB, PPC::LI, 1, TmpReg1).addSImm(0);
2003     }
2004     return;
2005
2006   case Intrinsic::frameaddress:
2007     TmpReg1 = getReg(CI);
2008     if (cast<Constant>(CI.getOperand(1))->isNullValue()) {
2009       BuildMI(BB, PPC::OR, 2, TmpReg1).addReg(PPC::R1).addReg(PPC::R1);
2010     } else {
2011       // Values other than zero are not implemented yet.
2012       BuildMI(BB, PPC::LI, 1, TmpReg1).addSImm(0);
2013     }
2014     return;
2015     
2016 #if 0
2017     // This may be useful for supporting isunordered
2018   case Intrinsic::isnan:
2019     // If this is only used by 'isunordered' style comparisons, don't emit it.
2020     if (isOnlyUsedByUnorderedComparisons(&CI)) return;
2021     TmpReg1 = getReg(CI.getOperand(1));
2022     emitUCOM(BB, BB->end(), TmpReg1, TmpReg1);
2023     TmpReg2 = makeAnotherReg(Type::IntTy);
2024     BuildMI(BB, PPC::MFCR, TmpReg2);
2025     TmpReg3 = getReg(CI);
2026     BuildMI(BB, PPC::RLWINM, 4, TmpReg3).addReg(TmpReg2).addImm(4).addImm(31).addImm(31);
2027     return;
2028 #endif
2029     
2030   default: assert(0 && "Error: unknown intrinsics should have been lowered!");
2031   }
2032 }
2033
2034 /// visitSimpleBinary - Implement simple binary operators for integral types...
2035 /// OperatorClass is one of: 0 for Add, 1 for Sub, 2 for And, 3 for Or, 4 for
2036 /// Xor.
2037 ///
2038 void PPC32ISel::visitSimpleBinary(BinaryOperator &B, unsigned OperatorClass) {
2039   if (std::find(SkipList.begin(), SkipList.end(), &B) != SkipList.end())
2040     return;
2041
2042   unsigned DestReg = getReg(B);
2043   MachineBasicBlock::iterator MI = BB->end();
2044   RlwimiRec RR = InsertMap[&B];
2045   if (RR.Target != 0) {
2046     unsigned TargetReg = getReg(RR.Target, BB, MI);
2047     unsigned InsertReg = getReg(RR.Insert, BB, MI);
2048     BuildMI(*BB, MI, PPC::RLWIMI, 5, DestReg).addReg(TargetReg)
2049       .addReg(InsertReg).addImm(RR.Shift).addImm(RR.MB).addImm(RR.ME);
2050     return;
2051   }
2052     
2053   unsigned Class = getClassB(B.getType());
2054   Value *Op0 = B.getOperand(0), *Op1 = B.getOperand(1);
2055   emitSimpleBinaryOperation(BB, MI, &B, Op0, Op1, OperatorClass, DestReg);
2056 }
2057
2058 /// emitBinaryFPOperation - This method handles emission of floating point
2059 /// Add (0), Sub (1), Mul (2), and Div (3) operations.
2060 void PPC32ISel::emitBinaryFPOperation(MachineBasicBlock *BB,
2061                                       MachineBasicBlock::iterator IP,
2062                                       Value *Op0, Value *Op1,
2063                                       unsigned OperatorClass, unsigned DestReg){
2064
2065   static const unsigned OpcodeTab[][4] = {
2066     { PPC::FADDS, PPC::FSUBS, PPC::FMULS, PPC::FDIVS },  // Float
2067     { PPC::FADD,  PPC::FSUB,  PPC::FMUL,  PPC::FDIV },   // Double
2068   };
2069
2070   // Special case: R1 = op <const fp>, R2
2071   if (ConstantFP *Op0C = dyn_cast<ConstantFP>(Op0))
2072     if (Op0C->isExactlyValue(-0.0) && OperatorClass == 1) {
2073       // -0.0 - X === -X
2074       unsigned op1Reg = getReg(Op1, BB, IP);
2075       BuildMI(*BB, IP, PPC::FNEG, 1, DestReg).addReg(op1Reg);
2076       return;
2077     }
2078
2079   unsigned Opcode = OpcodeTab[Op0->getType() == Type::DoubleTy][OperatorClass];
2080   unsigned Op0r = getReg(Op0, BB, IP);
2081   unsigned Op1r = getReg(Op1, BB, IP);
2082   BuildMI(*BB, IP, Opcode, 2, DestReg).addReg(Op0r).addReg(Op1r);
2083 }
2084
2085 // ExactLog2 - This function solves for (Val == 1 << (N-1)) and returns N.  It
2086 // returns zero when the input is not exactly a power of two.
2087 static unsigned ExactLog2(unsigned Val) {
2088   if (Val == 0 || (Val & (Val-1))) return 0;
2089   unsigned Count = 0;
2090   while (Val != 1) {
2091     Val >>= 1;
2092     ++Count;
2093   }
2094   return Count;
2095 }
2096
2097 // isRunOfOnes - returns true if Val consists of one contiguous run of 1's with
2098 // any number of 0's on either side.  the 1's are allowed to wrap from LSB to
2099 // MSB.  so 0x000FFF0, 0x0000FFFF, and 0xFF0000FF are all runs.  0x0F0F0000 is
2100 // not, since all 1's are not contiguous.
2101 static bool isRunOfOnes(unsigned Val, unsigned &MB, unsigned &ME) {
2102   bool isRun = true;
2103   MB = 0; 
2104   ME = 0;
2105
2106   // look for first set bit
2107   int i = 0;
2108   for (; i < 32; i++) {
2109     if ((Val & (1 << (31 - i))) != 0) {
2110       MB = i;
2111       ME = i;
2112       break;
2113     }
2114   }
2115   
2116   // look for last set bit
2117   for (; i < 32; i++) {
2118     if ((Val & (1 << (31 - i))) == 0)
2119       break;
2120     ME = i;
2121   }
2122
2123   // look for next set bit
2124   for (; i < 32; i++) {
2125     if ((Val & (1 << (31 - i))) != 0)
2126       break;
2127   }
2128   
2129   // if we exhausted all the bits, we found a match at this point for 0*1*0*
2130   if (i == 32)
2131     return true;
2132
2133   // since we just encountered more 1's, if it doesn't wrap around to the
2134   // most significant bit of the word, then we did not find a match to 1*0*1* so
2135   // exit.
2136   if (MB != 0)
2137     return false;
2138
2139   // look for last set bit
2140   for (MB = i; i < 32; i++) {
2141     if ((Val & (1 << (31 - i))) == 0)
2142       break;
2143   }
2144   
2145   // if we exhausted all the bits, then we found a match for 1*0*1*, otherwise,
2146   // the value is not a run of ones.
2147   if (i == 32)
2148     return true;
2149   return false;
2150 }
2151
2152 /// isInsertAndHalf - Helper function for emitBitfieldInsert.  Returns true if
2153 /// OpUser has one use, is used by an or instruction, and is itself an and whose
2154 /// second operand is a constant int.  Optionally, set OrI to the Or instruction
2155 /// that is the sole user of OpUser, and Op1User to the other operand of the Or
2156 /// instruction.
2157 static bool isInsertAndHalf(User *OpUser, Instruction **Op1User, 
2158                             Instruction **OrI, unsigned &Mask) {
2159   // If this instruction doesn't have one use, then return false.
2160   if (!OpUser->hasOneUse())
2161     return false;
2162   
2163   Mask = 0xFFFFFFFF;
2164   if (BinaryOperator *BO = dyn_cast<BinaryOperator>(OpUser))
2165     if (BO->getOpcode() == Instruction::And) {
2166       Value *AndUse = *(OpUser->use_begin());
2167       if (BinaryOperator *Or = dyn_cast<BinaryOperator>(AndUse)) {
2168         if (Or->getOpcode() == Instruction::Or) {
2169           if (ConstantInt *CI = dyn_cast<ConstantInt>(OpUser->getOperand(1))) {
2170             if (OrI) *OrI = Or;
2171             if (Op1User) {
2172               if (Or->getOperand(0) == OpUser)
2173                 *Op1User = dyn_cast<Instruction>(Or->getOperand(1));
2174               else
2175                 *Op1User = dyn_cast<Instruction>(Or->getOperand(0));
2176             }
2177             Mask &= CI->getRawValue();
2178             return true;
2179           }
2180         }
2181       }
2182     }
2183   return false;
2184 }
2185
2186 /// isInsertShiftHalf - Helper function for emitBitfieldInsert.  Returns true if
2187 /// OpUser has one use, is used by an or instruction, and is itself a shift
2188 /// instruction that is either used directly by the or instruction, or is used
2189 /// by an and instruction whose second operand is a constant int, and which is
2190 /// used by the or instruction.
2191 static bool isInsertShiftHalf(User *OpUser, Instruction **Op1User, 
2192                               Instruction **OrI, Instruction **OptAndI, 
2193                               unsigned &Shift, unsigned &Mask) {
2194   // If this instruction doesn't have one use, then return false.
2195   if (!OpUser->hasOneUse())
2196     return false;
2197   
2198   Mask = 0xFFFFFFFF;
2199   if (ShiftInst *SI = dyn_cast<ShiftInst>(OpUser)) {
2200     if (ConstantInt *CI = dyn_cast<ConstantInt>(SI->getOperand(1))) {
2201       Shift = CI->getRawValue();
2202       if (SI->getOpcode() == Instruction::Shl)
2203         Mask <<= Shift;
2204       else if (!SI->getOperand(0)->getType()->isSigned()) {
2205         Mask >>= Shift;
2206         Shift = 32 - Shift;
2207       }
2208
2209       // Now check to see if the shift instruction is used by an or.
2210       Value *ShiftUse = *(OpUser->use_begin());
2211       Value *OptAndICopy = 0;
2212       if (BinaryOperator *BO = dyn_cast<BinaryOperator>(ShiftUse)) {
2213         if (BO->getOpcode() == Instruction::And && BO->hasOneUse()) {
2214           if (ConstantInt *ACI = dyn_cast<ConstantInt>(BO->getOperand(1))) {
2215             if (OptAndI) *OptAndI = BO;
2216             OptAndICopy = BO;
2217             Mask &= ACI->getRawValue();
2218             BO = dyn_cast<BinaryOperator>(*(BO->use_begin()));
2219           }
2220         }
2221         if (BO && BO->getOpcode() == Instruction::Or) {
2222           if (OrI) *OrI = BO;
2223           if (Op1User) {
2224             if (BO->getOperand(0) == OpUser || BO->getOperand(0) == OptAndICopy)
2225               *Op1User = dyn_cast<Instruction>(BO->getOperand(1));
2226             else
2227               *Op1User = dyn_cast<Instruction>(BO->getOperand(0));
2228           }
2229           return true;
2230         }
2231       }
2232     }
2233   }
2234   return false;
2235 }
2236
2237 /// emitBitfieldInsert - turn a shift used only by an and with immediate into 
2238 /// the rotate left word immediate then mask insert (rlwimi) instruction.
2239 /// Patterns matched:
2240 /// 1. or shl, and   5. or (shl-and), and   9. or and, and
2241 /// 2. or and, shl   6. or and, (shl-and)
2242 /// 3. or shr, and   7. or (shr-and), and
2243 /// 4. or and, shr   8. or and, (shr-and)
2244 bool PPC32ISel::emitBitfieldInsert(User *OpUser, unsigned DestReg) {
2245   // Instructions to skip if we match any of the patterns
2246   Instruction *Op0User, *Op1User = 0, *OptAndI = 0, *OrI = 0;
2247   unsigned TgtMask, InsMask, Amount = 0;
2248   bool matched = false;
2249
2250   // We require OpUser to be an instruction to continue
2251   Op0User = dyn_cast<Instruction>(OpUser);
2252   if (0 == Op0User)
2253     return false;
2254
2255   // Look for cases 2, 4, 6, 8, and 9
2256   if (isInsertAndHalf(Op0User, &Op1User, &OrI, TgtMask))
2257     if (Op1User)
2258       if (isInsertAndHalf(Op1User, 0, 0, InsMask))
2259         matched = true;
2260       else if (isInsertShiftHalf(Op1User, 0, 0, &OptAndI, Amount, InsMask))
2261         matched = true;
2262   
2263   // Look for cases 1, 3, 5, and 7.  Force the shift argument to be the one
2264   // inserted into the target, since rlwimi can only rotate the value inserted,
2265   // not the value being inserted into.
2266   if (matched == false)
2267     if (isInsertShiftHalf(Op0User, &Op1User, &OrI, &OptAndI, Amount, InsMask))
2268       if (Op1User && isInsertAndHalf(Op1User, 0, 0, TgtMask)) {
2269         std::swap(Op0User, Op1User);
2270         matched = true;
2271       }
2272   
2273   // We didn't succeed in matching one of the patterns, so return false
2274   if (matched == false)
2275     return false;
2276   
2277   // If the masks xor to -1, and the insert mask is a run of ones, then we have
2278   // succeeded in matching one of the cases for generating rlwimi.  Update the
2279   // skip lists and users of the Instruction::Or.
2280   unsigned MB, ME;
2281   if (((TgtMask ^ InsMask) == 0xFFFFFFFF) && isRunOfOnes(InsMask, MB, ME)) {
2282     SkipList.push_back(Op0User);
2283     SkipList.push_back(Op1User);
2284     SkipList.push_back(OptAndI);
2285     InsertMap[OrI] = RlwimiRec(Op0User->getOperand(0), Op1User->getOperand(0), 
2286                                Amount, MB, ME);
2287     return true;
2288   }
2289   return false;
2290 }
2291
2292 /// emitBitfieldExtract - turn a shift used only by an and with immediate into the
2293 /// rotate left word immediate then and with mask (rlwinm) instruction.
2294 bool PPC32ISel::emitBitfieldExtract(MachineBasicBlock *MBB, 
2295                                     MachineBasicBlock::iterator IP,
2296                                     User *OpUser, unsigned DestReg) {
2297   return false;
2298   /*
2299   // Instructions to skip if we match any of the patterns
2300   Instruction *Op0User, *Op1User = 0;
2301   unsigned ShiftMask, AndMask, Amount = 0;
2302   bool matched = false;
2303
2304   // We require OpUser to be an instruction to continue
2305   Op0User = dyn_cast<Instruction>(OpUser);
2306   if (0 == Op0User)
2307     return false;
2308
2309   if (isExtractShiftHalf)
2310     if (isExtractAndHalf)
2311       matched = true;
2312   
2313   if (matched == false && isExtractAndHalf)
2314     if (isExtractShiftHalf)
2315     matched = true;
2316   
2317   if (matched == false)
2318     return false;
2319
2320   if (isRunOfOnes(Imm, MB, ME)) {
2321     unsigned SrcReg = getReg(Op, MBB, IP);
2322     BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(SrcReg).addImm(Rotate)
2323       .addImm(MB).addImm(ME);
2324     Op1User->replaceAllUsesWith(Op0User);
2325     SkipList.push_back(BO);
2326     return true;
2327   }
2328   */
2329 }
2330
2331 /// emitBinaryConstOperation - Implement simple binary operators for integral
2332 /// types with a constant operand.  Opcode is one of: 0 for Add, 1 for Sub, 
2333 /// 2 for And, 3 for Or, 4 for Xor, and 5 for Subtract-From.
2334 ///
2335 void PPC32ISel::emitBinaryConstOperation(MachineBasicBlock *MBB, 
2336                                          MachineBasicBlock::iterator IP,
2337                                          unsigned Op0Reg, ConstantInt *Op1, 
2338                                          unsigned Opcode, unsigned DestReg) {
2339   static const unsigned OpTab[] = {
2340     PPC::ADD, PPC::SUB, PPC::AND, PPC::OR, PPC::XOR, PPC::SUBF
2341   };
2342   static const unsigned ImmOpTab[2][6] = {
2343     {  PPC::ADDI,  PPC::ADDI,  PPC::ANDIo,  PPC::ORI,  PPC::XORI, PPC::SUBFIC },
2344     { PPC::ADDIS, PPC::ADDIS, PPC::ANDISo, PPC::ORIS, PPC::XORIS, PPC::SUBFIC }
2345   };
2346
2347   // Handle subtract now by inverting the constant value: X-4 == X+(-4)
2348   if (Opcode == 1) {
2349     Op1 = cast<ConstantInt>(ConstantExpr::getNeg(Op1));
2350     Opcode = 0;
2351   }
2352   
2353   // xor X, -1 -> not X
2354   if (Opcode == 4 && Op1->isAllOnesValue()) {
2355     BuildMI(*MBB, IP, PPC::NOR, 2, DestReg).addReg(Op0Reg).addReg(Op0Reg);
2356     return;
2357   }
2358   
2359   if (Opcode == 2 && !Op1->isNullValue()) {
2360     unsigned MB, ME, mask = Op1->getRawValue();
2361     if (isRunOfOnes(mask, MB, ME)) {
2362       BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(Op0Reg).addImm(0)
2363         .addImm(MB).addImm(ME);
2364       return;
2365     }
2366   }
2367
2368   // PowerPC 16 bit signed immediates are sign extended before use by the
2369   // instruction.  Therefore, we can only split up an add of a reg with a 32 bit
2370   // immediate into addis and addi if the sign bit of the low 16 bits is cleared
2371   // so that for register A, const imm X, we don't end up with
2372   // A + XXXX0000 + FFFFXXXX.
2373   bool WontSignExtend = (0 == (Op1->getRawValue() & 0x8000));
2374
2375   // For Add, Sub, and SubF the instruction takes a signed immediate.  For And,
2376   // Or, and Xor, the instruction takes an unsigned immediate.  There is no 
2377   // shifted immediate form of SubF so disallow its opcode for those constants.
2378   if (canUseAsImmediateForOpcode(Op1, Opcode, false)) {
2379     if (Opcode < 2 || Opcode == 5)
2380       BuildMI(*MBB, IP, ImmOpTab[0][Opcode], 2, DestReg).addReg(Op0Reg)
2381         .addSImm(Op1->getRawValue());
2382     else
2383       BuildMI(*MBB, IP, ImmOpTab[0][Opcode], 2, DestReg).addReg(Op0Reg)
2384         .addZImm(Op1->getRawValue());
2385   } else if (canUseAsImmediateForOpcode(Op1, Opcode, true) && (Opcode < 5)) {
2386     if (Opcode < 2)
2387       BuildMI(*MBB, IP, ImmOpTab[1][Opcode], 2, DestReg).addReg(Op0Reg)
2388         .addSImm(Op1->getRawValue() >> 16);
2389     else
2390       BuildMI(*MBB, IP, ImmOpTab[1][Opcode], 2, DestReg).addReg(Op0Reg)
2391         .addZImm(Op1->getRawValue() >> 16);
2392   } else if ((Opcode < 2 && WontSignExtend) || Opcode == 3 || Opcode == 4) {
2393     unsigned TmpReg = makeAnotherReg(Op1->getType());
2394     if (Opcode < 2) {
2395       BuildMI(*MBB, IP, ImmOpTab[1][Opcode], 2, TmpReg).addReg(Op0Reg)
2396         .addSImm(Op1->getRawValue() >> 16);
2397       BuildMI(*MBB, IP, ImmOpTab[0][Opcode], 2, DestReg).addReg(TmpReg)
2398         .addSImm(Op1->getRawValue());
2399     } else {
2400       BuildMI(*MBB, IP, ImmOpTab[1][Opcode], 2, TmpReg).addReg(Op0Reg)
2401         .addZImm(Op1->getRawValue() >> 16);
2402       BuildMI(*MBB, IP, ImmOpTab[0][Opcode], 2, DestReg).addReg(TmpReg)
2403         .addZImm(Op1->getRawValue());
2404     }
2405   } else {
2406     unsigned Op1Reg = getReg(Op1, MBB, IP);
2407     BuildMI(*MBB, IP, OpTab[Opcode], 2, DestReg).addReg(Op0Reg).addReg(Op1Reg);
2408   }
2409 }
2410
2411 /// emitSimpleBinaryOperation - Implement simple binary operators for integral
2412 /// types...  OperatorClass is one of: 0 for Add, 1 for Sub, 2 for And, 3 for
2413 /// Or, 4 for Xor.
2414 ///
2415 void PPC32ISel::emitSimpleBinaryOperation(MachineBasicBlock *MBB,
2416                                           MachineBasicBlock::iterator IP,
2417                                           BinaryOperator *BO, 
2418                                           Value *Op0, Value *Op1,
2419                                           unsigned OperatorClass, 
2420                                           unsigned DestReg) {
2421   // Arithmetic and Bitwise operators
2422   static const unsigned OpcodeTab[] = {
2423     PPC::ADD, PPC::SUBF, PPC::AND, PPC::OR, PPC::XOR
2424   };
2425   static const unsigned LongOpTab[2][5] = {
2426     { PPC::ADDC, PPC::SUBFC, PPC::AND, PPC::OR, PPC::XOR },
2427     { PPC::ADDE, PPC::SUBFE, PPC::AND, PPC::OR, PPC::XOR }
2428   };
2429   
2430   unsigned Class = getClassB(Op0->getType());
2431
2432   if (Class == cFP32 || Class == cFP64) {
2433     assert(OperatorClass < 2 && "No logical ops for FP!");
2434     emitBinaryFPOperation(MBB, IP, Op0, Op1, OperatorClass, DestReg);
2435     return;
2436   }
2437
2438   if (Op0->getType() == Type::BoolTy) {
2439     if (OperatorClass == 3)
2440       // If this is an or of two isnan's, emit an FP comparison directly instead
2441       // of or'ing two isnan's together.
2442       if (Value *LHS = dyncastIsNan(Op0))
2443         if (Value *RHS = dyncastIsNan(Op1)) {
2444           unsigned Op0Reg = getReg(RHS, MBB, IP), Op1Reg = getReg(LHS, MBB, IP);
2445           unsigned TmpReg = makeAnotherReg(Type::IntTy);
2446           emitUCOM(MBB, IP, Op0Reg, Op1Reg);
2447           BuildMI(*MBB, IP, PPC::MFCR, TmpReg);
2448           BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(TmpReg).addImm(4)
2449             .addImm(31).addImm(31);
2450           return;
2451         }
2452   }
2453
2454   // Special case: op <const int>, Reg
2455   if (ConstantInt *CI = dyn_cast<ConstantInt>(Op0))
2456     if (Class != cLong) {
2457       unsigned Opcode = (OperatorClass == 1) ? 5 : OperatorClass;
2458       unsigned Op1r = getReg(Op1, MBB, IP);
2459       emitBinaryConstOperation(MBB, IP, Op1r, CI, Opcode, DestReg);
2460       return;
2461     }
2462   // Special case: op Reg, <const int>
2463   if (ConstantInt *CI = dyn_cast<ConstantInt>(Op1))
2464     if (Class != cLong) {
2465       if (emitBitfieldInsert(BO, DestReg))
2466         return;
2467       
2468       unsigned Op0r = getReg(Op0, MBB, IP);
2469       emitBinaryConstOperation(MBB, IP, Op0r, CI, OperatorClass, DestReg);
2470       return;
2471     }
2472
2473   // We couldn't generate an immediate variant of the op, load both halves into
2474   // registers and emit the appropriate opcode.
2475   unsigned Op0r = getReg(Op0, MBB, IP);
2476   unsigned Op1r = getReg(Op1, MBB, IP);
2477
2478   // Subtracts have their operands swapped
2479   if (OperatorClass == 1) {
2480     if (Class != cLong) {
2481       BuildMI(*MBB, IP, PPC::SUBF, 2, DestReg).addReg(Op1r).addReg(Op0r);
2482     } else {
2483       BuildMI(*MBB, IP, PPC::SUBFC, 2, DestReg+1).addReg(Op1r+1).addReg(Op0r+1);
2484       BuildMI(*MBB, IP, PPC::SUBFE, 2, DestReg).addReg(Op1r).addReg(Op0r);
2485     }
2486     return;
2487   }
2488
2489   if (Class != cLong) {
2490     unsigned Opcode = OpcodeTab[OperatorClass];
2491     BuildMI(*MBB, IP, Opcode, 2, DestReg).addReg(Op0r).addReg(Op1r);
2492   } else {
2493     BuildMI(*MBB, IP, LongOpTab[0][OperatorClass], 2, DestReg+1).addReg(Op0r+1)
2494       .addReg(Op1r+1);
2495     BuildMI(*MBB, IP, LongOpTab[1][OperatorClass], 2, DestReg).addReg(Op0r)
2496       .addReg(Op1r);
2497   }
2498   return;
2499 }
2500
2501 /// doMultiply - Emit appropriate instructions to multiply together the
2502 /// Values Op0 and Op1, and put the result in DestReg.
2503 ///
2504 void PPC32ISel::doMultiply(MachineBasicBlock *MBB,
2505                            MachineBasicBlock::iterator IP,
2506                            unsigned DestReg, Value *Op0, Value *Op1) {
2507   unsigned Class0 = getClass(Op0->getType());
2508   unsigned Class1 = getClass(Op1->getType());
2509   
2510   unsigned Op0r = getReg(Op0, MBB, IP);
2511   unsigned Op1r = getReg(Op1, MBB, IP);
2512   
2513   // 64 x 64 -> 64
2514   if (Class0 == cLong && Class1 == cLong) {
2515     unsigned Tmp1 = makeAnotherReg(Type::IntTy);
2516     unsigned Tmp2 = makeAnotherReg(Type::IntTy);
2517     unsigned Tmp3 = makeAnotherReg(Type::IntTy);
2518     unsigned Tmp4 = makeAnotherReg(Type::IntTy);
2519     BuildMI(*MBB, IP, PPC::MULHWU, 2, Tmp1).addReg(Op0r+1).addReg(Op1r+1);
2520     BuildMI(*MBB, IP, PPC::MULLW, 2, DestReg+1).addReg(Op0r+1).addReg(Op1r+1);
2521     BuildMI(*MBB, IP, PPC::MULLW, 2, Tmp2).addReg(Op0r+1).addReg(Op1r);
2522     BuildMI(*MBB, IP, PPC::ADD, 2, Tmp3).addReg(Tmp1).addReg(Tmp2);
2523     BuildMI(*MBB, IP, PPC::MULLW, 2, Tmp4).addReg(Op0r).addReg(Op1r+1);
2524     BuildMI(*MBB, IP, PPC::ADD, 2, DestReg).addReg(Tmp3).addReg(Tmp4);
2525     return;
2526   }
2527   
2528   // 64 x 32 or less, promote 32 to 64 and do a 64 x 64
2529   if (Class0 == cLong && Class1 <= cInt) {
2530     unsigned Tmp0 = makeAnotherReg(Type::IntTy);
2531     unsigned Tmp1 = makeAnotherReg(Type::IntTy);
2532     unsigned Tmp2 = makeAnotherReg(Type::IntTy);
2533     unsigned Tmp3 = makeAnotherReg(Type::IntTy);
2534     unsigned Tmp4 = makeAnotherReg(Type::IntTy);
2535     if (Op1->getType()->isSigned())
2536       BuildMI(*MBB, IP, PPC::SRAWI, 2, Tmp0).addReg(Op1r).addImm(31);
2537     else
2538       BuildMI(*MBB, IP, PPC::LI, 2, Tmp0).addSImm(0);
2539     BuildMI(*MBB, IP, PPC::MULHWU, 2, Tmp1).addReg(Op0r+1).addReg(Op1r);
2540     BuildMI(*MBB, IP, PPC::MULLW, 2, DestReg+1).addReg(Op0r+1).addReg(Op1r);
2541     BuildMI(*MBB, IP, PPC::MULLW, 2, Tmp2).addReg(Op0r+1).addReg(Tmp0);
2542     BuildMI(*MBB, IP, PPC::ADD, 2, Tmp3).addReg(Tmp1).addReg(Tmp2);
2543     BuildMI(*MBB, IP, PPC::MULLW, 2, Tmp4).addReg(Op0r).addReg(Op1r);
2544     BuildMI(*MBB, IP, PPC::ADD, 2, DestReg).addReg(Tmp3).addReg(Tmp4);
2545     return;
2546   }
2547   
2548   // 32 x 32 -> 32
2549   if (Class0 <= cInt && Class1 <= cInt) {
2550     BuildMI(*MBB, IP, PPC::MULLW, 2, DestReg).addReg(Op0r).addReg(Op1r);
2551     return;
2552   }
2553   
2554   assert(0 && "doMultiply cannot operate on unknown type!");
2555 }
2556
2557 /// doMultiplyConst - This method will multiply the value in Op0 by the
2558 /// value of the ContantInt *CI
2559 void PPC32ISel::doMultiplyConst(MachineBasicBlock *MBB,
2560                                 MachineBasicBlock::iterator IP,
2561                                 unsigned DestReg, Value *Op0, ConstantInt *CI) {
2562   unsigned Class = getClass(Op0->getType());
2563
2564   // Mul op0, 0 ==> 0
2565   if (CI->isNullValue()) {
2566     BuildMI(*MBB, IP, PPC::LI, 1, DestReg).addSImm(0);
2567     if (Class == cLong)
2568       BuildMI(*MBB, IP, PPC::LI, 1, DestReg+1).addSImm(0);
2569     return;
2570   }
2571   
2572   // Mul op0, 1 ==> op0
2573   if (CI->equalsInt(1)) {
2574     unsigned Op0r = getReg(Op0, MBB, IP);
2575     BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(Op0r).addReg(Op0r);
2576     if (Class == cLong)
2577       BuildMI(*MBB, IP, PPC::OR, 2, DestReg+1).addReg(Op0r+1).addReg(Op0r+1);
2578     return;
2579   }
2580
2581   // If the element size is exactly a power of 2, use a shift to get it.
2582   if (unsigned Shift = ExactLog2(CI->getRawValue())) {
2583     ConstantUInt *ShiftCI = ConstantUInt::get(Type::UByteTy, Shift);
2584     emitShiftOperation(MBB, IP, Op0, ShiftCI, true, Op0->getType(), 0, DestReg);
2585     return;
2586   }
2587   
2588   // If 32 bits or less and immediate is in right range, emit mul by immediate
2589   if (Class == cByte || Class == cShort || Class == cInt) {
2590     if (canUseAsImmediateForOpcode(CI, 0, false)) {
2591       unsigned Op0r = getReg(Op0, MBB, IP);
2592       unsigned imm = CI->getRawValue() & 0xFFFF;
2593       BuildMI(*MBB, IP, PPC::MULLI, 2, DestReg).addReg(Op0r).addSImm(imm);
2594       return;
2595     }
2596   }
2597   
2598   doMultiply(MBB, IP, DestReg, Op0, CI);
2599 }
2600
2601 void PPC32ISel::visitMul(BinaryOperator &I) {
2602   unsigned ResultReg = getReg(I);
2603
2604   Value *Op0 = I.getOperand(0);
2605   Value *Op1 = I.getOperand(1);
2606
2607   MachineBasicBlock::iterator IP = BB->end();
2608   emitMultiply(BB, IP, Op0, Op1, ResultReg);
2609 }
2610
2611 void PPC32ISel::emitMultiply(MachineBasicBlock *MBB,
2612                              MachineBasicBlock::iterator IP,
2613                              Value *Op0, Value *Op1, unsigned DestReg) {
2614   TypeClass Class = getClass(Op0->getType());
2615
2616   switch (Class) {
2617   case cByte:
2618   case cShort:
2619   case cInt:
2620   case cLong:
2621     if (ConstantInt *CI = dyn_cast<ConstantInt>(Op1)) {
2622       doMultiplyConst(MBB, IP, DestReg, Op0, CI);
2623     } else {
2624       doMultiply(MBB, IP, DestReg, Op0, Op1);
2625     }
2626     return;
2627   case cFP32:
2628   case cFP64:
2629     emitBinaryFPOperation(MBB, IP, Op0, Op1, 2, DestReg);
2630     return;
2631     break;
2632   }
2633 }
2634
2635
2636 /// visitDivRem - Handle division and remainder instructions... these
2637 /// instruction both require the same instructions to be generated, they just
2638 /// select the result from a different register.  Note that both of these
2639 /// instructions work differently for signed and unsigned operands.
2640 ///
2641 void PPC32ISel::visitDivRem(BinaryOperator &I) {
2642   unsigned ResultReg = getReg(I);
2643   Value *Op0 = I.getOperand(0), *Op1 = I.getOperand(1);
2644
2645   MachineBasicBlock::iterator IP = BB->end();
2646   emitDivRemOperation(BB, IP, Op0, Op1, I.getOpcode() == Instruction::Div,
2647                       ResultReg);
2648 }
2649
2650 void PPC32ISel::emitDivRemOperation(MachineBasicBlock *MBB,
2651                                     MachineBasicBlock::iterator IP,
2652                                     Value *Op0, Value *Op1, bool isDiv,
2653                                     unsigned ResultReg) {
2654   const Type *Ty = Op0->getType();
2655   unsigned Class = getClass(Ty);
2656   switch (Class) {
2657   case cFP32:
2658     if (isDiv) {
2659       // Floating point divide...
2660       emitBinaryFPOperation(MBB, IP, Op0, Op1, 3, ResultReg);
2661       return;
2662     } else {
2663       // Floating point remainder via fmodf(float x, float y);
2664       unsigned Op0Reg = getReg(Op0, MBB, IP);
2665       unsigned Op1Reg = getReg(Op1, MBB, IP);
2666       MachineInstr *TheCall =
2667         BuildMI(PPC::CALLpcrel, 1).addGlobalAddress(fmodfFn, true);
2668       std::vector<ValueRecord> Args;
2669       Args.push_back(ValueRecord(Op0Reg, Type::FloatTy));
2670       Args.push_back(ValueRecord(Op1Reg, Type::FloatTy));
2671       doCall(ValueRecord(ResultReg, Type::FloatTy), TheCall, Args, false);
2672     }
2673     return;
2674   case cFP64:
2675     if (isDiv) {
2676       // Floating point divide...
2677       emitBinaryFPOperation(MBB, IP, Op0, Op1, 3, ResultReg);
2678       return;
2679     } else {               
2680       // Floating point remainder via fmod(double x, double y);
2681       unsigned Op0Reg = getReg(Op0, MBB, IP);
2682       unsigned Op1Reg = getReg(Op1, MBB, IP);
2683       MachineInstr *TheCall =
2684         BuildMI(PPC::CALLpcrel, 1).addGlobalAddress(fmodFn, true);
2685       std::vector<ValueRecord> Args;
2686       Args.push_back(ValueRecord(Op0Reg, Type::DoubleTy));
2687       Args.push_back(ValueRecord(Op1Reg, Type::DoubleTy));
2688       doCall(ValueRecord(ResultReg, Type::DoubleTy), TheCall, Args, false);
2689     }
2690     return;
2691   case cLong: {
2692     static Function* const Funcs[] =
2693       { __moddi3Fn, __divdi3Fn, __umoddi3Fn, __udivdi3Fn };
2694     unsigned Op0Reg = getReg(Op0, MBB, IP);
2695     unsigned Op1Reg = getReg(Op1, MBB, IP);
2696     unsigned NameIdx = Ty->isUnsigned()*2 + isDiv;
2697     MachineInstr *TheCall =
2698       BuildMI(PPC::CALLpcrel, 1).addGlobalAddress(Funcs[NameIdx], true);
2699
2700     std::vector<ValueRecord> Args;
2701     Args.push_back(ValueRecord(Op0Reg, Type::LongTy));
2702     Args.push_back(ValueRecord(Op1Reg, Type::LongTy));
2703     doCall(ValueRecord(ResultReg, Type::LongTy), TheCall, Args, false);
2704     return;
2705   }
2706   case cByte: case cShort: case cInt:
2707     break;          // Small integrals, handled below...
2708   default: assert(0 && "Unknown class!");
2709   }
2710
2711   // Special case signed division by power of 2.
2712   if (isDiv)
2713     if (ConstantSInt *CI = dyn_cast<ConstantSInt>(Op1)) {
2714       assert(Class != cLong && "This doesn't handle 64-bit divides!");
2715       int V = CI->getValue();
2716
2717       if (V == 1) {       // X /s 1 => X
2718         unsigned Op0Reg = getReg(Op0, MBB, IP);
2719         BuildMI(*MBB, IP, PPC::OR, 2, ResultReg).addReg(Op0Reg).addReg(Op0Reg);
2720         return;
2721       }
2722
2723       if (V == -1) {      // X /s -1 => -X
2724         unsigned Op0Reg = getReg(Op0, MBB, IP);
2725         BuildMI(*MBB, IP, PPC::NEG, 1, ResultReg).addReg(Op0Reg);
2726         return;
2727       }
2728
2729       unsigned log2V = ExactLog2(V);
2730       if (log2V != 0 && Ty->isSigned()) {
2731         unsigned Op0Reg = getReg(Op0, MBB, IP);
2732         unsigned TmpReg = makeAnotherReg(Op0->getType());
2733         
2734         BuildMI(*MBB, IP, PPC::SRAWI, 2, TmpReg).addReg(Op0Reg).addImm(log2V);
2735         BuildMI(*MBB, IP, PPC::ADDZE, 1, ResultReg).addReg(TmpReg);
2736         return;
2737       }
2738     }
2739
2740   unsigned Op0Reg = getReg(Op0, MBB, IP);
2741
2742   if (isDiv) {
2743     unsigned Op1Reg = getReg(Op1, MBB, IP);
2744     unsigned Opcode = Ty->isSigned() ? PPC::DIVW : PPC::DIVWU;
2745     BuildMI(*MBB, IP, Opcode, 2, ResultReg).addReg(Op0Reg).addReg(Op1Reg);
2746   } else { // Remainder
2747     // FIXME: don't load the CI part of a CI divide twice
2748     ConstantInt *CI = dyn_cast<ConstantInt>(Op1);
2749     unsigned TmpReg1 = makeAnotherReg(Op0->getType());
2750     unsigned TmpReg2 = makeAnotherReg(Op0->getType());
2751     emitDivRemOperation(MBB, IP, Op0, Op1, true, TmpReg1);
2752     if (CI && canUseAsImmediateForOpcode(CI, 0, false)) {
2753       BuildMI(*MBB, IP, PPC::MULLI, 2, TmpReg2).addReg(TmpReg1)
2754         .addSImm(CI->getRawValue());
2755     } else {
2756       unsigned Op1Reg = getReg(Op1, MBB, IP);
2757       BuildMI(*MBB, IP, PPC::MULLW, 2, TmpReg2).addReg(TmpReg1).addReg(Op1Reg);
2758     }
2759     BuildMI(*MBB, IP, PPC::SUBF, 2, ResultReg).addReg(TmpReg2).addReg(Op0Reg);
2760   }
2761 }
2762
2763
2764 /// Shift instructions: 'shl', 'sar', 'shr' - Some special cases here
2765 /// for constant immediate shift values, and for constant immediate
2766 /// shift values equal to 1. Even the general case is sort of special,
2767 /// because the shift amount has to be in CL, not just any old register.
2768 ///
2769 void PPC32ISel::visitShiftInst(ShiftInst &I) {
2770   if (std::find(SkipList.begin(), SkipList.end(), &I) != SkipList.end())
2771     return;
2772
2773   MachineBasicBlock::iterator IP = BB->end();
2774   emitShiftOperation(BB, IP, I.getOperand(0), I.getOperand(1),
2775                      I.getOpcode() == Instruction::Shl, I.getType(),
2776                      &I, getReg(I));
2777 }
2778
2779 /// emitShiftOperation - Common code shared between visitShiftInst and
2780 /// constant expression support.
2781 ///
2782 void PPC32ISel::emitShiftOperation(MachineBasicBlock *MBB,
2783                                    MachineBasicBlock::iterator IP,
2784                                    Value *Op, Value *ShiftAmount, 
2785                                    bool isLeftShift, const Type *ResultTy,
2786                                    ShiftInst *SI, unsigned DestReg) {
2787   bool isSigned = ResultTy->isSigned ();
2788   unsigned Class = getClass (ResultTy);
2789   
2790   // Longs, as usual, are handled specially...
2791   if (Class == cLong) {
2792     unsigned SrcReg = getReg (Op, MBB, IP);
2793     // If we have a constant shift, we can generate much more efficient code
2794     // than for a variable shift by using the rlwimi instruction.
2795     if (ConstantUInt *CUI = dyn_cast<ConstantUInt>(ShiftAmount)) {
2796       unsigned Amount = CUI->getValue();
2797       if (Amount == 0) {
2798         BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
2799         BuildMI(*MBB, IP, PPC::OR, 2, DestReg+1)
2800           .addReg(SrcReg+1).addReg(SrcReg+1);
2801
2802       } else if (Amount < 32) {
2803         unsigned TempReg = makeAnotherReg(ResultTy);
2804         if (isLeftShift) {
2805           BuildMI(*MBB, IP, PPC::RLWINM, 4, TempReg).addReg(SrcReg)
2806             .addImm(Amount).addImm(0).addImm(31-Amount);
2807           BuildMI(*MBB, IP, PPC::RLWIMI, 5, DestReg).addReg(TempReg)
2808             .addReg(SrcReg+1).addImm(Amount).addImm(32-Amount).addImm(31);
2809           BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg+1).addReg(SrcReg+1)
2810             .addImm(Amount).addImm(0).addImm(31-Amount);
2811         } else {
2812           BuildMI(*MBB, IP, PPC::RLWINM, 4, TempReg).addReg(SrcReg+1)
2813             .addImm(32-Amount).addImm(Amount).addImm(31);
2814           BuildMI(*MBB, IP, PPC::RLWIMI, 5, DestReg+1).addReg(TempReg)
2815             .addReg(SrcReg).addImm(32-Amount).addImm(0).addImm(Amount-1);
2816           if (isSigned) {
2817             BuildMI(*MBB, IP, PPC::SRAWI, 2, DestReg).addReg(SrcReg)
2818               .addImm(Amount);
2819           } else {
2820             BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(SrcReg)
2821               .addImm(32-Amount).addImm(Amount).addImm(31);
2822           }
2823         }
2824       } else {                 // Shifting more than 32 bits
2825         Amount -= 32;
2826         if (isLeftShift) {
2827           if (Amount != 0) {
2828             BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(SrcReg+1)
2829               .addImm(Amount).addImm(0).addImm(31-Amount);
2830           } else {
2831             BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(SrcReg+1)
2832               .addReg(SrcReg+1);
2833           }
2834           BuildMI(*MBB, IP, PPC::LI, 1, DestReg+1).addSImm(0);
2835         } else {
2836           if (Amount != 0) {
2837             if (isSigned)
2838               BuildMI(*MBB, IP, PPC::SRAWI, 2, DestReg+1).addReg(SrcReg)
2839                 .addImm(Amount);
2840             else
2841               BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg+1).addReg(SrcReg)
2842                 .addImm(32-Amount).addImm(Amount).addImm(31);
2843           } else {
2844             BuildMI(*MBB, IP, PPC::OR, 2, DestReg+1).addReg(SrcReg)
2845               .addReg(SrcReg);
2846           }
2847           if (isSigned)
2848             BuildMI(*MBB, IP, PPC::SRAWI, 2, DestReg).addReg(SrcReg)
2849               .addImm(31);
2850           else
2851             BuildMI(*MBB, IP,PPC::LI, 1, DestReg).addSImm(0);
2852         }
2853       }
2854     } else {
2855       unsigned TmpReg1 = makeAnotherReg(Type::IntTy);
2856       unsigned TmpReg2 = makeAnotherReg(Type::IntTy);
2857       unsigned TmpReg3 = makeAnotherReg(Type::IntTy);
2858       unsigned TmpReg4 = makeAnotherReg(Type::IntTy);
2859       unsigned TmpReg5 = makeAnotherReg(Type::IntTy);
2860       unsigned TmpReg6 = makeAnotherReg(Type::IntTy);
2861       unsigned ShiftAmountReg = getReg (ShiftAmount, MBB, IP);
2862       
2863       if (isLeftShift) {
2864         BuildMI(*MBB, IP, PPC::SUBFIC, 2, TmpReg1).addReg(ShiftAmountReg)
2865           .addSImm(32);
2866         BuildMI(*MBB, IP, PPC::SLW, 2, TmpReg2).addReg(SrcReg)
2867           .addReg(ShiftAmountReg);
2868         BuildMI(*MBB, IP, PPC::SRW, 2, TmpReg3).addReg(SrcReg+1)
2869           .addReg(TmpReg1);
2870         BuildMI(*MBB, IP, PPC::OR, 2,TmpReg4).addReg(TmpReg2).addReg(TmpReg3);
2871         BuildMI(*MBB, IP, PPC::ADDI, 2, TmpReg5).addReg(ShiftAmountReg)
2872           .addSImm(-32);
2873         BuildMI(*MBB, IP, PPC::SLW, 2, TmpReg6).addReg(SrcReg+1)
2874           .addReg(TmpReg5);
2875         BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(TmpReg4)
2876           .addReg(TmpReg6);
2877         BuildMI(*MBB, IP, PPC::SLW, 2, DestReg+1).addReg(SrcReg+1)
2878           .addReg(ShiftAmountReg);
2879       } else {
2880         if (isSigned) { // shift right algebraic 
2881           MachineBasicBlock *TmpMBB =new MachineBasicBlock(BB->getBasicBlock());
2882           MachineBasicBlock *PhiMBB =new MachineBasicBlock(BB->getBasicBlock());
2883           MachineBasicBlock *OldMBB = BB;
2884           ilist<MachineBasicBlock>::iterator It = BB; ++It;
2885           F->getBasicBlockList().insert(It, TmpMBB);
2886           F->getBasicBlockList().insert(It, PhiMBB);
2887           BB->addSuccessor(TmpMBB);
2888           BB->addSuccessor(PhiMBB);
2889
2890           BuildMI(*MBB, IP, PPC::SUBFIC, 2, TmpReg1).addReg(ShiftAmountReg)
2891             .addSImm(32);
2892           BuildMI(*MBB, IP, PPC::SRW, 2, TmpReg2).addReg(SrcReg+1)
2893             .addReg(ShiftAmountReg);
2894           BuildMI(*MBB, IP, PPC::SLW, 2, TmpReg3).addReg(SrcReg)
2895             .addReg(TmpReg1);
2896           BuildMI(*MBB, IP, PPC::OR, 2, TmpReg4).addReg(TmpReg2)
2897             .addReg(TmpReg3);
2898           BuildMI(*MBB, IP, PPC::ADDICo, 2, TmpReg5).addReg(ShiftAmountReg)
2899             .addSImm(-32);
2900           BuildMI(*MBB, IP, PPC::SRAW, 2, TmpReg6).addReg(SrcReg)
2901             .addReg(TmpReg5);
2902           BuildMI(*MBB, IP, PPC::SRAW, 2, DestReg).addReg(SrcReg)
2903             .addReg(ShiftAmountReg);
2904           BuildMI(*MBB, IP, PPC::BLE, 2).addReg(PPC::CR0).addMBB(PhiMBB);
2905  
2906           // OrMBB:
2907           //   Select correct least significant half if the shift amount > 32
2908           BB = TmpMBB;
2909           unsigned OrReg = makeAnotherReg(Type::IntTy);
2910           BuildMI(BB, PPC::OR, 2, OrReg).addReg(TmpReg6).addReg(TmpReg6);
2911           TmpMBB->addSuccessor(PhiMBB);
2912           
2913           BB = PhiMBB;
2914           BuildMI(BB, PPC::PHI, 4, DestReg+1).addReg(TmpReg4).addMBB(OldMBB)
2915             .addReg(OrReg).addMBB(TmpMBB);
2916         } else { // shift right logical
2917           BuildMI(*MBB, IP, PPC::SUBFIC, 2, TmpReg1).addReg(ShiftAmountReg)
2918             .addSImm(32);
2919           BuildMI(*MBB, IP, PPC::SRW, 2, TmpReg2).addReg(SrcReg+1)
2920             .addReg(ShiftAmountReg);
2921           BuildMI(*MBB, IP, PPC::SLW, 2, TmpReg3).addReg(SrcReg)
2922             .addReg(TmpReg1);
2923           BuildMI(*MBB, IP, PPC::OR, 2, TmpReg4).addReg(TmpReg2)
2924             .addReg(TmpReg3);
2925           BuildMI(*MBB, IP, PPC::ADDI, 2, TmpReg5).addReg(ShiftAmountReg)
2926             .addSImm(-32);
2927           BuildMI(*MBB, IP, PPC::SRW, 2, TmpReg6).addReg(SrcReg)
2928             .addReg(TmpReg5);
2929           BuildMI(*MBB, IP, PPC::OR, 2, DestReg+1).addReg(TmpReg4)
2930             .addReg(TmpReg6);
2931           BuildMI(*MBB, IP, PPC::SRW, 2, DestReg).addReg(SrcReg)
2932             .addReg(ShiftAmountReg);
2933         }
2934       }
2935     }
2936     return;
2937   }
2938
2939   if (ConstantUInt *CUI = dyn_cast<ConstantUInt>(ShiftAmount)) {
2940     // The shift amount is constant, guaranteed to be a ubyte. Get its value.
2941     assert(CUI->getType() == Type::UByteTy && "Shift amount not a ubyte?");
2942     unsigned Amount = CUI->getValue();
2943     
2944     // If this is a shift with one use, and that use is an And instruction,
2945     // then attempt to emit a bitfield operation.
2946     if (SI && emitBitfieldInsert(SI, DestReg))
2947       return;
2948     
2949     unsigned SrcReg = getReg (Op, MBB, IP);
2950     if (Amount == 0) {
2951       BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
2952     } else if (isLeftShift) {
2953       BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(SrcReg)
2954         .addImm(Amount).addImm(0).addImm(31-Amount);
2955     } else {
2956       if (isSigned) {
2957         BuildMI(*MBB, IP, PPC::SRAWI,2,DestReg).addReg(SrcReg).addImm(Amount);
2958       } else {
2959         BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(SrcReg)
2960           .addImm(32-Amount).addImm(Amount).addImm(31);
2961       }
2962     }
2963   } else {                  // The shift amount is non-constant.
2964     unsigned SrcReg = getReg (Op, MBB, IP);
2965     unsigned ShiftAmountReg = getReg (ShiftAmount, MBB, IP);
2966
2967     if (isLeftShift) {
2968       BuildMI(*MBB, IP, PPC::SLW, 2, DestReg).addReg(SrcReg)
2969         .addReg(ShiftAmountReg);
2970     } else {
2971       BuildMI(*MBB, IP, isSigned ? PPC::SRAW : PPC::SRW, 2, DestReg)
2972         .addReg(SrcReg).addReg(ShiftAmountReg);
2973     }
2974   }
2975 }
2976
2977 /// LoadNeedsSignExtend - On PowerPC, there is no load byte with sign extend.
2978 /// Therefore, if this is a byte load and the destination type is signed, we
2979 /// would normally need to also emit a sign extend instruction after the load.
2980 /// However, store instructions don't care whether a signed type was sign
2981 /// extended across a whole register.  Also, a SetCC instruction will emit its
2982 /// own sign extension to force the value into the appropriate range, so we
2983 /// need not emit it here.  Ideally, this kind of thing wouldn't be necessary
2984 /// once LLVM's type system is improved.
2985 static bool LoadNeedsSignExtend(LoadInst &LI) {
2986   if (cByte == getClassB(LI.getType()) && LI.getType()->isSigned()) {
2987     bool AllUsesAreStoresOrSetCC = true;
2988     for (Value::use_iterator I = LI.use_begin(), E = LI.use_end(); I != E; ++I){
2989       if (isa<SetCondInst>(*I))
2990         continue;
2991       if (StoreInst *SI = dyn_cast<StoreInst>(*I))
2992         if (cByte == getClassB(SI->getOperand(0)->getType()))
2993         continue;
2994       AllUsesAreStoresOrSetCC = false;
2995       break;
2996     }
2997     if (!AllUsesAreStoresOrSetCC)
2998       return true;
2999   }
3000   return false;
3001 }
3002
3003 /// visitLoadInst - Implement LLVM load instructions.  Pretty straightforward
3004 /// mapping of LLVM classes to PPC load instructions, with the exception of
3005 /// signed byte loads, which need a sign extension following them.
3006 ///
3007 void PPC32ISel::visitLoadInst(LoadInst &I) {
3008   // Immediate opcodes, for reg+imm addressing
3009   static const unsigned ImmOpcodes[] = { 
3010     PPC::LBZ, PPC::LHZ, PPC::LWZ, 
3011     PPC::LFS, PPC::LFD, PPC::LWZ
3012   };
3013   // Indexed opcodes, for reg+reg addressing
3014   static const unsigned IdxOpcodes[] = {
3015     PPC::LBZX, PPC::LHZX, PPC::LWZX,
3016     PPC::LFSX, PPC::LFDX, PPC::LWZX
3017   };
3018
3019   unsigned Class     = getClassB(I.getType());
3020   unsigned ImmOpcode = ImmOpcodes[Class];
3021   unsigned IdxOpcode = IdxOpcodes[Class];
3022   unsigned DestReg   = getReg(I);
3023   Value *SourceAddr  = I.getOperand(0);
3024   
3025   if (Class == cShort && I.getType()->isSigned()) ImmOpcode = PPC::LHA;
3026   if (Class == cShort && I.getType()->isSigned()) IdxOpcode = PPC::LHAX;
3027
3028   // If this is a fixed size alloca, emit a load directly from the stack slot
3029   // corresponding to it.
3030   if (AllocaInst *AI = dyn_castFixedAlloca(SourceAddr)) {
3031     unsigned FI = getFixedSizedAllocaFI(AI);
3032     if (Class == cLong) {
3033       addFrameReference(BuildMI(BB, ImmOpcode, 2, DestReg), FI);
3034       addFrameReference(BuildMI(BB, ImmOpcode, 2, DestReg+1), FI, 4);
3035     } else if (LoadNeedsSignExtend(I)) {
3036       unsigned TmpReg = makeAnotherReg(I.getType());
3037       addFrameReference(BuildMI(BB, ImmOpcode, 2, TmpReg), FI);
3038       BuildMI(BB, PPC::EXTSB, 1, DestReg).addReg(TmpReg);
3039     } else {
3040       addFrameReference(BuildMI(BB, ImmOpcode, 2, DestReg), FI);
3041     }
3042     return;
3043   }
3044   
3045   // If the offset fits in 16 bits, we can emit a reg+imm load, otherwise, we
3046   // use the index from the FoldedGEP struct and use reg+reg addressing.
3047   if (GetElementPtrInst *GEPI = canFoldGEPIntoLoadOrStore(SourceAddr)) {
3048
3049     // Generate the code for the GEP and get the components of the folded GEP
3050     emitGEPOperation(BB, BB->end(), GEPI, true);
3051     unsigned baseReg = GEPMap[GEPI].base;
3052     unsigned indexReg = GEPMap[GEPI].index;
3053     ConstantSInt *offset = GEPMap[GEPI].offset;
3054
3055     if (Class != cLong) {
3056       unsigned TmpReg = LoadNeedsSignExtend(I) ? makeAnotherReg(I.getType())
3057                                                : DestReg;
3058       if (indexReg == 0)
3059         BuildMI(BB, ImmOpcode, 2, TmpReg).addSImm(offset->getValue())
3060           .addReg(baseReg);
3061       else
3062         BuildMI(BB, IdxOpcode, 2, TmpReg).addReg(indexReg).addReg(baseReg);
3063       if (LoadNeedsSignExtend(I))
3064         BuildMI(BB, PPC::EXTSB, 1, DestReg).addReg(TmpReg);
3065     } else {
3066       indexReg = (indexReg != 0) ? indexReg : getReg(offset);
3067       unsigned indexPlus4 = makeAnotherReg(Type::IntTy);
3068       BuildMI(BB, PPC::ADDI, 2, indexPlus4).addReg(indexReg).addSImm(4);
3069       BuildMI(BB, IdxOpcode, 2, DestReg).addReg(indexReg).addReg(baseReg);
3070       BuildMI(BB, IdxOpcode, 2, DestReg+1).addReg(indexPlus4).addReg(baseReg);
3071     }
3072     return;
3073   }
3074   
3075   // The fallback case, where the load was from a source that could not be
3076   // folded into the load instruction. 
3077   unsigned SrcAddrReg = getReg(SourceAddr);
3078     
3079   if (Class == cLong) {
3080     BuildMI(BB, ImmOpcode, 2, DestReg).addSImm(0).addReg(SrcAddrReg);
3081     BuildMI(BB, ImmOpcode, 2, DestReg+1).addSImm(4).addReg(SrcAddrReg);
3082   } else if (LoadNeedsSignExtend(I)) {
3083     unsigned TmpReg = makeAnotherReg(I.getType());
3084     BuildMI(BB, ImmOpcode, 2, TmpReg).addSImm(0).addReg(SrcAddrReg);
3085     BuildMI(BB, PPC::EXTSB, 1, DestReg).addReg(TmpReg);
3086   } else {
3087     BuildMI(BB, ImmOpcode, 2, DestReg).addSImm(0).addReg(SrcAddrReg);
3088   }
3089 }
3090
3091 /// visitStoreInst - Implement LLVM store instructions
3092 ///
3093 void PPC32ISel::visitStoreInst(StoreInst &I) {
3094   // Immediate opcodes, for reg+imm addressing
3095   static const unsigned ImmOpcodes[] = {
3096     PPC::STB, PPC::STH, PPC::STW, 
3097     PPC::STFS, PPC::STFD, PPC::STW
3098   };
3099   // Indexed opcodes, for reg+reg addressing
3100   static const unsigned IdxOpcodes[] = {
3101     PPC::STBX, PPC::STHX, PPC::STWX, 
3102     PPC::STFSX, PPC::STFDX, PPC::STWX
3103   };
3104   
3105   Value *SourceAddr  = I.getOperand(1);
3106   const Type *ValTy  = I.getOperand(0)->getType();
3107   unsigned Class     = getClassB(ValTy);
3108   unsigned ImmOpcode = ImmOpcodes[Class];
3109   unsigned IdxOpcode = IdxOpcodes[Class];
3110   unsigned ValReg    = getReg(I.getOperand(0));
3111
3112   // If this is a fixed size alloca, emit a store directly to the stack slot
3113   // corresponding to it.
3114   if (AllocaInst *AI = dyn_castFixedAlloca(SourceAddr)) {
3115     unsigned FI = getFixedSizedAllocaFI(AI);
3116     addFrameReference(BuildMI(BB, ImmOpcode, 3).addReg(ValReg), FI);
3117     if (Class == cLong)
3118       addFrameReference(BuildMI(BB, ImmOpcode, 3).addReg(ValReg+1), FI, 4);
3119     return;
3120   }
3121   
3122   // If the offset fits in 16 bits, we can emit a reg+imm store, otherwise, we
3123   // use the index from the FoldedGEP struct and use reg+reg addressing.
3124   if (GetElementPtrInst *GEPI = canFoldGEPIntoLoadOrStore(SourceAddr)) {
3125     // Generate the code for the GEP and get the components of the folded GEP
3126     emitGEPOperation(BB, BB->end(), GEPI, true);
3127     unsigned baseReg = GEPMap[GEPI].base;
3128     unsigned indexReg = GEPMap[GEPI].index;
3129     ConstantSInt *offset = GEPMap[GEPI].offset;
3130     
3131     if (Class != cLong) {
3132       if (indexReg == 0)
3133         BuildMI(BB, ImmOpcode, 3).addReg(ValReg).addSImm(offset->getValue())
3134           .addReg(baseReg);
3135       else
3136         BuildMI(BB, IdxOpcode, 3).addReg(ValReg).addReg(indexReg)
3137           .addReg(baseReg);
3138     } else {
3139       indexReg = (indexReg != 0) ? indexReg : getReg(offset);
3140       unsigned indexPlus4 = makeAnotherReg(Type::IntTy);
3141       BuildMI(BB, PPC::ADDI, 2, indexPlus4).addReg(indexReg).addSImm(4);
3142       BuildMI(BB, IdxOpcode, 3).addReg(ValReg).addReg(indexReg).addReg(baseReg);
3143       BuildMI(BB, IdxOpcode, 3).addReg(ValReg+1).addReg(indexPlus4)
3144         .addReg(baseReg);
3145     }
3146     return;
3147   }
3148   
3149   // If the store address wasn't the only use of a GEP, we fall back to the
3150   // standard path: store the ValReg at the value in AddressReg.
3151   unsigned AddressReg  = getReg(I.getOperand(1));
3152   if (Class == cLong) {
3153     BuildMI(BB, ImmOpcode, 3).addReg(ValReg).addSImm(0).addReg(AddressReg);
3154     BuildMI(BB, ImmOpcode, 3).addReg(ValReg+1).addSImm(4).addReg(AddressReg);
3155     return;
3156   }
3157   BuildMI(BB, ImmOpcode, 3).addReg(ValReg).addSImm(0).addReg(AddressReg);
3158 }
3159
3160
3161 /// visitCastInst - Here we have various kinds of copying with or without sign
3162 /// extension going on.
3163 ///
3164 void PPC32ISel::visitCastInst(CastInst &CI) {
3165   Value *Op = CI.getOperand(0);
3166
3167   unsigned SrcClass = getClassB(Op->getType());
3168   unsigned DestClass = getClassB(CI.getType());
3169
3170   // Noop casts are not emitted: getReg will return the source operand as the
3171   // register to use for any uses of the noop cast.
3172   if (DestClass == SrcClass) return;
3173
3174   // If this is a cast from a 32-bit integer to a Long type, and the only uses
3175   // of the cast are GEP instructions, then the cast does not need to be
3176   // generated explicitly, it will be folded into the GEP.
3177   if (DestClass == cLong && SrcClass == cInt) {
3178     bool AllUsesAreGEPs = true;
3179     for (Value::use_iterator I = CI.use_begin(), E = CI.use_end(); I != E; ++I)
3180       if (!isa<GetElementPtrInst>(*I)) {
3181         AllUsesAreGEPs = false;
3182         break;
3183       }        
3184     if (AllUsesAreGEPs) return;
3185   }
3186   
3187   unsigned DestReg = getReg(CI);
3188   MachineBasicBlock::iterator MI = BB->end();
3189
3190   // If this is a cast from an integer type to a ubyte, with one use where the
3191   // use is the shift amount argument of a shift instruction, just emit a move
3192   // instead (since the shift instruction will only look at the low 5 bits
3193   // regardless of how it is sign extended)
3194   if (CI.getType() == Type::UByteTy && SrcClass <= cInt && CI.hasOneUse()) {
3195     ShiftInst *SI = dyn_cast<ShiftInst>(*(CI.use_begin()));
3196     if (SI && (SI->getOperand(1) == &CI)) {
3197       unsigned SrcReg = getReg(Op, BB, MI);
3198       BuildMI(*BB, MI, PPC::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
3199       return; 
3200     }
3201   }
3202
3203   // If this is a cast from an byte, short, or int to an integer type of equal
3204   // or lesser width, and all uses of the cast are store instructions then dont
3205   // emit them, as the store instruction will implicitly not store the zero or
3206   // sign extended bytes.
3207   if (SrcClass <= cInt && SrcClass >= DestClass) {
3208     bool AllUsesAreStores = true;
3209     for (Value::use_iterator I = CI.use_begin(), E = CI.use_end(); I != E; ++I)
3210       if (!isa<StoreInst>(*I)) {
3211         AllUsesAreStores = false;
3212         break;
3213       }        
3214     // Turn this cast directly into a move instruction, which the register
3215     // allocator will deal with.
3216     if (AllUsesAreStores) { 
3217       unsigned SrcReg = getReg(Op, BB, MI);
3218       BuildMI(*BB, MI, PPC::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
3219       return; 
3220     }
3221   }
3222   emitCastOperation(BB, MI, Op, CI.getType(), DestReg);
3223 }
3224
3225 /// emitCastOperation - Common code shared between visitCastInst and constant
3226 /// expression cast support.
3227 ///
3228 void PPC32ISel::emitCastOperation(MachineBasicBlock *MBB,
3229                                   MachineBasicBlock::iterator IP,
3230                                   Value *Src, const Type *DestTy,
3231                                   unsigned DestReg) {
3232   const Type *SrcTy = Src->getType();
3233   unsigned SrcClass = getClassB(SrcTy);
3234   unsigned DestClass = getClassB(DestTy);
3235   unsigned SrcReg = getReg(Src, MBB, IP);
3236
3237   // Implement casts from bool to integer types as a move operation
3238   if (SrcTy == Type::BoolTy) {
3239     switch (DestClass) {
3240     case cByte:
3241     case cShort:
3242     case cInt:
3243       BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
3244       return;
3245     case cLong:
3246       BuildMI(*MBB, IP, PPC::LI, 1, DestReg).addImm(0);
3247       BuildMI(*MBB, IP, PPC::OR, 2, DestReg+1).addReg(SrcReg).addReg(SrcReg);
3248       return;
3249     default:
3250       break;
3251     }
3252   }
3253
3254   // Implement casts to bool by using compare on the operand followed by set if
3255   // not zero on the result.
3256   if (DestTy == Type::BoolTy) {
3257     switch (SrcClass) {
3258     case cByte:
3259     case cShort:
3260     case cInt: {
3261       unsigned TmpReg = makeAnotherReg(Type::IntTy);
3262       BuildMI(*MBB, IP, PPC::ADDIC, 2, TmpReg).addReg(SrcReg).addSImm(-1);
3263       BuildMI(*MBB, IP, PPC::SUBFE, 2, DestReg).addReg(TmpReg).addReg(SrcReg);
3264       break;
3265     }
3266     case cLong: {
3267       unsigned TmpReg = makeAnotherReg(Type::IntTy);
3268       unsigned SrcReg2 = makeAnotherReg(Type::IntTy);
3269       BuildMI(*MBB, IP, PPC::OR, 2, SrcReg2).addReg(SrcReg).addReg(SrcReg+1);
3270       BuildMI(*MBB, IP, PPC::ADDIC, 2, TmpReg).addReg(SrcReg2).addSImm(-1);
3271       BuildMI(*MBB, IP, PPC::SUBFE, 2, DestReg).addReg(TmpReg)
3272         .addReg(SrcReg2);
3273       break;
3274     }
3275     case cFP32:
3276     case cFP64:
3277       unsigned TmpReg = makeAnotherReg(Type::IntTy);
3278       unsigned ConstZero = getReg(ConstantFP::get(Type::DoubleTy, 0.0), BB, IP);
3279       BuildMI(*MBB, IP, PPC::FCMPU, PPC::CR7).addReg(SrcReg).addReg(ConstZero);
3280       BuildMI(*MBB, IP, PPC::MFCR, TmpReg);
3281       BuildMI(*MBB, IP, PPC::RLWINM, DestReg).addReg(TmpReg).addImm(31)
3282         .addImm(31).addImm(31);
3283     }
3284     return;
3285   }
3286
3287   // Handle cast of Float -> Double
3288   if (SrcClass == cFP32 && DestClass == cFP64) {
3289     BuildMI(*MBB, IP, PPC::FMR, 1, DestReg).addReg(SrcReg);
3290     return;
3291   }
3292   
3293   // Handle cast of Double -> Float
3294   if (SrcClass == cFP64 && DestClass == cFP32) {
3295     BuildMI(*MBB, IP, PPC::FRSP, 1, DestReg).addReg(SrcReg);
3296     return;
3297   }
3298   
3299   // Handle casts from integer to floating point now...
3300   if (DestClass == cFP32 || DestClass == cFP64) {
3301
3302     // Emit a library call for long to float conversion
3303     if (SrcClass == cLong) {
3304       Function *floatFn = (DestClass == cFP32) ? __floatdisfFn : __floatdidfFn;
3305       if (SrcTy->isSigned()) {
3306         std::vector<ValueRecord> Args;
3307         Args.push_back(ValueRecord(SrcReg, SrcTy));
3308         MachineInstr *TheCall =
3309           BuildMI(PPC::CALLpcrel, 1).addGlobalAddress(floatFn, true);
3310         doCall(ValueRecord(DestReg, DestTy), TheCall, Args, false);
3311       } else {
3312         std::vector<ValueRecord> CmpArgs, ClrArgs, SetArgs;
3313         unsigned ZeroLong = getReg(ConstantUInt::get(SrcTy, 0));
3314         unsigned CondReg = makeAnotherReg(Type::IntTy);
3315
3316         // Update machine-CFG edges
3317         MachineBasicBlock *ClrMBB = new MachineBasicBlock(BB->getBasicBlock());
3318         MachineBasicBlock *SetMBB = new MachineBasicBlock(BB->getBasicBlock());
3319         MachineBasicBlock *PhiMBB = new MachineBasicBlock(BB->getBasicBlock());
3320         MachineBasicBlock *OldMBB = BB;
3321         ilist<MachineBasicBlock>::iterator It = BB; ++It;
3322         F->getBasicBlockList().insert(It, ClrMBB);
3323         F->getBasicBlockList().insert(It, SetMBB);
3324         F->getBasicBlockList().insert(It, PhiMBB);
3325         BB->addSuccessor(ClrMBB);
3326         BB->addSuccessor(SetMBB);
3327
3328         CmpArgs.push_back(ValueRecord(SrcReg, SrcTy));
3329         CmpArgs.push_back(ValueRecord(ZeroLong, SrcTy));
3330         MachineInstr *TheCall =
3331           BuildMI(PPC::CALLpcrel, 1).addGlobalAddress(__cmpdi2Fn, true);
3332         doCall(ValueRecord(CondReg, Type::IntTy), TheCall, CmpArgs, false);
3333         BuildMI(*MBB, IP, PPC::CMPWI, 2, PPC::CR0).addReg(CondReg).addSImm(0);
3334         BuildMI(*MBB, IP, PPC::BLE, 2).addReg(PPC::CR0).addMBB(SetMBB);
3335
3336         // ClrMBB
3337         BB = ClrMBB;
3338         unsigned ClrReg = makeAnotherReg(DestTy);
3339         ClrArgs.push_back(ValueRecord(SrcReg, SrcTy));
3340         TheCall = BuildMI(PPC::CALLpcrel, 1).addGlobalAddress(floatFn, true);
3341         doCall(ValueRecord(ClrReg, DestTy), TheCall, ClrArgs, false);
3342         BuildMI(BB, PPC::B, 1).addMBB(PhiMBB);
3343         BB->addSuccessor(PhiMBB);
3344         
3345         // SetMBB
3346         BB = SetMBB;
3347         unsigned SetReg = makeAnotherReg(DestTy);
3348         unsigned CallReg = makeAnotherReg(DestTy);
3349         unsigned ShiftedReg = makeAnotherReg(SrcTy);
3350         ConstantSInt *Const1 = ConstantSInt::get(Type::IntTy, 1);
3351         emitShiftOperation(BB, BB->end(), Src, Const1, false, SrcTy, 0, 
3352                            ShiftedReg);
3353         SetArgs.push_back(ValueRecord(ShiftedReg, SrcTy));
3354         TheCall = BuildMI(PPC::CALLpcrel, 1).addGlobalAddress(floatFn, true);
3355         doCall(ValueRecord(CallReg, DestTy), TheCall, SetArgs, false);
3356         unsigned SetOpcode = (DestClass == cFP32) ? PPC::FADDS : PPC::FADD;
3357         BuildMI(BB, SetOpcode, 2, SetReg).addReg(CallReg).addReg(CallReg);
3358         BB->addSuccessor(PhiMBB);
3359         
3360         // PhiMBB
3361         BB = PhiMBB;
3362         BuildMI(BB, PPC::PHI, 4, DestReg).addReg(ClrReg).addMBB(ClrMBB)
3363           .addReg(SetReg).addMBB(SetMBB);
3364       }
3365       return;
3366     }
3367     
3368     // Make sure we're dealing with a full 32 bits
3369     if (SrcClass < cInt) {
3370       unsigned TmpReg = makeAnotherReg(Type::IntTy);
3371       promote32(TmpReg, ValueRecord(SrcReg, SrcTy));
3372       SrcReg = TmpReg;
3373     }
3374     
3375     // Spill the integer to memory and reload it from there.
3376     // Also spill room for a special conversion constant
3377     int ValueFrameIdx =
3378       F->getFrameInfo()->CreateStackObject(Type::DoubleTy, TM.getTargetData());
3379
3380     unsigned constantHi = makeAnotherReg(Type::IntTy);
3381     unsigned TempF = makeAnotherReg(Type::DoubleTy);
3382     
3383     if (!SrcTy->isSigned()) {
3384       ConstantFP *CFP = ConstantFP::get(Type::DoubleTy, 0x1.000000p52);
3385       unsigned ConstF = getReg(CFP, BB, IP);
3386       BuildMI(*MBB, IP, PPC::LIS, 1, constantHi).addSImm(0x4330);
3387       addFrameReference(BuildMI(*MBB, IP, PPC::STW, 3).addReg(constantHi), 
3388                         ValueFrameIdx);
3389       addFrameReference(BuildMI(*MBB, IP, PPC::STW, 3).addReg(SrcReg), 
3390                         ValueFrameIdx, 4);
3391       addFrameReference(BuildMI(*MBB, IP, PPC::LFD, 2, TempF), ValueFrameIdx);
3392       BuildMI(*MBB, IP, PPC::FSUB, 2, DestReg).addReg(TempF).addReg(ConstF);
3393     } else {
3394       ConstantFP *CFP = ConstantFP::get(Type::DoubleTy, 0x1.000008p52);
3395       unsigned ConstF = getReg(CFP, BB, IP);
3396       unsigned TempLo = makeAnotherReg(Type::IntTy);
3397       BuildMI(*MBB, IP, PPC::LIS, 1, constantHi).addSImm(0x4330);
3398       addFrameReference(BuildMI(*MBB, IP, PPC::STW, 3).addReg(constantHi), 
3399                         ValueFrameIdx);
3400       BuildMI(*MBB, IP, PPC::XORIS, 2, TempLo).addReg(SrcReg).addImm(0x8000);
3401       addFrameReference(BuildMI(*MBB, IP, PPC::STW, 3).addReg(TempLo), 
3402                         ValueFrameIdx, 4);
3403       addFrameReference(BuildMI(*MBB, IP, PPC::LFD, 2, TempF), ValueFrameIdx);
3404       BuildMI(*MBB, IP, PPC::FSUB, 2, DestReg).addReg(TempF).addReg(ConstF);
3405     }
3406     return;
3407   }
3408
3409   // Handle casts from floating point to integer now...
3410   if (SrcClass == cFP32 || SrcClass == cFP64) {
3411     static Function* const Funcs[] =
3412       { __fixsfdiFn, __fixdfdiFn, __fixunssfdiFn, __fixunsdfdiFn };
3413     // emit library call
3414     if (DestClass == cLong) {
3415       bool isDouble = SrcClass == cFP64;
3416       unsigned nameIndex = 2 * DestTy->isSigned() + isDouble;
3417       std::vector<ValueRecord> Args;
3418       Args.push_back(ValueRecord(SrcReg, SrcTy));
3419       Function *floatFn = Funcs[nameIndex];
3420       MachineInstr *TheCall =
3421         BuildMI(PPC::CALLpcrel, 1).addGlobalAddress(floatFn, true);
3422       doCall(ValueRecord(DestReg, DestTy), TheCall, Args, false);
3423       return;
3424     }
3425
3426     int ValueFrameIdx =
3427       F->getFrameInfo()->CreateStackObject(Type::DoubleTy, TM.getTargetData());
3428
3429     if (DestTy->isSigned()) {
3430       unsigned TempReg = makeAnotherReg(Type::DoubleTy);
3431       
3432       // Convert to integer in the FP reg and store it to a stack slot
3433       BuildMI(*MBB, IP, PPC::FCTIWZ, 1, TempReg).addReg(SrcReg);
3434       addFrameReference(BuildMI(*MBB, IP, PPC::STFD, 3)
3435                           .addReg(TempReg), ValueFrameIdx);
3436
3437       // There is no load signed byte opcode, so we must emit a sign extend for
3438       // that particular size.  Make sure to source the new integer from the 
3439       // correct offset.
3440       if (DestClass == cByte) {
3441         unsigned TempReg2 = makeAnotherReg(DestTy);
3442         addFrameReference(BuildMI(*MBB, IP, PPC::LBZ, 2, TempReg2), 
3443                           ValueFrameIdx, 7);
3444         BuildMI(*MBB, IP, PPC::EXTSB, 1, DestReg).addReg(TempReg2);
3445       } else {
3446         int offset = (DestClass == cShort) ? 6 : 4;
3447         unsigned LoadOp = (DestClass == cShort) ? PPC::LHA : PPC::LWZ;
3448         addFrameReference(BuildMI(*MBB, IP, LoadOp, 2, DestReg), 
3449                           ValueFrameIdx, offset);
3450       }
3451     } else {
3452       unsigned Zero = getReg(ConstantFP::get(Type::DoubleTy, 0.0f));
3453       double maxInt = (1LL << 32) - 1;
3454       unsigned MaxInt = getReg(ConstantFP::get(Type::DoubleTy, maxInt));
3455       double border = 1LL << 31;
3456       unsigned Border = getReg(ConstantFP::get(Type::DoubleTy, border));
3457       unsigned UseZero = makeAnotherReg(Type::DoubleTy);
3458       unsigned UseMaxInt = makeAnotherReg(Type::DoubleTy);
3459       unsigned UseChoice = makeAnotherReg(Type::DoubleTy);
3460       unsigned TmpReg = makeAnotherReg(Type::DoubleTy);
3461       unsigned TmpReg2 = makeAnotherReg(Type::DoubleTy);
3462       unsigned ConvReg = makeAnotherReg(Type::DoubleTy);
3463       unsigned IntTmp = makeAnotherReg(Type::IntTy);
3464       unsigned XorReg = makeAnotherReg(Type::IntTy);
3465       int FrameIdx = 
3466         F->getFrameInfo()->CreateStackObject(SrcTy, TM.getTargetData());
3467       // Update machine-CFG edges
3468       MachineBasicBlock *XorMBB = new MachineBasicBlock(BB->getBasicBlock());
3469       MachineBasicBlock *PhiMBB = new MachineBasicBlock(BB->getBasicBlock());
3470       MachineBasicBlock *OldMBB = BB;
3471       ilist<MachineBasicBlock>::iterator It = BB; ++It;
3472       F->getBasicBlockList().insert(It, XorMBB);
3473       F->getBasicBlockList().insert(It, PhiMBB);
3474       BB->addSuccessor(XorMBB);
3475       BB->addSuccessor(PhiMBB);
3476
3477       // Convert from floating point to unsigned 32-bit value
3478       // Use 0 if incoming value is < 0.0
3479       BuildMI(*MBB, IP, PPC::FSEL, 3, UseZero).addReg(SrcReg).addReg(SrcReg)
3480         .addReg(Zero);
3481       // Use 2**32 - 1 if incoming value is >= 2**32
3482       BuildMI(*MBB, IP, PPC::FSUB, 2, UseMaxInt).addReg(MaxInt).addReg(SrcReg);
3483       BuildMI(*MBB, IP, PPC::FSEL, 3, UseChoice).addReg(UseMaxInt)
3484         .addReg(UseZero).addReg(MaxInt);
3485       // Subtract 2**31
3486       BuildMI(*MBB, IP, PPC::FSUB, 2, TmpReg).addReg(UseChoice).addReg(Border);
3487       // Use difference if >= 2**31
3488       BuildMI(*MBB, IP, PPC::FCMPU, 2, PPC::CR0).addReg(UseChoice)
3489         .addReg(Border);
3490       BuildMI(*MBB, IP, PPC::FSEL, 3, TmpReg2).addReg(TmpReg).addReg(TmpReg)
3491         .addReg(UseChoice);
3492       // Convert to integer
3493       BuildMI(*MBB, IP, PPC::FCTIWZ, 1, ConvReg).addReg(TmpReg2);
3494       addFrameReference(BuildMI(*MBB, IP, PPC::STFD, 3).addReg(ConvReg),
3495                         FrameIdx);
3496       if (DestClass == cByte) {
3497         addFrameReference(BuildMI(*MBB, IP, PPC::LBZ, 2, DestReg),
3498                           FrameIdx, 7);
3499       } else if (DestClass == cShort) {
3500         addFrameReference(BuildMI(*MBB, IP, PPC::LHZ, 2, DestReg),
3501                           FrameIdx, 6);
3502       } if (DestClass == cInt) {
3503         addFrameReference(BuildMI(*MBB, IP, PPC::LWZ, 2, IntTmp),
3504                           FrameIdx, 4);
3505         BuildMI(*MBB, IP, PPC::BLT, 2).addReg(PPC::CR0).addMBB(PhiMBB);
3506         BuildMI(*MBB, IP, PPC::B, 1).addMBB(XorMBB);
3507
3508         // XorMBB:
3509         //   add 2**31 if input was >= 2**31
3510         BB = XorMBB;
3511         BuildMI(BB, PPC::XORIS, 2, XorReg).addReg(IntTmp).addImm(0x8000);
3512         XorMBB->addSuccessor(PhiMBB);
3513
3514         // PhiMBB:
3515         //   DestReg = phi [ IntTmp, OldMBB ], [ XorReg, XorMBB ]
3516         BB = PhiMBB;
3517         BuildMI(BB, PPC::PHI, 4, DestReg).addReg(IntTmp).addMBB(OldMBB)
3518           .addReg(XorReg).addMBB(XorMBB);
3519       }
3520     }
3521     return;
3522   }
3523
3524   // Check our invariants
3525   assert((SrcClass <= cInt || SrcClass == cLong) && 
3526          "Unhandled source class for cast operation!");
3527   assert((DestClass <= cInt || DestClass == cLong) && 
3528          "Unhandled destination class for cast operation!");
3529
3530   bool sourceUnsigned = SrcTy->isUnsigned() || SrcTy == Type::BoolTy;
3531   bool destUnsigned = DestTy->isUnsigned();
3532
3533   // Unsigned -> Unsigned, clear if larger, 
3534   if (sourceUnsigned && destUnsigned) {
3535     // handle long dest class now to keep switch clean
3536     if (DestClass == cLong) {
3537       BuildMI(*MBB, IP, PPC::LI, 1, DestReg).addSImm(0);
3538       BuildMI(*MBB, IP, PPC::OR, 2, DestReg+1).addReg(SrcReg)
3539         .addReg(SrcReg);
3540       return;
3541     }
3542
3543     // handle u{ byte, short, int } x u{ byte, short, int }
3544     unsigned clearBits = (SrcClass == cByte || DestClass == cByte) ? 24 : 16;
3545     switch (SrcClass) {
3546     case cByte:
3547     case cShort:
3548       BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(SrcReg)
3549         .addImm(0).addImm(clearBits).addImm(31);
3550       break;
3551     case cLong:
3552       ++SrcReg;
3553       // Fall through
3554     case cInt:
3555       BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(SrcReg)
3556         .addImm(0).addImm(clearBits).addImm(31);
3557       break;
3558     }
3559     return;
3560   }
3561
3562   // Signed -> Signed
3563   if (!sourceUnsigned && !destUnsigned) {
3564     // handle long dest class now to keep switch clean
3565     if (DestClass == cLong) {
3566       BuildMI(*MBB, IP, PPC::SRAWI, 2, DestReg).addReg(SrcReg).addImm(31);
3567       BuildMI(*MBB, IP, PPC::OR, 2, DestReg+1).addReg(SrcReg)
3568         .addReg(SrcReg);
3569       return;
3570     }
3571
3572     // handle { byte, short, int } x { byte, short, int }
3573     switch (SrcClass) {
3574     case cByte:
3575       BuildMI(*MBB, IP, PPC::EXTSB, 1, DestReg).addReg(SrcReg);
3576       break;
3577     case cShort:
3578       if (DestClass == cByte)
3579         BuildMI(*MBB, IP, PPC::EXTSB, 1, DestReg).addReg(SrcReg);
3580       else
3581         BuildMI(*MBB, IP, PPC::EXTSH, 1, DestReg).addReg(SrcReg);
3582       break;
3583     case cLong:
3584       ++SrcReg;
3585       // Fall through
3586     case cInt:
3587       if (DestClass == cByte)
3588         BuildMI(*MBB, IP, PPC::EXTSB, 1, DestReg).addReg(SrcReg);
3589       else if (DestClass == cShort)
3590         BuildMI(*MBB, IP, PPC::EXTSH, 1, DestReg).addReg(SrcReg);
3591       else
3592         BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
3593       break;
3594     }
3595     return;
3596   }
3597
3598   // Unsigned -> Signed
3599   if (sourceUnsigned && !destUnsigned) {
3600     // handle long dest class now to keep switch clean
3601     if (DestClass == cLong) {
3602       BuildMI(*MBB, IP, PPC::LI, 1, DestReg).addSImm(0);
3603       BuildMI(*MBB, IP, PPC::OR, 2, DestReg+1).addReg(SrcReg)
3604         .addReg(SrcReg);
3605       return;
3606     }
3607
3608     // handle u{ byte, short, int } -> { byte, short, int }
3609     switch (SrcClass) {
3610     case cByte:
3611       // uByte 255 -> signed short/int == 255
3612       BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(SrcReg).addImm(0)
3613         .addImm(24).addImm(31);
3614       break;
3615     case cShort:
3616       if (DestClass == cByte)
3617         BuildMI(*MBB, IP, PPC::EXTSB, 1, DestReg).addReg(SrcReg);
3618       else
3619         BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(SrcReg).addImm(0)
3620           .addImm(16).addImm(31);
3621       break;
3622     case cLong:
3623       ++SrcReg;
3624       // Fall through
3625     case cInt:
3626       if (DestClass == cByte)
3627         BuildMI(*MBB, IP, PPC::EXTSB, 1, DestReg).addReg(SrcReg);
3628       else if (DestClass == cShort)
3629         BuildMI(*MBB, IP, PPC::EXTSH, 1, DestReg).addReg(SrcReg);
3630       else
3631         BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
3632       break;
3633     }
3634     return;
3635   }
3636
3637   // Signed -> Unsigned
3638   if (!sourceUnsigned && destUnsigned) {
3639     // handle long dest class now to keep switch clean
3640     if (DestClass == cLong) {
3641       BuildMI(*MBB, IP, PPC::SRAWI, 2, DestReg).addReg(SrcReg).addImm(31);
3642       BuildMI(*MBB, IP, PPC::OR, 2, DestReg+1).addReg(SrcReg)
3643         .addReg(SrcReg);
3644       return;
3645     }
3646
3647     // handle { byte, short, int } -> u{ byte, short, int }
3648     unsigned clearBits = (DestClass == cByte) ? 24 : 16;
3649     switch (SrcClass) {
3650     case cByte:
3651        BuildMI(*MBB, IP, PPC::EXTSB, 1, DestReg).addReg(SrcReg);
3652        break;
3653     case cShort:
3654       if (DestClass == cByte)
3655         BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(SrcReg)
3656           .addImm(0).addImm(clearBits).addImm(31);
3657       else
3658         BuildMI(*MBB, IP, PPC::EXTSH, 1, DestReg).addReg(SrcReg);
3659       break;
3660     case cLong:
3661       ++SrcReg;
3662       // Fall through
3663     case cInt:
3664       if (DestClass == cInt)
3665         BuildMI(*MBB, IP, PPC::OR, 2, DestReg).addReg(SrcReg).addReg(SrcReg);
3666       else
3667         BuildMI(*MBB, IP, PPC::RLWINM, 4, DestReg).addReg(SrcReg)
3668           .addImm(0).addImm(clearBits).addImm(31);
3669       break;
3670     }
3671     return;
3672   }
3673
3674   // Anything we haven't handled already, we can't (yet) handle at all.
3675   std::cerr << "Unhandled cast from " << SrcTy->getDescription()
3676             << "to " << DestTy->getDescription() << '\n';
3677   abort();
3678 }
3679
3680 /// visitVANextInst - Implement the va_next instruction...
3681 ///
3682 void PPC32ISel::visitVANextInst(VANextInst &I) {
3683   unsigned VAList = getReg(I.getOperand(0));
3684   unsigned DestReg = getReg(I);
3685
3686   unsigned Size;
3687   switch (I.getArgType()->getTypeID()) {
3688   default:
3689     std::cerr << I;
3690     assert(0 && "Error: bad type for va_next instruction!");
3691     return;
3692   case Type::PointerTyID:
3693   case Type::UIntTyID:
3694   case Type::IntTyID:
3695     Size = 4;
3696     break;
3697   case Type::ULongTyID:
3698   case Type::LongTyID:
3699   case Type::DoubleTyID:
3700     Size = 8;
3701     break;
3702   }
3703
3704   // Increment the VAList pointer...
3705   BuildMI(BB, PPC::ADDI, 2, DestReg).addReg(VAList).addSImm(Size);
3706 }
3707
3708 void PPC32ISel::visitVAArgInst(VAArgInst &I) {
3709   unsigned VAList = getReg(I.getOperand(0));
3710   unsigned DestReg = getReg(I);
3711
3712   switch (I.getType()->getTypeID()) {
3713   default:
3714     std::cerr << I;
3715     assert(0 && "Error: bad type for va_next instruction!");
3716     return;
3717   case Type::PointerTyID:
3718   case Type::UIntTyID:
3719   case Type::IntTyID:
3720     BuildMI(BB, PPC::LWZ, 2, DestReg).addSImm(0).addReg(VAList);
3721     break;
3722   case Type::ULongTyID:
3723   case Type::LongTyID:
3724     BuildMI(BB, PPC::LWZ, 2, DestReg).addSImm(0).addReg(VAList);
3725     BuildMI(BB, PPC::LWZ, 2, DestReg+1).addSImm(4).addReg(VAList);
3726     break;
3727   case Type::FloatTyID:
3728     BuildMI(BB, PPC::LFS, 2, DestReg).addSImm(0).addReg(VAList);
3729     break;
3730   case Type::DoubleTyID:
3731     BuildMI(BB, PPC::LFD, 2, DestReg).addSImm(0).addReg(VAList);
3732     break;
3733   }
3734 }
3735
3736 /// visitGetElementPtrInst - instruction-select GEP instructions
3737 ///
3738 void PPC32ISel::visitGetElementPtrInst(GetElementPtrInst &I) {
3739   if (canFoldGEPIntoLoadOrStore(&I))
3740     return;
3741
3742   emitGEPOperation(BB, BB->end(), &I, false);
3743 }
3744
3745 /// emitGEPOperation - Common code shared between visitGetElementPtrInst and
3746 /// constant expression GEP support.
3747 ///
3748 void PPC32ISel::emitGEPOperation(MachineBasicBlock *MBB,
3749                                  MachineBasicBlock::iterator IP,
3750                                  GetElementPtrInst *GEPI, bool GEPIsFolded) {
3751   // If we've already emitted this particular GEP, just return to avoid
3752   // multiple definitions of the base register.
3753   if (GEPIsFolded && (GEPMap[GEPI].base != 0))
3754     return;
3755   
3756   Value *Src = GEPI->getOperand(0);
3757   User::op_iterator IdxBegin = GEPI->op_begin()+1;
3758   User::op_iterator IdxEnd = GEPI->op_end();
3759   const TargetData &TD = TM.getTargetData();
3760   const Type *Ty = Src->getType();
3761   int32_t constValue = 0;
3762   
3763   // Record the operations to emit the GEP in a vector so that we can emit them
3764   // after having analyzed the entire instruction.
3765   std::vector<CollapsedGepOp> ops;
3766   
3767   // GEPs have zero or more indices; we must perform a struct access
3768   // or array access for each one.
3769   for (GetElementPtrInst::op_iterator oi = IdxBegin, oe = IdxEnd; oi != oe;
3770        ++oi) {
3771     Value *idx = *oi;
3772     if (const StructType *StTy = dyn_cast<StructType>(Ty)) {
3773       // It's a struct access.  idx is the index into the structure,
3774       // which names the field. Use the TargetData structure to
3775       // pick out what the layout of the structure is in memory.
3776       // Use the (constant) structure index's value to find the
3777       // right byte offset from the StructLayout class's list of
3778       // structure member offsets.
3779       unsigned fieldIndex = cast<ConstantUInt>(idx)->getValue();
3780
3781       // StructType member offsets are always constant values.  Add it to the
3782       // running total.
3783       constValue += TD.getStructLayout(StTy)->MemberOffsets[fieldIndex];
3784
3785       // The next type is the member of the structure selected by the index.
3786       Ty = StTy->getElementType (fieldIndex);
3787     } else if (const SequentialType *SqTy = dyn_cast<SequentialType>(Ty)) {
3788       // Many GEP instructions use a [cast (int/uint) to LongTy] as their
3789       // operand.  Handle this case directly now...
3790       if (CastInst *CI = dyn_cast<CastInst>(idx))
3791         if (CI->getOperand(0)->getType() == Type::IntTy ||
3792             CI->getOperand(0)->getType() == Type::UIntTy)
3793           idx = CI->getOperand(0);
3794
3795       // It's an array or pointer access: [ArraySize x ElementType].
3796       // We want to add basePtrReg to (idxReg * sizeof ElementType). First, we
3797       // must find the size of the pointed-to type (Not coincidentally, the next
3798       // type is the type of the elements in the array).
3799       Ty = SqTy->getElementType();
3800       unsigned elementSize = TD.getTypeSize(Ty);
3801       
3802       if (ConstantInt *C = dyn_cast<ConstantInt>(idx)) {
3803         if (ConstantSInt *CS = dyn_cast<ConstantSInt>(C))
3804           constValue += CS->getValue() * elementSize;
3805         else if (ConstantUInt *CU = dyn_cast<ConstantUInt>(C))
3806           constValue += CU->getValue() * elementSize;
3807         else
3808           assert(0 && "Invalid ConstantInt GEP index type!");
3809       } else {
3810         // Push current gep state to this point as an add and multiply
3811         ops.push_back(CollapsedGepOp(
3812           ConstantSInt::get(Type::IntTy, constValue),
3813           idx, ConstantUInt::get(Type::UIntTy, elementSize)));
3814
3815         constValue = 0;
3816       }
3817     }
3818   }
3819   // Emit instructions for all the collapsed ops
3820   unsigned indexReg = 0;
3821   for(std::vector<CollapsedGepOp>::iterator cgo_i = ops.begin(),
3822       cgo_e = ops.end(); cgo_i != cgo_e; ++cgo_i) {
3823     CollapsedGepOp& cgo = *cgo_i;
3824
3825     // Avoid emitting known move instructions here for the register allocator
3826     // to deal with later.  val * 1 == val.  val + 0 == val.
3827     unsigned TmpReg1;
3828     if (cgo.size->getValue() == 1) {
3829       TmpReg1 = getReg(cgo.index, MBB, IP);
3830     } else {
3831       TmpReg1 = makeAnotherReg(Type::IntTy);
3832       doMultiplyConst(MBB, IP, TmpReg1, cgo.index, cgo.size);
3833     }
3834     
3835     unsigned TmpReg2;
3836     if (cgo.offset->isNullValue()) { 
3837       TmpReg2 = TmpReg1;
3838     } else {
3839       TmpReg2 = makeAnotherReg(Type::IntTy);
3840       emitBinaryConstOperation(MBB, IP, TmpReg1, cgo.offset, 0, TmpReg2);
3841     }
3842     
3843     if (indexReg == 0)
3844       indexReg = TmpReg2;
3845     else {
3846       unsigned TmpReg3 = makeAnotherReg(Type::IntTy);
3847       BuildMI(*MBB, IP, PPC::ADD, 2, TmpReg3).addReg(indexReg).addReg(TmpReg2);
3848       indexReg = TmpReg3;
3849     }
3850   }
3851   
3852   // We now have a base register, an index register, and possibly a constant
3853   // remainder.  If the GEP is going to be folded, we try to generate the
3854   // optimal addressing mode.
3855   ConstantSInt *remainder = ConstantSInt::get(Type::IntTy, constValue);
3856   
3857   // If we are emitting this during a fold, copy the current base register to
3858   // the target, and save the current constant offset so the folding load or
3859   // store can try and use it as an immediate.
3860   if (GEPIsFolded) {
3861     if (indexReg == 0) {
3862       if (!canUseAsImmediateForOpcode(remainder, 0, false)) {
3863         indexReg = getReg(remainder, MBB, IP);
3864         remainder = 0;
3865       }
3866     } else if (!remainder->isNullValue()) {
3867       unsigned TmpReg = makeAnotherReg(Type::IntTy);
3868       emitBinaryConstOperation(MBB, IP, indexReg, remainder, 0, TmpReg);
3869       indexReg = TmpReg;
3870       remainder = 0;
3871     }
3872     unsigned basePtrReg = getReg(Src, MBB, IP);
3873     GEPMap[GEPI] = FoldedGEP(basePtrReg, indexReg, remainder);
3874     return;
3875   }
3876
3877   // We're not folding, so collapse the base, index, and any remainder into the
3878   // destination register.
3879   unsigned TargetReg = getReg(GEPI, MBB, IP);
3880   unsigned basePtrReg = getReg(Src, MBB, IP);
3881
3882   if ((indexReg == 0) && remainder->isNullValue()) {
3883     BuildMI(*MBB, IP, PPC::OR, 2, TargetReg).addReg(basePtrReg)
3884       .addReg(basePtrReg);
3885     return;
3886   }
3887   if (!remainder->isNullValue()) {
3888     unsigned TmpReg = (indexReg == 0) ? TargetReg : makeAnotherReg(Type::IntTy);
3889     emitBinaryConstOperation(MBB, IP, basePtrReg, remainder, 0, TmpReg);
3890     basePtrReg = TmpReg;
3891   }
3892   if (indexReg != 0)
3893     BuildMI(*MBB, IP, PPC::ADD, 2, TargetReg).addReg(indexReg)
3894       .addReg(basePtrReg);
3895 }
3896
3897 /// visitAllocaInst - If this is a fixed size alloca, allocate space from the
3898 /// frame manager, otherwise do it the hard way.
3899 ///
3900 void PPC32ISel::visitAllocaInst(AllocaInst &I) {
3901   // If this is a fixed size alloca in the entry block for the function, we
3902   // statically stack allocate the space, so we don't need to do anything here.
3903   //
3904   if (dyn_castFixedAlloca(&I)) return;
3905   
3906   // Find the data size of the alloca inst's getAllocatedType.
3907   const Type *Ty = I.getAllocatedType();
3908   unsigned TySize = TM.getTargetData().getTypeSize(Ty);
3909
3910   // Create a register to hold the temporary result of multiplying the type size
3911   // constant by the variable amount.
3912   unsigned TotalSizeReg = makeAnotherReg(Type::UIntTy);
3913   
3914   // TotalSizeReg = mul <numelements>, <TypeSize>
3915   MachineBasicBlock::iterator MBBI = BB->end();
3916   ConstantUInt *CUI = ConstantUInt::get(Type::UIntTy, TySize);
3917   doMultiplyConst(BB, MBBI, TotalSizeReg, I.getArraySize(), CUI);
3918
3919   // AddedSize = add <TotalSizeReg>, 15
3920   unsigned AddedSizeReg = makeAnotherReg(Type::UIntTy);
3921   BuildMI(BB, PPC::ADDI, 2, AddedSizeReg).addReg(TotalSizeReg).addSImm(15);
3922
3923   // AlignedSize = and <AddedSize>, ~15
3924   unsigned AlignedSize = makeAnotherReg(Type::UIntTy);
3925   BuildMI(BB, PPC::RLWINM, 4, AlignedSize).addReg(AddedSizeReg).addImm(0)
3926     .addImm(0).addImm(27);
3927   
3928   // Subtract size from stack pointer, thereby allocating some space.
3929   BuildMI(BB, PPC::SUBF, 2, PPC::R1).addReg(AlignedSize).addReg(PPC::R1);
3930
3931   // Put a pointer to the space into the result register, by copying
3932   // the stack pointer.
3933   BuildMI(BB, PPC::OR, 2, getReg(I)).addReg(PPC::R1).addReg(PPC::R1);
3934
3935   // Inform the Frame Information that we have just allocated a variable-sized
3936   // object.
3937   F->getFrameInfo()->CreateVariableSizedObject();
3938 }
3939
3940 /// visitMallocInst - Malloc instructions are code generated into direct calls
3941 /// to the library malloc.
3942 ///
3943 void PPC32ISel::visitMallocInst(MallocInst &I) {
3944   unsigned AllocSize = TM.getTargetData().getTypeSize(I.getAllocatedType());
3945   unsigned Arg;
3946
3947   if (ConstantUInt *C = dyn_cast<ConstantUInt>(I.getOperand(0))) {
3948     Arg = getReg(ConstantUInt::get(Type::UIntTy, C->getValue() * AllocSize));
3949   } else {
3950     Arg = makeAnotherReg(Type::UIntTy);
3951     MachineBasicBlock::iterator MBBI = BB->end();
3952     ConstantUInt *CUI = ConstantUInt::get(Type::UIntTy, AllocSize);
3953     doMultiplyConst(BB, MBBI, Arg, I.getOperand(0), CUI);
3954   }
3955
3956   std::vector<ValueRecord> Args;
3957   Args.push_back(ValueRecord(Arg, Type::UIntTy));
3958   MachineInstr *TheCall = 
3959     BuildMI(PPC::CALLpcrel, 1).addGlobalAddress(mallocFn, true);
3960   doCall(ValueRecord(getReg(I), I.getType()), TheCall, Args, false);
3961 }
3962
3963 /// visitFreeInst - Free instructions are code gen'd to call the free libc
3964 /// function.
3965 ///
3966 void PPC32ISel::visitFreeInst(FreeInst &I) {
3967   std::vector<ValueRecord> Args;
3968   Args.push_back(ValueRecord(I.getOperand(0)));
3969   MachineInstr *TheCall = 
3970     BuildMI(PPC::CALLpcrel, 1).addGlobalAddress(freeFn, true);
3971   doCall(ValueRecord(0, Type::VoidTy), TheCall, Args, false);
3972 }
3973    
3974 /// createPPC32ISelSimple - This pass converts an LLVM function into a machine
3975 /// code representation is a very simple peep-hole fashion.
3976 ///
3977 FunctionPass *llvm::createPPC32ISelSimple(TargetMachine &TM) {
3978   return new PPC32ISel(TM);
3979 }