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