blob: 23dfeffc8b3e011da1615b41284e3befe43726a6 [file] [log] [blame]
Chris Lattner1c809c52004-02-29 00:27:00 +00001//===-- InstSelectSimple.cpp - A simple instruction selector for SparcV8 --===//
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// This file defines a simple peephole instruction selector for the V8 target
11//
12//===----------------------------------------------------------------------===//
13
14#include "SparcV8.h"
Brian Gaekebc1d27a2004-03-03 23:03:14 +000015#include "SparcV8InstrInfo.h"
Chris Lattner1c809c52004-02-29 00:27:00 +000016#include "llvm/Instructions.h"
17#include "llvm/IntrinsicLowering.h"
18#include "llvm/Pass.h"
Brian Gaekebc1d27a2004-03-03 23:03:14 +000019#include "llvm/Constants.h"
Chris Lattner1c809c52004-02-29 00:27:00 +000020#include "llvm/CodeGen/MachineInstrBuilder.h"
21#include "llvm/CodeGen/MachineFunction.h"
Brian Gaekebc1d27a2004-03-03 23:03:14 +000022#include "llvm/CodeGen/SSARegMap.h"
Chris Lattner1c809c52004-02-29 00:27:00 +000023#include "llvm/Target/TargetMachine.h"
24#include "llvm/Support/GetElementPtrTypeIterator.h"
25#include "llvm/Support/InstVisitor.h"
26#include "llvm/Support/CFG.h"
27using namespace llvm;
28
29namespace {
30 struct V8ISel : public FunctionPass, public InstVisitor<V8ISel> {
31 TargetMachine &TM;
32 MachineFunction *F; // The function we are compiling into
33 MachineBasicBlock *BB; // The current MBB we are compiling
34
35 std::map<Value*, unsigned> RegMap; // Mapping between Val's and SSA Regs
36
37 // MBBMap - Mapping between LLVM BB -> Machine BB
38 std::map<const BasicBlock*, MachineBasicBlock*> MBBMap;
39
40 V8ISel(TargetMachine &tm) : TM(tm), F(0), BB(0) {}
41
42 /// runOnFunction - Top level implementation of instruction selection for
43 /// the entire function.
44 ///
45 bool runOnFunction(Function &Fn);
46
47 virtual const char *getPassName() const {
48 return "SparcV8 Simple Instruction Selection";
49 }
50
51 /// visitBasicBlock - This method is called when we are visiting a new basic
52 /// block. This simply creates a new MachineBasicBlock to emit code into
53 /// and adds it to the current MachineFunction. Subsequent visit* for
54 /// instructions will be invoked for all instructions in the basic block.
55 ///
56 void visitBasicBlock(BasicBlock &LLVM_BB) {
57 BB = MBBMap[&LLVM_BB];
58 }
59
Chris Lattner4be7ca52004-04-07 04:27:16 +000060 void visitBinaryOperator(Instruction &I);
61 void visitShiftInstruction(Instruction &I) { visitBinaryOperator(I); }
Chris Lattner4d0cda42004-04-07 05:04:51 +000062 void visitSetCondInst(Instruction &I);
Chris Lattner4be7ca52004-04-07 04:27:16 +000063 void visitCallInst(CallInst &I);
64 void visitReturnInst(ReturnInst &RI);
Chris Lattner1c809c52004-02-29 00:27:00 +000065
66 void visitInstruction(Instruction &I) {
67 std::cerr << "Unhandled instruction: " << I;
68 abort();
69 }
70
71 /// LowerUnknownIntrinsicFunctionCalls - This performs a prepass over the
72 /// function, lowering any calls to unknown intrinsic functions into the
73 /// equivalent LLVM code.
74 void LowerUnknownIntrinsicFunctionCalls(Function &F);
Chris Lattner1c809c52004-02-29 00:27:00 +000075 void visitIntrinsicCall(Intrinsic::ID ID, CallInst &CI);
76
Brian Gaeke562cb162004-04-07 17:04:09 +000077 void LoadArgumentsToVirtualRegs(Function *F);
78
Brian Gaekebc1d27a2004-03-03 23:03:14 +000079 /// copyConstantToRegister - Output the instructions required to put the
80 /// specified constant into the specified register.
81 ///
82 void copyConstantToRegister(MachineBasicBlock *MBB,
83 MachineBasicBlock::iterator IP,
84 Constant *C, unsigned R);
85
86 /// makeAnotherReg - This method returns the next register number we haven't
87 /// yet used.
88 ///
89 /// Long values are handled somewhat specially. They are always allocated
90 /// as pairs of 32 bit integer values. The register number returned is the
91 /// lower 32 bits of the long value, and the regNum+1 is the upper 32 bits
92 /// of the long value.
93 ///
94 unsigned makeAnotherReg(const Type *Ty) {
95 assert(dynamic_cast<const SparcV8RegisterInfo*>(TM.getRegisterInfo()) &&
96 "Current target doesn't have SparcV8 reg info??");
97 const SparcV8RegisterInfo *MRI =
98 static_cast<const SparcV8RegisterInfo*>(TM.getRegisterInfo());
99 if (Ty == Type::LongTy || Ty == Type::ULongTy) {
100 const TargetRegisterClass *RC = MRI->getRegClassForType(Type::IntTy);
101 // Create the lower part
102 F->getSSARegMap()->createVirtualRegister(RC);
103 // Create the upper part.
104 return F->getSSARegMap()->createVirtualRegister(RC)-1;
105 }
106
107 // Add the mapping of regnumber => reg class to MachineFunction
108 const TargetRegisterClass *RC = MRI->getRegClassForType(Ty);
109 return F->getSSARegMap()->createVirtualRegister(RC);
110 }
111
112 unsigned getReg(Value &V) { return getReg (&V); } // allow refs.
113 unsigned getReg(Value *V) {
114 // Just append to the end of the current bb.
115 MachineBasicBlock::iterator It = BB->end();
116 return getReg(V, BB, It);
117 }
118 unsigned getReg(Value *V, MachineBasicBlock *MBB,
119 MachineBasicBlock::iterator IPt) {
120 unsigned &Reg = RegMap[V];
121 if (Reg == 0) {
122 Reg = makeAnotherReg(V->getType());
123 RegMap[V] = Reg;
124 }
125 // If this operand is a constant, emit the code to copy the constant into
126 // the register here...
127 //
128 if (Constant *C = dyn_cast<Constant>(V)) {
129 copyConstantToRegister(MBB, IPt, C, Reg);
130 RegMap.erase(V); // Assign a new name to this constant if ref'd again
131 } else if (GlobalValue *GV = dyn_cast<GlobalValue>(V)) {
132 // Move the address of the global into the register
Brian Gaekecf471982004-03-09 04:49:13 +0000133 unsigned TmpReg = makeAnotherReg(V->getType());
134 BuildMI (*MBB, IPt, V8::SETHIi, 1, TmpReg).addGlobalAddress (GV);
135 BuildMI (*MBB, IPt, V8::ORri, 2, Reg).addReg (TmpReg)
136 .addGlobalAddress (GV);
Brian Gaekebc1d27a2004-03-03 23:03:14 +0000137 RegMap.erase(V); // Assign a new name to this address if ref'd again
138 }
139
140 return Reg;
141 }
142
Chris Lattner1c809c52004-02-29 00:27:00 +0000143 };
144}
145
146FunctionPass *llvm::createSparcV8SimpleInstructionSelector(TargetMachine &TM) {
147 return new V8ISel(TM);
148}
149
Brian Gaekebc1d27a2004-03-03 23:03:14 +0000150enum TypeClass {
Brian Gaekef57e3642004-03-16 22:37:11 +0000151 cByte, cShort, cInt, cLong, cFloat, cDouble
Brian Gaekebc1d27a2004-03-03 23:03:14 +0000152};
153
154static TypeClass getClass (const Type *T) {
155 switch (T->getPrimitiveID ()) {
156 case Type::UByteTyID: case Type::SByteTyID: return cByte;
157 case Type::UShortTyID: case Type::ShortTyID: return cShort;
Brian Gaeke562cb162004-04-07 17:04:09 +0000158 case Type::PointerTyID:
Brian Gaekebc1d27a2004-03-03 23:03:14 +0000159 case Type::UIntTyID: case Type::IntTyID: return cInt;
Brian Gaekef57e3642004-03-16 22:37:11 +0000160 case Type::ULongTyID: case Type::LongTyID: return cLong;
Brian Gaekebc1d27a2004-03-03 23:03:14 +0000161 case Type::FloatTyID: return cFloat;
162 case Type::DoubleTyID: return cDouble;
163 default:
164 assert (0 && "Type of unknown class passed to getClass?");
165 return cByte;
166 }
167}
Chris Lattner0d538bb2004-04-07 04:36:53 +0000168static TypeClass getClassB(const Type *T) {
169 if (T == Type::BoolTy) return cByte;
170 return getClass(T);
171}
172
173
Brian Gaekebc1d27a2004-03-03 23:03:14 +0000174
175/// copyConstantToRegister - Output the instructions required to put the
176/// specified constant into the specified register.
177///
178void V8ISel::copyConstantToRegister(MachineBasicBlock *MBB,
179 MachineBasicBlock::iterator IP,
180 Constant *C, unsigned R) {
Brian Gaeke775158d2004-03-04 04:37:45 +0000181 if (ConstantInt *CI = dyn_cast<ConstantInt> (C)) {
Brian Gaekebc1d27a2004-03-03 23:03:14 +0000182 unsigned Class = getClass(C->getType());
Chris Lattner4be7ca52004-04-07 04:27:16 +0000183 uint64_t Val = CI->getRawValue ();
Brian Gaekee8061732004-03-04 00:56:25 +0000184 switch (Class) {
185 case cByte:
Chris Lattner4be7ca52004-04-07 04:27:16 +0000186 BuildMI (*MBB, IP, V8::ORri, 2, R).addReg (V8::G0).addImm((uint8_t)Val);
Brian Gaekee8061732004-03-04 00:56:25 +0000187 return;
188 case cShort: {
189 unsigned TmpReg = makeAnotherReg (C->getType ());
Chris Lattner4be7ca52004-04-07 04:27:16 +0000190 BuildMI (*MBB, IP, V8::SETHIi, 1, TmpReg)
191 .addImm (((uint16_t) Val) >> 10);
192 BuildMI (*MBB, IP, V8::ORri, 2, R).addReg (TmpReg)
193 .addImm (((uint16_t) Val) & 0x03ff);
Brian Gaekee8061732004-03-04 00:56:25 +0000194 return;
195 }
196 case cInt: {
197 unsigned TmpReg = makeAnotherReg (C->getType ());
Chris Lattner4be7ca52004-04-07 04:27:16 +0000198 BuildMI (*MBB, IP, V8::SETHIi, 1, TmpReg).addImm(((uint32_t)Val) >> 10);
199 BuildMI (*MBB, IP, V8::ORri, 2, R).addReg (TmpReg)
200 .addImm (((uint32_t) Val) & 0x03ff);
Brian Gaekee8061732004-03-04 00:56:25 +0000201 return;
202 }
Brian Gaeke2d4fa8f2004-04-07 04:00:49 +0000203 case cLong: {
204 unsigned TmpReg = makeAnotherReg (Type::UIntTy);
Chris Lattner4be7ca52004-04-07 04:27:16 +0000205 uint32_t topHalf = (uint32_t) (Val >> 32);
206 uint32_t bottomHalf = (uint32_t)Val;
Brian Gaeke2d4fa8f2004-04-07 04:00:49 +0000207 BuildMI (*MBB, IP, V8::SETHIi, 1, TmpReg).addImm (topHalf >> 10);
Chris Lattner4be7ca52004-04-07 04:27:16 +0000208 BuildMI (*MBB, IP, V8::ORri, 2, R).addReg (TmpReg)
209 .addImm (topHalf & 0x03ff);
Brian Gaeke2d4fa8f2004-04-07 04:00:49 +0000210 BuildMI (*MBB, IP, V8::SETHIi, 1, TmpReg).addImm (bottomHalf >> 10);
Chris Lattner4be7ca52004-04-07 04:27:16 +0000211 BuildMI (*MBB, IP, V8::ORri, 2, R).addReg (TmpReg)
212 .addImm (bottomHalf & 0x03ff);
Brian Gaeke2d4fa8f2004-04-07 04:00:49 +0000213 return;
214 }
Brian Gaekee8061732004-03-04 00:56:25 +0000215 default:
Brian Gaeke2d4fa8f2004-04-07 04:00:49 +0000216 std::cerr << "Offending constant: " << *C << "\n";
Brian Gaeke775158d2004-03-04 04:37:45 +0000217 assert (0 && "Can't copy this kind of constant into register yet");
Brian Gaekee8061732004-03-04 00:56:25 +0000218 return;
219 }
Brian Gaekebc1d27a2004-03-03 23:03:14 +0000220 }
221
Brian Gaeke2d4fa8f2004-04-07 04:00:49 +0000222 std::cerr << "Offending constant: " << *C << "\n";
Brian Gaeke775158d2004-03-04 04:37:45 +0000223 assert (0 && "Can't copy this kind of constant into register yet");
Brian Gaekebc1d27a2004-03-03 23:03:14 +0000224}
Chris Lattner1c809c52004-02-29 00:27:00 +0000225
Brian Gaeke562cb162004-04-07 17:04:09 +0000226void V8ISel::LoadArgumentsToVirtualRegs (Function *F) {
227 unsigned ArgOffset = 0;
228 static const unsigned IncomingArgRegs[] = { V8::I0, V8::I1, V8::I2,
229 V8::I3, V8::I4, V8::I5 };
230 assert (F->asize () < 7
231 && "Can't handle loading excess call args off the stack yet");
232
233 for (Function::aiterator I = F->abegin(), E = F->aend(); I != E; ++I) {
234 unsigned Reg = getReg(*I);
235 switch (getClassB(I->getType())) {
236 case cByte:
237 case cShort:
238 case cInt:
239 BuildMI(BB, V8::ORrr, 2, Reg).addReg (V8::G0)
240 .addReg (IncomingArgRegs[ArgOffset]);
241 break;
242 default:
243 assert (0 && "Only <=32-bit, integral arguments currently handled");
244 return;
245 }
246 ++ArgOffset;
247 }
248}
249
Chris Lattner1c809c52004-02-29 00:27:00 +0000250bool V8ISel::runOnFunction(Function &Fn) {
251 // First pass over the function, lower any unknown intrinsic functions
252 // with the IntrinsicLowering class.
253 LowerUnknownIntrinsicFunctionCalls(Fn);
254
255 F = &MachineFunction::construct(&Fn, TM);
256
257 // Create all of the machine basic blocks for the function...
258 for (Function::iterator I = Fn.begin(), E = Fn.end(); I != E; ++I)
259 F->getBasicBlockList().push_back(MBBMap[I] = new MachineBasicBlock(I));
260
261 BB = &F->front();
262
263 // Set up a frame object for the return address. This is used by the
264 // llvm.returnaddress & llvm.frameaddress intrinisics.
265 //ReturnAddressIndex = F->getFrameInfo()->CreateFixedObject(4, -4);
266
267 // Copy incoming arguments off of the stack and out of fixed registers.
Brian Gaeke562cb162004-04-07 17:04:09 +0000268 LoadArgumentsToVirtualRegs(&Fn);
Chris Lattner1c809c52004-02-29 00:27:00 +0000269
270 // Instruction select everything except PHI nodes
271 visit(Fn);
272
273 // Select the PHI nodes
274 //SelectPHINodes();
275
276 RegMap.clear();
277 MBBMap.clear();
278 F = 0;
279 // We always build a machine code representation for the function
280 return true;
281}
282
Brian Gaekef7e44ef2004-04-02 20:53:33 +0000283void V8ISel::visitCallInst(CallInst &I) {
Brian Gaeked54c38b2004-04-07 16:41:22 +0000284 assert (I.getNumOperands () < 8
285 && "Can't handle pushing excess call args on the stack yet");
Brian Gaeke562cb162004-04-07 17:04:09 +0000286 static const unsigned OutgoingArgRegs[] = { V8::O0, V8::O1, V8::O2, V8::O3,
Brian Gaeked54c38b2004-04-07 16:41:22 +0000287 V8::O4, V8::O5 };
288 for (unsigned i = 1; i < 7; ++i)
289 if (i < I.getNumOperands ()) {
290 unsigned ArgReg = getReg (I.getOperand (i));
291 // Schlep it over into the incoming arg register
Brian Gaeke562cb162004-04-07 17:04:09 +0000292 BuildMI (BB, V8::ORrr, 2, OutgoingArgRegs[i - 1]).addReg (V8::G0)
Brian Gaeked54c38b2004-04-07 16:41:22 +0000293 .addReg (ArgReg);
294 }
295
Brian Gaekeea8494b2004-04-06 22:09:23 +0000296 unsigned DestReg = getReg (I);
Brian Gaekef7e44ef2004-04-02 20:53:33 +0000297 BuildMI (BB, V8::CALL, 1).addPCDisp (I.getOperand (0));
Brian Gaekeea8494b2004-04-06 22:09:23 +0000298 if (I.getType ()->getPrimitiveID () == Type::VoidTyID)
299 return;
300 // Deal w/ return value
301 switch (getClass (I.getType ())) {
302 case cByte:
303 case cShort:
304 case cInt:
305 // Schlep it over into the destination register
306 BuildMI (BB, V8::ORrr, 2, DestReg).addReg(V8::G0).addReg(V8::O0);
307 break;
308 default:
309 visitInstruction (I);
310 return;
311 }
Brian Gaekef7e44ef2004-04-02 20:53:33 +0000312}
Chris Lattner1c809c52004-02-29 00:27:00 +0000313
314void V8ISel::visitReturnInst(ReturnInst &I) {
Brian Gaeke08f64c32004-03-06 05:32:28 +0000315 if (I.getNumOperands () == 1) {
316 unsigned RetValReg = getReg (I.getOperand (0));
317 switch (getClass (I.getOperand (0)->getType ())) {
318 case cByte:
319 case cShort:
320 case cInt:
321 // Schlep it over into i0 (where it will become o0 after restore).
322 BuildMI (BB, V8::ORrr, 2, V8::I0).addReg(V8::G0).addReg(RetValReg);
323 break;
324 default:
325 visitInstruction (I);
326 return;
327 }
Chris Lattner1c809c52004-02-29 00:27:00 +0000328 }
Chris Lattner0d538bb2004-04-07 04:36:53 +0000329
Brian Gaeke08f64c32004-03-06 05:32:28 +0000330 // Just emit a 'retl' instruction to return.
331 BuildMI(BB, V8::RETL, 0);
332 return;
Chris Lattner1c809c52004-02-29 00:27:00 +0000333}
334
Chris Lattner4be7ca52004-04-07 04:27:16 +0000335void V8ISel::visitBinaryOperator (Instruction &I) {
Brian Gaekebc1d27a2004-03-03 23:03:14 +0000336 unsigned DestReg = getReg (I);
337 unsigned Op0Reg = getReg (I.getOperand (0));
338 unsigned Op1Reg = getReg (I.getOperand (1));
339
Chris Lattner0d538bb2004-04-07 04:36:53 +0000340 unsigned ResultReg = DestReg;
341 if (getClassB(I.getType()) != cInt)
342 ResultReg = makeAnotherReg (I.getType ());
Chris Lattner22ede702004-04-07 04:06:46 +0000343 unsigned OpCase = ~0;
344
Brian Gaeke2d4fa8f2004-04-07 04:00:49 +0000345 // FIXME: support long, ulong, fp.
Brian Gaekebc1d27a2004-03-03 23:03:14 +0000346 switch (I.getOpcode ()) {
Chris Lattner22ede702004-04-07 04:06:46 +0000347 case Instruction::Add: OpCase = 0; break;
348 case Instruction::Sub: OpCase = 1; break;
349 case Instruction::Mul: OpCase = 2; break;
350 case Instruction::And: OpCase = 3; break;
351 case Instruction::Or: OpCase = 4; break;
352 case Instruction::Xor: OpCase = 5; break;
Chris Lattner4be7ca52004-04-07 04:27:16 +0000353 case Instruction::Shl: OpCase = 6; break;
354 case Instruction::Shr: OpCase = 7+I.getType()->isSigned(); break;
Chris Lattner22ede702004-04-07 04:06:46 +0000355
356 case Instruction::Div:
357 case Instruction::Rem: {
358 unsigned Dest = ResultReg;
359 if (I.getOpcode() == Instruction::Rem)
360 Dest = makeAnotherReg(I.getType());
361
362 // FIXME: this is probably only right for 32 bit operands.
363 if (I.getType ()->isSigned()) {
364 unsigned Tmp = makeAnotherReg (I.getType ());
365 // Sign extend into the Y register
366 BuildMI (BB, V8::SRAri, 2, Tmp).addReg (Op0Reg).addZImm (31);
367 BuildMI (BB, V8::WRrr, 2, V8::Y).addReg (Tmp).addReg (V8::G0);
368 BuildMI (BB, V8::SDIVrr, 2, Dest).addReg (Op0Reg).addReg (Op1Reg);
369 } else {
370 // Zero extend into the Y register, ie, just set it to zero
371 BuildMI (BB, V8::WRrr, 2, V8::Y).addReg (V8::G0).addReg (V8::G0);
372 BuildMI (BB, V8::UDIVrr, 2, Dest).addReg (Op0Reg).addReg (Op1Reg);
Brian Gaeke2d4fa8f2004-04-07 04:00:49 +0000373 }
Chris Lattner22ede702004-04-07 04:06:46 +0000374
375 if (I.getOpcode() == Instruction::Rem) {
376 unsigned Tmp = makeAnotherReg (I.getType ());
377 BuildMI (BB, V8::SMULrr, 2, Tmp).addReg(Dest).addReg(Op1Reg);
378 BuildMI (BB, V8::SUBrr, 2, ResultReg).addReg(Op0Reg).addReg(Tmp);
Brian Gaekef57e3642004-03-16 22:37:11 +0000379 }
Chris Lattner22ede702004-04-07 04:06:46 +0000380 break;
381 }
382 default:
383 visitInstruction (I);
384 return;
385 }
386
387 if (OpCase != ~0U) {
388 static const unsigned Opcodes[] = {
Chris Lattner4be7ca52004-04-07 04:27:16 +0000389 V8::ADDrr, V8::SUBrr, V8::SMULrr, V8::ANDrr, V8::ORrr, V8::XORrr,
390 V8::SLLrr, V8::SRLrr, V8::SRArr
Chris Lattner22ede702004-04-07 04:06:46 +0000391 };
392 BuildMI (BB, Opcodes[OpCase], 2, ResultReg).addReg (Op0Reg).addReg (Op1Reg);
Brian Gaekebc1d27a2004-03-03 23:03:14 +0000393 }
394
395 switch (getClass (I.getType ())) {
396 case cByte:
Brian Gaeke08f64c32004-03-06 05:32:28 +0000397 if (I.getType ()->isSigned ()) { // add byte
398 BuildMI (BB, V8::ANDri, 2, DestReg).addReg (ResultReg).addZImm (0xff);
399 } else { // add ubyte
400 unsigned TmpReg = makeAnotherReg (I.getType ());
401 BuildMI (BB, V8::SLLri, 2, TmpReg).addReg (ResultReg).addZImm (24);
402 BuildMI (BB, V8::SRAri, 2, DestReg).addReg (TmpReg).addZImm (24);
403 }
Brian Gaekebc1d27a2004-03-03 23:03:14 +0000404 break;
405 case cShort:
Brian Gaeke08f64c32004-03-06 05:32:28 +0000406 if (I.getType ()->isSigned ()) { // add short
407 unsigned TmpReg = makeAnotherReg (I.getType ());
408 BuildMI (BB, V8::SLLri, 2, TmpReg).addReg (ResultReg).addZImm (16);
409 BuildMI (BB, V8::SRAri, 2, DestReg).addReg (TmpReg).addZImm (16);
410 } else { // add ushort
411 unsigned TmpReg = makeAnotherReg (I.getType ());
Brian Gaeke6d339f92004-03-16 22:45:42 +0000412 BuildMI (BB, V8::SLLri, 2, TmpReg).addReg (ResultReg).addZImm (16);
413 BuildMI (BB, V8::SRLri, 2, DestReg).addReg (TmpReg).addZImm (16);
Brian Gaeke08f64c32004-03-06 05:32:28 +0000414 }
Brian Gaekebc1d27a2004-03-03 23:03:14 +0000415 break;
416 case cInt:
Chris Lattner0d538bb2004-04-07 04:36:53 +0000417 // Nothing todo here.
Brian Gaekebc1d27a2004-03-03 23:03:14 +0000418 break;
419 default:
Brian Gaeke08f64c32004-03-06 05:32:28 +0000420 visitInstruction (I);
Brian Gaekebc1d27a2004-03-03 23:03:14 +0000421 return;
422 }
423}
424
Chris Lattner4d0cda42004-04-07 05:04:51 +0000425void V8ISel::visitSetCondInst(Instruction &I) {
426 unsigned Op0Reg = getReg (I.getOperand (0));
427 unsigned Op1Reg = getReg (I.getOperand (1));
428 unsigned DestReg = getReg (I);
429
430 // Compare the two values.
431 BuildMI(BB, V8::SUBCCrr, 2, V8::G0).addReg(Op0Reg).addReg(Op1Reg);
432
433 // Put 0 into a register.
434 //unsigned ZeroReg = makeAnotheRReg(Type::IntTy);
435 //BuildMI(BB, V8::ORri, 2, ZeroReg).addReg(V8::G0).addReg(V8::G0);
436
437 unsigned Opcode;
438 switch (I.getOpcode()) {
439 default: assert(0 && "Unknown setcc instruction!");
440 case Instruction::SetEQ:
441 case Instruction::SetNE:
442 case Instruction::SetLT:
443 case Instruction::SetGT:
444 case Instruction::SetLE:
445 case Instruction::SetGE:
Brian Gaeked54c38b2004-04-07 16:41:22 +0000446 ;
Chris Lattner4d0cda42004-04-07 05:04:51 +0000447 }
448
449 // FIXME: We need either conditional moves like the V9 has (e.g. movge), or we
450 // need to be able to turn a single LLVM basic block into multiple machine
451 // code basic blocks. For now, it probably makes sense to emit Sparc V9
452 // instructions until the code generator is upgraded. Note that this should
453 // only happen when the setcc cannot be folded into the branch, but this needs
454 // to be handled correctly!
455
456 visitInstruction(I);
457}
458
459
Chris Lattner1c809c52004-02-29 00:27:00 +0000460
461/// LowerUnknownIntrinsicFunctionCalls - This performs a prepass over the
462/// function, lowering any calls to unknown intrinsic functions into the
463/// equivalent LLVM code.
464void V8ISel::LowerUnknownIntrinsicFunctionCalls(Function &F) {
465 for (Function::iterator BB = F.begin(), E = F.end(); BB != E; ++BB)
466 for (BasicBlock::iterator I = BB->begin(), E = BB->end(); I != E; )
467 if (CallInst *CI = dyn_cast<CallInst>(I++))
468 if (Function *F = CI->getCalledFunction())
469 switch (F->getIntrinsicID()) {
470 case Intrinsic::not_intrinsic: break;
471 default:
472 // All other intrinsic calls we must lower.
473 Instruction *Before = CI->getPrev();
474 TM.getIntrinsicLowering().LowerIntrinsicCall(CI);
475 if (Before) { // Move iterator to instruction after call
476 I = Before; ++I;
477 } else {
478 I = BB->begin();
479 }
480 }
481}
482
483
484void V8ISel::visitIntrinsicCall(Intrinsic::ID ID, CallInst &CI) {
485 unsigned TmpReg1, TmpReg2;
486 switch (ID) {
487 default: assert(0 && "Intrinsic not supported!");
488 }
489}