blob: 3eaae8eacc530b26675e24cc61cd35e8ae029db9 [file] [log] [blame]
Chris Lattner466a0492002-05-21 20:50:24 +00001//===- SimplifyCFG.cpp - Code to perform CFG simplification ---------------===//
Misha Brukmanb1c93172005-04-21 23:48:37 +00002//
John Criswell482202a2003-10-20 19:43:21 +00003// 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.
Misha Brukmanb1c93172005-04-21 23:48:37 +00007//
John Criswell482202a2003-10-20 19:43:21 +00008//===----------------------------------------------------------------------===//
Chris Lattner466a0492002-05-21 20:50:24 +00009//
Chris Lattnera704ac82002-10-08 21:36:33 +000010// Peephole optimize the CFG.
Chris Lattner466a0492002-05-21 20:50:24 +000011//
12//===----------------------------------------------------------------------===//
13
Chris Lattner9734fd02004-06-20 01:13:18 +000014#define DEBUG_TYPE "simplifycfg"
Chris Lattner466a0492002-05-21 20:50:24 +000015#include "llvm/Transforms/Utils/Local.h"
Chris Lattner18d1f192004-02-11 03:36:04 +000016#include "llvm/Constants.h"
17#include "llvm/Instructions.h"
Chris Lattner6f4b45a2004-02-24 05:38:11 +000018#include "llvm/Type.h"
Chris Lattner466a0492002-05-21 20:50:24 +000019#include "llvm/Support/CFG.h"
Reid Spencer7c16caa2004-09-01 22:55:40 +000020#include "llvm/Support/Debug.h"
Chris Lattner466a0492002-05-21 20:50:24 +000021#include <algorithm>
22#include <functional>
Chris Lattnera2ab4892004-02-24 07:23:58 +000023#include <set>
Chris Lattner5edb2f32004-10-18 04:07:22 +000024#include <map>
Chris Lattnerdf3c3422004-01-09 06:12:26 +000025using namespace llvm;
Brian Gaeke960707c2003-11-11 22:41:34 +000026
Chris Lattner76dc2042005-08-03 00:19:45 +000027/// SafeToMergeTerminators - Return true if it is safe to merge these two
28/// terminator instructions together.
29///
30static bool SafeToMergeTerminators(TerminatorInst *SI1, TerminatorInst *SI2) {
31 if (SI1 == SI2) return false; // Can't merge with self!
32
33 // It is not safe to merge these two switch instructions if they have a common
34 // successor, and if that successor has a PHI node, and if *that* PHI node has
35 // conflicting incoming values from the two switch blocks.
36 BasicBlock *SI1BB = SI1->getParent();
37 BasicBlock *SI2BB = SI2->getParent();
38 std::set<BasicBlock*> SI1Succs(succ_begin(SI1BB), succ_end(SI1BB));
39
40 for (succ_iterator I = succ_begin(SI2BB), E = succ_end(SI2BB); I != E; ++I)
41 if (SI1Succs.count(*I))
42 for (BasicBlock::iterator BBI = (*I)->begin();
43 isa<PHINode>(BBI); ++BBI) {
44 PHINode *PN = cast<PHINode>(BBI);
45 if (PN->getIncomingValueForBlock(SI1BB) !=
46 PN->getIncomingValueForBlock(SI2BB))
47 return false;
48 }
49
50 return true;
51}
52
53/// AddPredecessorToBlock - Update PHI nodes in Succ to indicate that there will
54/// now be entries in it from the 'NewPred' block. The values that will be
55/// flowing into the PHI nodes will be the same as those coming in from
56/// ExistPred, an existing predecessor of Succ.
57static void AddPredecessorToBlock(BasicBlock *Succ, BasicBlock *NewPred,
58 BasicBlock *ExistPred) {
59 assert(std::find(succ_begin(ExistPred), succ_end(ExistPred), Succ) !=
60 succ_end(ExistPred) && "ExistPred is not a predecessor of Succ!");
61 if (!isa<PHINode>(Succ->begin())) return; // Quick exit if nothing to do
62
63 for (BasicBlock::iterator I = Succ->begin(); isa<PHINode>(I); ++I) {
64 PHINode *PN = cast<PHINode>(I);
65 Value *V = PN->getIncomingValueForBlock(ExistPred);
66 PN->addIncoming(V, NewPred);
67 }
68}
69
Chris Lattner6f4b45a2004-02-24 05:38:11 +000070// PropagatePredecessorsForPHIs - This gets "Succ" ready to have the
71// predecessors from "BB". This is a little tricky because "Succ" has PHI
72// nodes, which need to have extra slots added to them to hold the merge edges
73// from BB's predecessors, and BB itself might have had PHI nodes in it. This
74// function returns true (failure) if the Succ BB already has a predecessor that
75// is a predecessor of BB and incoming PHI arguments would not be discernible.
Chris Lattner466a0492002-05-21 20:50:24 +000076//
77// Assumption: Succ is the single successor for BB.
78//
Misha Brukman632df282002-10-29 23:06:16 +000079static bool PropagatePredecessorsForPHIs(BasicBlock *BB, BasicBlock *Succ) {
Chris Lattner466a0492002-05-21 20:50:24 +000080 assert(*succ_begin(BB) == Succ && "Succ is not successor of BB!");
Chris Lattner5325c5f2002-09-24 00:09:26 +000081
82 if (!isa<PHINode>(Succ->front()))
83 return false; // We can make the transformation, no problem.
Chris Lattner466a0492002-05-21 20:50:24 +000084
85 // If there is more than one predecessor, and there are PHI nodes in
86 // the successor, then we need to add incoming edges for the PHI nodes
87 //
88 const std::vector<BasicBlock*> BBPreds(pred_begin(BB), pred_end(BB));
89
90 // Check to see if one of the predecessors of BB is already a predecessor of
Chris Lattner31116ba2003-03-05 21:01:52 +000091 // Succ. If so, we cannot do the transformation if there are any PHI nodes
92 // with incompatible values coming in from the two edges!
Chris Lattner466a0492002-05-21 20:50:24 +000093 //
Chris Lattner76dc2042005-08-03 00:19:45 +000094 if (!SafeToMergeTerminators(BB->getTerminator(), Succ->getTerminator()))
95 return true; // Cannot merge.
Chris Lattner466a0492002-05-21 20:50:24 +000096
Chris Lattner9734fd02004-06-20 01:13:18 +000097 // Loop over all of the PHI nodes in the successor BB.
Reid Spencer66149462004-09-15 17:06:42 +000098 for (BasicBlock::iterator I = Succ->begin(); isa<PHINode>(I); ++I) {
99 PHINode *PN = cast<PHINode>(I);
Chris Lattnera704ac82002-10-08 21:36:33 +0000100 Value *OldVal = PN->removeIncomingValue(BB, false);
Chris Lattner466a0492002-05-21 20:50:24 +0000101 assert(OldVal && "No entry in PHI for Pred BB!");
102
Chris Lattner9734fd02004-06-20 01:13:18 +0000103 // If this incoming value is one of the PHI nodes in BB, the new entries in
104 // the PHI node are the entries from the old PHI.
Chris Lattnere54d2142003-03-05 21:36:33 +0000105 if (isa<PHINode>(OldVal) && cast<PHINode>(OldVal)->getParent() == BB) {
106 PHINode *OldValPN = cast<PHINode>(OldVal);
Chris Lattner9734fd02004-06-20 01:13:18 +0000107 for (unsigned i = 0, e = OldValPN->getNumIncomingValues(); i != e; ++i)
108 PN->addIncoming(OldValPN->getIncomingValue(i),
109 OldValPN->getIncomingBlock(i));
Chris Lattnere54d2142003-03-05 21:36:33 +0000110 } else {
Misha Brukmanb1c93172005-04-21 23:48:37 +0000111 for (std::vector<BasicBlock*>::const_iterator PredI = BBPreds.begin(),
Chris Lattnere54d2142003-03-05 21:36:33 +0000112 End = BBPreds.end(); PredI != End; ++PredI) {
113 // Add an incoming value for each of the new incoming values...
114 PN->addIncoming(OldVal, *PredI);
115 }
Chris Lattner466a0492002-05-21 20:50:24 +0000116 }
117 }
118 return false;
119}
120
Chris Lattner733d6702005-08-03 00:11:16 +0000121/// TryToSimplifyUncondBranchFromEmptyBlock - BB contains an unconditional
122/// branch to Succ, and contains no instructions other than PHI nodes and the
123/// branch. If possible, eliminate BB.
124static bool TryToSimplifyUncondBranchFromEmptyBlock(BasicBlock *BB,
125 BasicBlock *Succ) {
126 // If our successor has PHI nodes, then we need to update them to include
127 // entries for BB's predecessors, not for BB itself. Be careful though,
128 // if this transformation fails (returns true) then we cannot do this
129 // transformation!
130 //
131 if (PropagatePredecessorsForPHIs(BB, Succ)) return false;
132
133 DEBUG(std::cerr << "Killing Trivial BB: \n" << *BB);
134
135 if (isa<PHINode>(&BB->front())) {
136 std::vector<BasicBlock*>
137 OldSuccPreds(pred_begin(Succ), pred_end(Succ));
138
139 // Move all PHI nodes in BB to Succ if they are alive, otherwise
140 // delete them.
141 while (PHINode *PN = dyn_cast<PHINode>(&BB->front()))
142 if (PN->use_empty() /*|| Succ->getSinglePredecessor() == 0*/) {
143 // We can only move the PHI node into Succ if BB dominates Succ.
144 // Since BB only has a single successor (Succ), the PHI nodes
145 // will dominate Succ, unless Succ has multiple predecessors. In
146 // this case, the PHIs are either dead, or have references in dead
147 // blocks. In either case, we can just remove them.
148 if (!PN->use_empty()) // Uses in dead block?
149 PN->replaceAllUsesWith(UndefValue::get(PN->getType()));
150 PN->eraseFromParent(); // Nuke instruction.
151 } else {
152 // The instruction is alive, so this means that Succ must have
153 // *ONLY* had BB as a predecessor, and the PHI node is still valid
154 // now. Simply move it into Succ, because we know that BB
155 // strictly dominated Succ.
Chris Lattner1f047fd2005-08-03 00:23:42 +0000156 Succ->getInstList().splice(Succ->begin(),
157 BB->getInstList(), BB->begin());
Chris Lattner733d6702005-08-03 00:11:16 +0000158
159 // We need to add new entries for the PHI node to account for
160 // predecessors of Succ that the PHI node does not take into
161 // account. At this point, since we know that BB dominated succ,
162 // this means that we should any newly added incoming edges should
163 // use the PHI node as the value for these edges, because they are
164 // loop back edges.
165 for (unsigned i = 0, e = OldSuccPreds.size(); i != e; ++i)
166 if (OldSuccPreds[i] != BB)
167 PN->addIncoming(PN, OldSuccPreds[i]);
168 }
169 }
170
171 // Everything that jumped to BB now goes to Succ.
172 std::string OldName = BB->getName();
173 BB->replaceAllUsesWith(Succ);
174 BB->eraseFromParent(); // Delete the old basic block.
175
176 if (!OldName.empty() && !Succ->hasName()) // Transfer name if we can
177 Succ->setName(OldName);
178 return true;
179}
180
Chris Lattner18d1f192004-02-11 03:36:04 +0000181/// GetIfCondition - Given a basic block (BB) with two predecessors (and
182/// presumably PHI nodes in it), check to see if the merge at this block is due
183/// to an "if condition". If so, return the boolean condition that determines
184/// which entry into BB will be taken. Also, return by references the block
185/// that will be entered from if the condition is true, and the block that will
186/// be entered if the condition is false.
Misha Brukmanb1c93172005-04-21 23:48:37 +0000187///
Chris Lattner18d1f192004-02-11 03:36:04 +0000188///
189static Value *GetIfCondition(BasicBlock *BB,
190 BasicBlock *&IfTrue, BasicBlock *&IfFalse) {
191 assert(std::distance(pred_begin(BB), pred_end(BB)) == 2 &&
192 "Function can only handle blocks with 2 predecessors!");
193 BasicBlock *Pred1 = *pred_begin(BB);
194 BasicBlock *Pred2 = *++pred_begin(BB);
195
196 // We can only handle branches. Other control flow will be lowered to
197 // branches if possible anyway.
198 if (!isa<BranchInst>(Pred1->getTerminator()) ||
199 !isa<BranchInst>(Pred2->getTerminator()))
200 return 0;
201 BranchInst *Pred1Br = cast<BranchInst>(Pred1->getTerminator());
202 BranchInst *Pred2Br = cast<BranchInst>(Pred2->getTerminator());
203
204 // Eliminate code duplication by ensuring that Pred1Br is conditional if
205 // either are.
206 if (Pred2Br->isConditional()) {
207 // If both branches are conditional, we don't have an "if statement". In
208 // reality, we could transform this case, but since the condition will be
209 // required anyway, we stand no chance of eliminating it, so the xform is
210 // probably not profitable.
211 if (Pred1Br->isConditional())
212 return 0;
213
214 std::swap(Pred1, Pred2);
215 std::swap(Pred1Br, Pred2Br);
216 }
217
218 if (Pred1Br->isConditional()) {
219 // If we found a conditional branch predecessor, make sure that it branches
220 // to BB and Pred2Br. If it doesn't, this isn't an "if statement".
221 if (Pred1Br->getSuccessor(0) == BB &&
222 Pred1Br->getSuccessor(1) == Pred2) {
223 IfTrue = Pred1;
224 IfFalse = Pred2;
225 } else if (Pred1Br->getSuccessor(0) == Pred2 &&
226 Pred1Br->getSuccessor(1) == BB) {
227 IfTrue = Pred2;
228 IfFalse = Pred1;
229 } else {
230 // We know that one arm of the conditional goes to BB, so the other must
231 // go somewhere unrelated, and this must not be an "if statement".
232 return 0;
233 }
234
235 // The only thing we have to watch out for here is to make sure that Pred2
236 // doesn't have incoming edges from other blocks. If it does, the condition
237 // doesn't dominate BB.
238 if (++pred_begin(Pred2) != pred_end(Pred2))
239 return 0;
240
241 return Pred1Br->getCondition();
242 }
243
244 // Ok, if we got here, both predecessors end with an unconditional branch to
245 // BB. Don't panic! If both blocks only have a single (identical)
246 // predecessor, and THAT is a conditional branch, then we're all ok!
247 if (pred_begin(Pred1) == pred_end(Pred1) ||
248 ++pred_begin(Pred1) != pred_end(Pred1) ||
249 pred_begin(Pred2) == pred_end(Pred2) ||
250 ++pred_begin(Pred2) != pred_end(Pred2) ||
251 *pred_begin(Pred1) != *pred_begin(Pred2))
252 return 0;
253
254 // Otherwise, if this is a conditional branch, then we can use it!
255 BasicBlock *CommonPred = *pred_begin(Pred1);
256 if (BranchInst *BI = dyn_cast<BranchInst>(CommonPred->getTerminator())) {
257 assert(BI->isConditional() && "Two successors but not conditional?");
258 if (BI->getSuccessor(0) == Pred1) {
259 IfTrue = Pred1;
260 IfFalse = Pred2;
261 } else {
262 IfTrue = Pred2;
263 IfFalse = Pred1;
264 }
265 return BI->getCondition();
266 }
267 return 0;
268}
269
270
271// If we have a merge point of an "if condition" as accepted above, return true
272// if the specified value dominates the block. We don't handle the true
273// generality of domination here, just a special case which works well enough
274// for us.
Chris Lattner45c35b12004-10-14 05:13:36 +0000275//
276// If AggressiveInsts is non-null, and if V does not dominate BB, we check to
277// see if V (which must be an instruction) is cheap to compute and is
278// non-trapping. If both are true, the instruction is inserted into the set and
279// true is returned.
280static bool DominatesMergePoint(Value *V, BasicBlock *BB,
281 std::set<Instruction*> *AggressiveInsts) {
Chris Lattner0aa56562004-04-09 22:50:22 +0000282 Instruction *I = dyn_cast<Instruction>(V);
283 if (!I) return true; // Non-instructions all dominate instructions.
284 BasicBlock *PBB = I->getParent();
Chris Lattner18d1f192004-02-11 03:36:04 +0000285
Chris Lattner0ce80cd2005-02-27 06:18:25 +0000286 // We don't want to allow weird loops that might have the "if condition" in
Chris Lattner0aa56562004-04-09 22:50:22 +0000287 // the bottom of this block.
288 if (PBB == BB) return false;
Chris Lattner18d1f192004-02-11 03:36:04 +0000289
Chris Lattner0aa56562004-04-09 22:50:22 +0000290 // If this instruction is defined in a block that contains an unconditional
291 // branch to BB, then it must be in the 'conditional' part of the "if
292 // statement".
293 if (BranchInst *BI = dyn_cast<BranchInst>(PBB->getTerminator()))
294 if (BI->isUnconditional() && BI->getSuccessor(0) == BB) {
Chris Lattner45c35b12004-10-14 05:13:36 +0000295 if (!AggressiveInsts) return false;
Chris Lattner0aa56562004-04-09 22:50:22 +0000296 // Okay, it looks like the instruction IS in the "condition". Check to
297 // see if its a cheap instruction to unconditionally compute, and if it
298 // only uses stuff defined outside of the condition. If so, hoist it out.
299 switch (I->getOpcode()) {
300 default: return false; // Cannot hoist this out safely.
301 case Instruction::Load:
302 // We can hoist loads that are non-volatile and obviously cannot trap.
303 if (cast<LoadInst>(I)->isVolatile())
304 return false;
305 if (!isa<AllocaInst>(I->getOperand(0)) &&
Reid Spenceref784f02004-07-18 00:32:14 +0000306 !isa<Constant>(I->getOperand(0)))
Chris Lattner0aa56562004-04-09 22:50:22 +0000307 return false;
308
309 // Finally, we have to check to make sure there are no instructions
310 // before the load in its basic block, as we are going to hoist the loop
311 // out to its predecessor.
312 if (PBB->begin() != BasicBlock::iterator(I))
313 return false;
314 break;
315 case Instruction::Add:
316 case Instruction::Sub:
317 case Instruction::And:
318 case Instruction::Or:
319 case Instruction::Xor:
320 case Instruction::Shl:
321 case Instruction::Shr:
Chris Lattnerb38b4432005-04-21 05:31:13 +0000322 case Instruction::SetEQ:
323 case Instruction::SetNE:
324 case Instruction::SetLT:
325 case Instruction::SetGT:
326 case Instruction::SetLE:
327 case Instruction::SetGE:
Chris Lattner0aa56562004-04-09 22:50:22 +0000328 break; // These are all cheap and non-trapping instructions.
329 }
Misha Brukmanb1c93172005-04-21 23:48:37 +0000330
Chris Lattner0aa56562004-04-09 22:50:22 +0000331 // Okay, we can only really hoist these out if their operands are not
332 // defined in the conditional region.
333 for (unsigned i = 0, e = I->getNumOperands(); i != e; ++i)
Chris Lattner45c35b12004-10-14 05:13:36 +0000334 if (!DominatesMergePoint(I->getOperand(i), BB, 0))
Chris Lattner0aa56562004-04-09 22:50:22 +0000335 return false;
Chris Lattner45c35b12004-10-14 05:13:36 +0000336 // Okay, it's safe to do this! Remember this instruction.
337 AggressiveInsts->insert(I);
Chris Lattner0aa56562004-04-09 22:50:22 +0000338 }
339
Chris Lattner18d1f192004-02-11 03:36:04 +0000340 return true;
341}
Chris Lattner466a0492002-05-21 20:50:24 +0000342
Chris Lattner6f4b45a2004-02-24 05:38:11 +0000343// GatherConstantSetEQs - Given a potentially 'or'd together collection of seteq
344// instructions that compare a value against a constant, return the value being
345// compared, and stick the constant into the Values vector.
Chris Lattnerb2b151d2004-06-19 07:02:14 +0000346static Value *GatherConstantSetEQs(Value *V, std::vector<ConstantInt*> &Values){
Chris Lattner6f4b45a2004-02-24 05:38:11 +0000347 if (Instruction *Inst = dyn_cast<Instruction>(V))
348 if (Inst->getOpcode() == Instruction::SetEQ) {
Chris Lattnerb2b151d2004-06-19 07:02:14 +0000349 if (ConstantInt *C = dyn_cast<ConstantInt>(Inst->getOperand(1))) {
Chris Lattner6f4b45a2004-02-24 05:38:11 +0000350 Values.push_back(C);
351 return Inst->getOperand(0);
Chris Lattnerb2b151d2004-06-19 07:02:14 +0000352 } else if (ConstantInt *C = dyn_cast<ConstantInt>(Inst->getOperand(0))) {
Chris Lattner6f4b45a2004-02-24 05:38:11 +0000353 Values.push_back(C);
354 return Inst->getOperand(1);
355 }
356 } else if (Inst->getOpcode() == Instruction::Or) {
357 if (Value *LHS = GatherConstantSetEQs(Inst->getOperand(0), Values))
358 if (Value *RHS = GatherConstantSetEQs(Inst->getOperand(1), Values))
359 if (LHS == RHS)
360 return LHS;
361 }
362 return 0;
363}
364
365// GatherConstantSetNEs - Given a potentially 'and'd together collection of
366// setne instructions that compare a value against a constant, return the value
367// being compared, and stick the constant into the Values vector.
Chris Lattnerb2b151d2004-06-19 07:02:14 +0000368static Value *GatherConstantSetNEs(Value *V, std::vector<ConstantInt*> &Values){
Chris Lattner6f4b45a2004-02-24 05:38:11 +0000369 if (Instruction *Inst = dyn_cast<Instruction>(V))
370 if (Inst->getOpcode() == Instruction::SetNE) {
Chris Lattnerb2b151d2004-06-19 07:02:14 +0000371 if (ConstantInt *C = dyn_cast<ConstantInt>(Inst->getOperand(1))) {
Chris Lattner6f4b45a2004-02-24 05:38:11 +0000372 Values.push_back(C);
373 return Inst->getOperand(0);
Chris Lattnerb2b151d2004-06-19 07:02:14 +0000374 } else if (ConstantInt *C = dyn_cast<ConstantInt>(Inst->getOperand(0))) {
Chris Lattner6f4b45a2004-02-24 05:38:11 +0000375 Values.push_back(C);
376 return Inst->getOperand(1);
377 }
378 } else if (Inst->getOpcode() == Instruction::Cast) {
379 // Cast of X to bool is really a comparison against zero.
380 assert(Inst->getType() == Type::BoolTy && "Can only handle bool values!");
Chris Lattnerb2b151d2004-06-19 07:02:14 +0000381 Values.push_back(ConstantInt::get(Inst->getOperand(0)->getType(), 0));
Chris Lattner6f4b45a2004-02-24 05:38:11 +0000382 return Inst->getOperand(0);
383 } else if (Inst->getOpcode() == Instruction::And) {
384 if (Value *LHS = GatherConstantSetNEs(Inst->getOperand(0), Values))
385 if (Value *RHS = GatherConstantSetNEs(Inst->getOperand(1), Values))
386 if (LHS == RHS)
387 return LHS;
388 }
389 return 0;
390}
391
392
393
394/// GatherValueComparisons - If the specified Cond is an 'and' or 'or' of a
395/// bunch of comparisons of one value against constants, return the value and
396/// the constants being compared.
397static bool GatherValueComparisons(Instruction *Cond, Value *&CompVal,
Chris Lattnerb2b151d2004-06-19 07:02:14 +0000398 std::vector<ConstantInt*> &Values) {
Chris Lattner6f4b45a2004-02-24 05:38:11 +0000399 if (Cond->getOpcode() == Instruction::Or) {
400 CompVal = GatherConstantSetEQs(Cond, Values);
401
402 // Return true to indicate that the condition is true if the CompVal is
403 // equal to one of the constants.
404 return true;
405 } else if (Cond->getOpcode() == Instruction::And) {
406 CompVal = GatherConstantSetNEs(Cond, Values);
Misha Brukmanb1c93172005-04-21 23:48:37 +0000407
Chris Lattner6f4b45a2004-02-24 05:38:11 +0000408 // Return false to indicate that the condition is false if the CompVal is
409 // equal to one of the constants.
410 return false;
411 }
412 return false;
413}
414
415/// ErasePossiblyDeadInstructionTree - If the specified instruction is dead and
416/// has no side effects, nuke it. If it uses any instructions that become dead
417/// because the instruction is now gone, nuke them too.
418static void ErasePossiblyDeadInstructionTree(Instruction *I) {
419 if (isInstructionTriviallyDead(I)) {
420 std::vector<Value*> Operands(I->op_begin(), I->op_end());
421 I->getParent()->getInstList().erase(I);
422 for (unsigned i = 0, e = Operands.size(); i != e; ++i)
423 if (Instruction *OpI = dyn_cast<Instruction>(Operands[i]))
424 ErasePossiblyDeadInstructionTree(OpI);
425 }
426}
427
Chris Lattnerd3e6ae22004-02-28 21:28:10 +0000428// isValueEqualityComparison - Return true if the specified terminator checks to
429// see if a value is equal to constant integer value.
430static Value *isValueEqualityComparison(TerminatorInst *TI) {
Chris Lattnera64923a2004-03-16 19:45:22 +0000431 if (SwitchInst *SI = dyn_cast<SwitchInst>(TI)) {
432 // Do not permit merging of large switch instructions into their
433 // predecessors unless there is only one predecessor.
434 if (SI->getNumSuccessors() * std::distance(pred_begin(SI->getParent()),
435 pred_end(SI->getParent())) > 128)
436 return 0;
437
Chris Lattnerd3e6ae22004-02-28 21:28:10 +0000438 return SI->getCondition();
Chris Lattnera64923a2004-03-16 19:45:22 +0000439 }
Chris Lattnerd3e6ae22004-02-28 21:28:10 +0000440 if (BranchInst *BI = dyn_cast<BranchInst>(TI))
441 if (BI->isConditional() && BI->getCondition()->hasOneUse())
442 if (SetCondInst *SCI = dyn_cast<SetCondInst>(BI->getCondition()))
443 if ((SCI->getOpcode() == Instruction::SetEQ ||
Misha Brukmanb1c93172005-04-21 23:48:37 +0000444 SCI->getOpcode() == Instruction::SetNE) &&
Chris Lattnerd3e6ae22004-02-28 21:28:10 +0000445 isa<ConstantInt>(SCI->getOperand(1)))
446 return SCI->getOperand(0);
447 return 0;
448}
449
450// Given a value comparison instruction, decode all of the 'cases' that it
451// represents and return the 'default' block.
452static BasicBlock *
Misha Brukmanb1c93172005-04-21 23:48:37 +0000453GetValueEqualityComparisonCases(TerminatorInst *TI,
Chris Lattnerd3e6ae22004-02-28 21:28:10 +0000454 std::vector<std::pair<ConstantInt*,
455 BasicBlock*> > &Cases) {
456 if (SwitchInst *SI = dyn_cast<SwitchInst>(TI)) {
457 Cases.reserve(SI->getNumCases());
458 for (unsigned i = 1, e = SI->getNumCases(); i != e; ++i)
Chris Lattnercc6d75f2005-02-26 18:33:28 +0000459 Cases.push_back(std::make_pair(SI->getCaseValue(i), SI->getSuccessor(i)));
Chris Lattnerd3e6ae22004-02-28 21:28:10 +0000460 return SI->getDefaultDest();
461 }
462
463 BranchInst *BI = cast<BranchInst>(TI);
464 SetCondInst *SCI = cast<SetCondInst>(BI->getCondition());
465 Cases.push_back(std::make_pair(cast<ConstantInt>(SCI->getOperand(1)),
466 BI->getSuccessor(SCI->getOpcode() ==
467 Instruction::SetNE)));
468 return BI->getSuccessor(SCI->getOpcode() == Instruction::SetEQ);
469}
470
471
Chris Lattner1cca9592005-02-24 06:17:52 +0000472// EliminateBlockCases - Given an vector of bb/value pairs, remove any entries
473// in the list that match the specified block.
Misha Brukmanb1c93172005-04-21 23:48:37 +0000474static void EliminateBlockCases(BasicBlock *BB,
Chris Lattner1cca9592005-02-24 06:17:52 +0000475 std::vector<std::pair<ConstantInt*, BasicBlock*> > &Cases) {
476 for (unsigned i = 0, e = Cases.size(); i != e; ++i)
477 if (Cases[i].second == BB) {
478 Cases.erase(Cases.begin()+i);
479 --i; --e;
480 }
481}
482
483// ValuesOverlap - Return true if there are any keys in C1 that exist in C2 as
484// well.
485static bool
486ValuesOverlap(std::vector<std::pair<ConstantInt*, BasicBlock*> > &C1,
487 std::vector<std::pair<ConstantInt*, BasicBlock*> > &C2) {
488 std::vector<std::pair<ConstantInt*, BasicBlock*> > *V1 = &C1, *V2 = &C2;
489
490 // Make V1 be smaller than V2.
491 if (V1->size() > V2->size())
492 std::swap(V1, V2);
493
494 if (V1->size() == 0) return false;
495 if (V1->size() == 1) {
496 // Just scan V2.
497 ConstantInt *TheVal = (*V1)[0].first;
498 for (unsigned i = 0, e = V2->size(); i != e; ++i)
499 if (TheVal == (*V2)[i].first)
500 return true;
501 }
502
503 // Otherwise, just sort both lists and compare element by element.
504 std::sort(V1->begin(), V1->end());
505 std::sort(V2->begin(), V2->end());
506 unsigned i1 = 0, i2 = 0, e1 = V1->size(), e2 = V2->size();
507 while (i1 != e1 && i2 != e2) {
508 if ((*V1)[i1].first == (*V2)[i2].first)
509 return true;
510 if ((*V1)[i1].first < (*V2)[i2].first)
511 ++i1;
512 else
513 ++i2;
514 }
515 return false;
516}
517
518// SimplifyEqualityComparisonWithOnlyPredecessor - If TI is known to be a
519// terminator instruction and its block is known to only have a single
520// predecessor block, check to see if that predecessor is also a value
521// comparison with the same value, and if that comparison determines the outcome
522// of this comparison. If so, simplify TI. This does a very limited form of
523// jump threading.
524static bool SimplifyEqualityComparisonWithOnlyPredecessor(TerminatorInst *TI,
525 BasicBlock *Pred) {
526 Value *PredVal = isValueEqualityComparison(Pred->getTerminator());
527 if (!PredVal) return false; // Not a value comparison in predecessor.
528
529 Value *ThisVal = isValueEqualityComparison(TI);
530 assert(ThisVal && "This isn't a value comparison!!");
531 if (ThisVal != PredVal) return false; // Different predicates.
532
533 // Find out information about when control will move from Pred to TI's block.
534 std::vector<std::pair<ConstantInt*, BasicBlock*> > PredCases;
535 BasicBlock *PredDef = GetValueEqualityComparisonCases(Pred->getTerminator(),
536 PredCases);
537 EliminateBlockCases(PredDef, PredCases); // Remove default from cases.
Misha Brukmanb1c93172005-04-21 23:48:37 +0000538
Chris Lattner1cca9592005-02-24 06:17:52 +0000539 // Find information about how control leaves this block.
540 std::vector<std::pair<ConstantInt*, BasicBlock*> > ThisCases;
541 BasicBlock *ThisDef = GetValueEqualityComparisonCases(TI, ThisCases);
542 EliminateBlockCases(ThisDef, ThisCases); // Remove default from cases.
543
544 // If TI's block is the default block from Pred's comparison, potentially
545 // simplify TI based on this knowledge.
546 if (PredDef == TI->getParent()) {
547 // If we are here, we know that the value is none of those cases listed in
548 // PredCases. If there are any cases in ThisCases that are in PredCases, we
549 // can simplify TI.
550 if (ValuesOverlap(PredCases, ThisCases)) {
551 if (BranchInst *BTI = dyn_cast<BranchInst>(TI)) {
552 // Okay, one of the successors of this condbr is dead. Convert it to a
553 // uncond br.
554 assert(ThisCases.size() == 1 && "Branch can only have one case!");
555 Value *Cond = BTI->getCondition();
556 // Insert the new branch.
557 Instruction *NI = new BranchInst(ThisDef, TI);
558
559 // Remove PHI node entries for the dead edge.
560 ThisCases[0].second->removePredecessor(TI->getParent());
561
562 DEBUG(std::cerr << "Threading pred instr: " << *Pred->getTerminator()
563 << "Through successor TI: " << *TI << "Leaving: " << *NI << "\n");
564
565 TI->eraseFromParent(); // Nuke the old one.
566 // If condition is now dead, nuke it.
567 if (Instruction *CondI = dyn_cast<Instruction>(Cond))
568 ErasePossiblyDeadInstructionTree(CondI);
569 return true;
570
571 } else {
572 SwitchInst *SI = cast<SwitchInst>(TI);
573 // Okay, TI has cases that are statically dead, prune them away.
574 std::set<Constant*> DeadCases;
575 for (unsigned i = 0, e = PredCases.size(); i != e; ++i)
576 DeadCases.insert(PredCases[i].first);
577
578 DEBUG(std::cerr << "Threading pred instr: " << *Pred->getTerminator()
579 << "Through successor TI: " << *TI);
580
581 for (unsigned i = SI->getNumCases()-1; i != 0; --i)
582 if (DeadCases.count(SI->getCaseValue(i))) {
583 SI->getSuccessor(i)->removePredecessor(TI->getParent());
584 SI->removeCase(i);
585 }
586
587 DEBUG(std::cerr << "Leaving: " << *TI << "\n");
588 return true;
589 }
590 }
591
592 } else {
593 // Otherwise, TI's block must correspond to some matched value. Find out
594 // which value (or set of values) this is.
595 ConstantInt *TIV = 0;
596 BasicBlock *TIBB = TI->getParent();
597 for (unsigned i = 0, e = PredCases.size(); i != e; ++i)
598 if (PredCases[i].second == TIBB)
599 if (TIV == 0)
600 TIV = PredCases[i].first;
601 else
602 return false; // Cannot handle multiple values coming to this block.
603 assert(TIV && "No edge from pred to succ?");
604
605 // Okay, we found the one constant that our value can be if we get into TI's
606 // BB. Find out which successor will unconditionally be branched to.
607 BasicBlock *TheRealDest = 0;
608 for (unsigned i = 0, e = ThisCases.size(); i != e; ++i)
609 if (ThisCases[i].first == TIV) {
610 TheRealDest = ThisCases[i].second;
611 break;
612 }
613
614 // If not handled by any explicit cases, it is handled by the default case.
615 if (TheRealDest == 0) TheRealDest = ThisDef;
616
617 // Remove PHI node entries for dead edges.
618 BasicBlock *CheckEdge = TheRealDest;
619 for (succ_iterator SI = succ_begin(TIBB), e = succ_end(TIBB); SI != e; ++SI)
620 if (*SI != CheckEdge)
621 (*SI)->removePredecessor(TIBB);
622 else
623 CheckEdge = 0;
624
625 // Insert the new branch.
626 Instruction *NI = new BranchInst(TheRealDest, TI);
627
628 DEBUG(std::cerr << "Threading pred instr: " << *Pred->getTerminator()
629 << "Through successor TI: " << *TI << "Leaving: " << *NI << "\n");
630 Instruction *Cond = 0;
631 if (BranchInst *BI = dyn_cast<BranchInst>(TI))
632 Cond = dyn_cast<Instruction>(BI->getCondition());
633 TI->eraseFromParent(); // Nuke the old one.
634
635 if (Cond) ErasePossiblyDeadInstructionTree(Cond);
636 return true;
637 }
638 return false;
639}
640
Chris Lattnerd3e6ae22004-02-28 21:28:10 +0000641// FoldValueComparisonIntoPredecessors - The specified terminator is a value
642// equality comparison instruction (either a switch or a branch on "X == c").
643// See if any of the predecessors of the terminator block are value comparisons
644// on the same value. If so, and if safe to do so, fold them together.
645static bool FoldValueComparisonIntoPredecessors(TerminatorInst *TI) {
646 BasicBlock *BB = TI->getParent();
647 Value *CV = isValueEqualityComparison(TI); // CondVal
648 assert(CV && "Not a comparison?");
649 bool Changed = false;
650
651 std::vector<BasicBlock*> Preds(pred_begin(BB), pred_end(BB));
652 while (!Preds.empty()) {
653 BasicBlock *Pred = Preds.back();
654 Preds.pop_back();
Misha Brukmanb1c93172005-04-21 23:48:37 +0000655
Chris Lattnerd3e6ae22004-02-28 21:28:10 +0000656 // See if the predecessor is a comparison with the same value.
657 TerminatorInst *PTI = Pred->getTerminator();
658 Value *PCV = isValueEqualityComparison(PTI); // PredCondVal
659
660 if (PCV == CV && SafeToMergeTerminators(TI, PTI)) {
661 // Figure out which 'cases' to copy from SI to PSI.
662 std::vector<std::pair<ConstantInt*, BasicBlock*> > BBCases;
663 BasicBlock *BBDefault = GetValueEqualityComparisonCases(TI, BBCases);
664
665 std::vector<std::pair<ConstantInt*, BasicBlock*> > PredCases;
666 BasicBlock *PredDefault = GetValueEqualityComparisonCases(PTI, PredCases);
667
668 // Based on whether the default edge from PTI goes to BB or not, fill in
669 // PredCases and PredDefault with the new switch cases we would like to
670 // build.
671 std::vector<BasicBlock*> NewSuccessors;
672
673 if (PredDefault == BB) {
674 // If this is the default destination from PTI, only the edges in TI
675 // that don't occur in PTI, or that branch to BB will be activated.
676 std::set<ConstantInt*> PTIHandled;
677 for (unsigned i = 0, e = PredCases.size(); i != e; ++i)
678 if (PredCases[i].second != BB)
679 PTIHandled.insert(PredCases[i].first);
680 else {
681 // The default destination is BB, we don't need explicit targets.
682 std::swap(PredCases[i], PredCases.back());
683 PredCases.pop_back();
684 --i; --e;
685 }
686
687 // Reconstruct the new switch statement we will be building.
688 if (PredDefault != BBDefault) {
689 PredDefault->removePredecessor(Pred);
690 PredDefault = BBDefault;
691 NewSuccessors.push_back(BBDefault);
692 }
693 for (unsigned i = 0, e = BBCases.size(); i != e; ++i)
694 if (!PTIHandled.count(BBCases[i].first) &&
695 BBCases[i].second != BBDefault) {
696 PredCases.push_back(BBCases[i]);
697 NewSuccessors.push_back(BBCases[i].second);
698 }
699
700 } else {
701 // If this is not the default destination from PSI, only the edges
702 // in SI that occur in PSI with a destination of BB will be
703 // activated.
704 std::set<ConstantInt*> PTIHandled;
705 for (unsigned i = 0, e = PredCases.size(); i != e; ++i)
706 if (PredCases[i].second == BB) {
707 PTIHandled.insert(PredCases[i].first);
708 std::swap(PredCases[i], PredCases.back());
709 PredCases.pop_back();
710 --i; --e;
711 }
712
713 // Okay, now we know which constants were sent to BB from the
714 // predecessor. Figure out where they will all go now.
715 for (unsigned i = 0, e = BBCases.size(); i != e; ++i)
716 if (PTIHandled.count(BBCases[i].first)) {
717 // If this is one we are capable of getting...
718 PredCases.push_back(BBCases[i]);
719 NewSuccessors.push_back(BBCases[i].second);
720 PTIHandled.erase(BBCases[i].first);// This constant is taken care of
721 }
722
723 // If there are any constants vectored to BB that TI doesn't handle,
724 // they must go to the default destination of TI.
725 for (std::set<ConstantInt*>::iterator I = PTIHandled.begin(),
726 E = PTIHandled.end(); I != E; ++I) {
727 PredCases.push_back(std::make_pair(*I, BBDefault));
728 NewSuccessors.push_back(BBDefault);
729 }
730 }
731
732 // Okay, at this point, we know which new successor Pred will get. Make
733 // sure we update the number of entries in the PHI nodes for these
734 // successors.
735 for (unsigned i = 0, e = NewSuccessors.size(); i != e; ++i)
736 AddPredecessorToBlock(NewSuccessors[i], Pred, BB);
737
738 // Now that the successors are updated, create the new Switch instruction.
Chris Lattnera35dfce2005-01-29 00:38:26 +0000739 SwitchInst *NewSI = new SwitchInst(CV, PredDefault, PredCases.size(),PTI);
Chris Lattnerd3e6ae22004-02-28 21:28:10 +0000740 for (unsigned i = 0, e = PredCases.size(); i != e; ++i)
741 NewSI->addCase(PredCases[i].first, PredCases[i].second);
Chris Lattner3215bb62005-01-01 16:02:12 +0000742
743 Instruction *DeadCond = 0;
744 if (BranchInst *BI = dyn_cast<BranchInst>(PTI))
745 // If PTI is a branch, remember the condition.
746 DeadCond = dyn_cast<Instruction>(BI->getCondition());
Chris Lattnerd3e6ae22004-02-28 21:28:10 +0000747 Pred->getInstList().erase(PTI);
748
Chris Lattner3215bb62005-01-01 16:02:12 +0000749 // If the condition is dead now, remove the instruction tree.
750 if (DeadCond) ErasePossiblyDeadInstructionTree(DeadCond);
751
Chris Lattnerd3e6ae22004-02-28 21:28:10 +0000752 // Okay, last check. If BB is still a successor of PSI, then we must
753 // have an infinite loop case. If so, add an infinitely looping block
754 // to handle the case to preserve the behavior of the code.
755 BasicBlock *InfLoopBlock = 0;
756 for (unsigned i = 0, e = NewSI->getNumSuccessors(); i != e; ++i)
757 if (NewSI->getSuccessor(i) == BB) {
758 if (InfLoopBlock == 0) {
759 // Insert it at the end of the loop, because it's either code,
760 // or it won't matter if it's hot. :)
761 InfLoopBlock = new BasicBlock("infloop", BB->getParent());
762 new BranchInst(InfLoopBlock, InfLoopBlock);
763 }
764 NewSI->setSuccessor(i, InfLoopBlock);
765 }
Misha Brukmanb1c93172005-04-21 23:48:37 +0000766
Chris Lattnerd3e6ae22004-02-28 21:28:10 +0000767 Changed = true;
768 }
769 }
770 return Changed;
771}
772
Chris Lattner389cfac2004-11-30 00:29:14 +0000773/// HoistThenElseCodeToIf - Given a conditional branch that codes to BB1 and
774/// BB2, hoist any common code in the two blocks up into the branch block. The
775/// caller of this function guarantees that BI's block dominates BB1 and BB2.
776static bool HoistThenElseCodeToIf(BranchInst *BI) {
777 // This does very trivial matching, with limited scanning, to find identical
778 // instructions in the two blocks. In particular, we don't want to get into
779 // O(M*N) situations here where M and N are the sizes of BB1 and BB2. As
780 // such, we currently just scan for obviously identical instructions in an
781 // identical order.
782 BasicBlock *BB1 = BI->getSuccessor(0); // The true destination.
783 BasicBlock *BB2 = BI->getSuccessor(1); // The false destination
784
785 Instruction *I1 = BB1->begin(), *I2 = BB2->begin();
786 if (I1->getOpcode() != I2->getOpcode() || !I1->isIdenticalTo(I2))
787 return false;
788
789 // If we get here, we can hoist at least one instruction.
790 BasicBlock *BIParent = BI->getParent();
Chris Lattner389cfac2004-11-30 00:29:14 +0000791
792 do {
793 // If we are hoisting the terminator instruction, don't move one (making a
794 // broken BB), instead clone it, and remove BI.
795 if (isa<TerminatorInst>(I1))
796 goto HoistTerminator;
Misha Brukmanb1c93172005-04-21 23:48:37 +0000797
Chris Lattner389cfac2004-11-30 00:29:14 +0000798 // For a normal instruction, we just move one to right before the branch,
799 // then replace all uses of the other with the first. Finally, we remove
800 // the now redundant second instruction.
801 BIParent->getInstList().splice(BI, BB1->getInstList(), I1);
802 if (!I2->use_empty())
803 I2->replaceAllUsesWith(I1);
804 BB2->getInstList().erase(I2);
Misha Brukmanb1c93172005-04-21 23:48:37 +0000805
Chris Lattner389cfac2004-11-30 00:29:14 +0000806 I1 = BB1->begin();
807 I2 = BB2->begin();
Chris Lattner389cfac2004-11-30 00:29:14 +0000808 } while (I1->getOpcode() == I2->getOpcode() && I1->isIdenticalTo(I2));
809
810 return true;
811
812HoistTerminator:
813 // Okay, it is safe to hoist the terminator.
814 Instruction *NT = I1->clone();
815 BIParent->getInstList().insert(BI, NT);
816 if (NT->getType() != Type::VoidTy) {
817 I1->replaceAllUsesWith(NT);
818 I2->replaceAllUsesWith(NT);
819 NT->setName(I1->getName());
820 }
821
822 // Hoisting one of the terminators from our successor is a great thing.
823 // Unfortunately, the successors of the if/else blocks may have PHI nodes in
824 // them. If they do, all PHI entries for BB1/BB2 must agree for all PHI
825 // nodes, so we insert select instruction to compute the final result.
826 std::map<std::pair<Value*,Value*>, SelectInst*> InsertedSelects;
827 for (succ_iterator SI = succ_begin(BB1), E = succ_end(BB1); SI != E; ++SI) {
828 PHINode *PN;
829 for (BasicBlock::iterator BBI = SI->begin();
Chris Lattner01944572004-11-30 07:47:34 +0000830 (PN = dyn_cast<PHINode>(BBI)); ++BBI) {
Chris Lattner389cfac2004-11-30 00:29:14 +0000831 Value *BB1V = PN->getIncomingValueForBlock(BB1);
832 Value *BB2V = PN->getIncomingValueForBlock(BB2);
833 if (BB1V != BB2V) {
834 // These values do not agree. Insert a select instruction before NT
835 // that determines the right value.
836 SelectInst *&SI = InsertedSelects[std::make_pair(BB1V, BB2V)];
837 if (SI == 0)
838 SI = new SelectInst(BI->getCondition(), BB1V, BB2V,
839 BB1V->getName()+"."+BB2V->getName(), NT);
840 // Make the PHI node use the select for all incoming values for BB1/BB2
841 for (unsigned i = 0, e = PN->getNumIncomingValues(); i != e; ++i)
842 if (PN->getIncomingBlock(i) == BB1 || PN->getIncomingBlock(i) == BB2)
843 PN->setIncomingValue(i, SI);
844 }
845 }
846 }
847
848 // Update any PHI nodes in our new successors.
849 for (succ_iterator SI = succ_begin(BB1), E = succ_end(BB1); SI != E; ++SI)
850 AddPredecessorToBlock(*SI, BIParent, BB1);
Misha Brukmanb1c93172005-04-21 23:48:37 +0000851
Chris Lattner389cfac2004-11-30 00:29:14 +0000852 BI->eraseFromParent();
853 return true;
854}
855
Chris Lattnerb2b151d2004-06-19 07:02:14 +0000856namespace {
857 /// ConstantIntOrdering - This class implements a stable ordering of constant
858 /// integers that does not depend on their address. This is important for
859 /// applications that sort ConstantInt's to ensure uniqueness.
860 struct ConstantIntOrdering {
861 bool operator()(const ConstantInt *LHS, const ConstantInt *RHS) const {
862 return LHS->getRawValue() < RHS->getRawValue();
863 }
864 };
865}
866
Chris Lattner466a0492002-05-21 20:50:24 +0000867// SimplifyCFG - This function is used to do simplification of a CFG. For
868// example, it adjusts branches to branches to eliminate the extra hop, it
869// eliminates unreachable basic blocks, and does other "peephole" optimization
Chris Lattner31116ba2003-03-05 21:01:52 +0000870// of the CFG. It returns true if a modification was made.
Chris Lattner466a0492002-05-21 20:50:24 +0000871//
872// WARNING: The entry node of a function may not be simplified.
873//
Chris Lattnerdf3c3422004-01-09 06:12:26 +0000874bool llvm::SimplifyCFG(BasicBlock *BB) {
Chris Lattner3f5823f2003-08-24 18:36:16 +0000875 bool Changed = false;
Chris Lattner466a0492002-05-21 20:50:24 +0000876 Function *M = BB->getParent();
877
878 assert(BB && BB->getParent() && "Block not embedded in function!");
879 assert(BB->getTerminator() && "Degenerate basic block encountered!");
Chris Lattnerfda72b12002-06-25 16:12:52 +0000880 assert(&BB->getParent()->front() != BB && "Can't Simplify entry block!");
Chris Lattner466a0492002-05-21 20:50:24 +0000881
Chris Lattner466a0492002-05-21 20:50:24 +0000882 // Remove basic blocks that have no predecessors... which are unreachable.
Chris Lattnera2ab4892004-02-24 07:23:58 +0000883 if (pred_begin(BB) == pred_end(BB) ||
884 *pred_begin(BB) == BB && ++pred_begin(BB) == pred_end(BB)) {
Chris Lattner32c518e2004-07-15 02:06:12 +0000885 DEBUG(std::cerr << "Removing BB: \n" << *BB);
Chris Lattner466a0492002-05-21 20:50:24 +0000886
887 // Loop through all of our successors and make sure they know that one
888 // of their predecessors is going away.
Chris Lattner95f16a32005-04-12 18:51:33 +0000889 for (succ_iterator SI = succ_begin(BB), E = succ_end(BB); SI != E; ++SI)
890 SI->removePredecessor(BB);
Chris Lattner466a0492002-05-21 20:50:24 +0000891
892 while (!BB->empty()) {
Chris Lattnerfda72b12002-06-25 16:12:52 +0000893 Instruction &I = BB->back();
Chris Lattner466a0492002-05-21 20:50:24 +0000894 // If this instruction is used, replace uses with an arbitrary
Chris Lattnereee90f72005-08-02 23:29:23 +0000895 // value. Because control flow can't get here, we don't care
Misha Brukmanb1c93172005-04-21 23:48:37 +0000896 // what we replace the value with. Note that since this block is
Chris Lattner466a0492002-05-21 20:50:24 +0000897 // unreachable, and all values contained within it must dominate their
898 // uses, that all uses will eventually be removed.
Misha Brukmanb1c93172005-04-21 23:48:37 +0000899 if (!I.use_empty())
Chris Lattnereee90f72005-08-02 23:29:23 +0000900 // Make all users of this instruction use undef instead
901 I.replaceAllUsesWith(UndefValue::get(I.getType()));
Misha Brukmanb1c93172005-04-21 23:48:37 +0000902
Chris Lattner466a0492002-05-21 20:50:24 +0000903 // Remove the instruction from the basic block
Chris Lattnerfda72b12002-06-25 16:12:52 +0000904 BB->getInstList().pop_back();
Chris Lattner466a0492002-05-21 20:50:24 +0000905 }
Chris Lattnerfda72b12002-06-25 16:12:52 +0000906 M->getBasicBlockList().erase(BB);
Chris Lattner466a0492002-05-21 20:50:24 +0000907 return true;
908 }
909
Chris Lattner031340a2003-08-17 19:41:53 +0000910 // Check to see if we can constant propagate this terminator instruction
911 // away...
Chris Lattner3f5823f2003-08-24 18:36:16 +0000912 Changed |= ConstantFoldTerminator(BB);
Chris Lattner031340a2003-08-17 19:41:53 +0000913
Chris Lattnere42732e2004-02-16 06:35:48 +0000914 // If this is a returning block with only PHI nodes in it, fold the return
915 // instruction into any unconditional branch predecessors.
Chris Lattner9f0db322004-04-02 18:13:43 +0000916 //
917 // If any predecessor is a conditional branch that just selects among
918 // different return values, fold the replace the branch/return with a select
919 // and return.
Chris Lattnere42732e2004-02-16 06:35:48 +0000920 if (ReturnInst *RI = dyn_cast<ReturnInst>(BB->getTerminator())) {
921 BasicBlock::iterator BBI = BB->getTerminator();
922 if (BBI == BB->begin() || isa<PHINode>(--BBI)) {
Chris Lattner9f0db322004-04-02 18:13:43 +0000923 // Find predecessors that end with branches.
Chris Lattnere42732e2004-02-16 06:35:48 +0000924 std::vector<BasicBlock*> UncondBranchPreds;
Chris Lattner9f0db322004-04-02 18:13:43 +0000925 std::vector<BranchInst*> CondBranchPreds;
Chris Lattnere42732e2004-02-16 06:35:48 +0000926 for (pred_iterator PI = pred_begin(BB), E = pred_end(BB); PI != E; ++PI) {
927 TerminatorInst *PTI = (*PI)->getTerminator();
928 if (BranchInst *BI = dyn_cast<BranchInst>(PTI))
929 if (BI->isUnconditional())
930 UncondBranchPreds.push_back(*PI);
Chris Lattner9f0db322004-04-02 18:13:43 +0000931 else
932 CondBranchPreds.push_back(BI);
Chris Lattnere42732e2004-02-16 06:35:48 +0000933 }
Misha Brukmanb1c93172005-04-21 23:48:37 +0000934
Chris Lattnere42732e2004-02-16 06:35:48 +0000935 // If we found some, do the transformation!
936 if (!UncondBranchPreds.empty()) {
937 while (!UncondBranchPreds.empty()) {
938 BasicBlock *Pred = UncondBranchPreds.back();
939 UncondBranchPreds.pop_back();
940 Instruction *UncondBranch = Pred->getTerminator();
941 // Clone the return and add it to the end of the predecessor.
942 Instruction *NewRet = RI->clone();
943 Pred->getInstList().push_back(NewRet);
944
945 // If the return instruction returns a value, and if the value was a
946 // PHI node in "BB", propagate the right value into the return.
947 if (NewRet->getNumOperands() == 1)
948 if (PHINode *PN = dyn_cast<PHINode>(NewRet->getOperand(0)))
949 if (PN->getParent() == BB)
950 NewRet->setOperand(0, PN->getIncomingValueForBlock(Pred));
951 // Update any PHI nodes in the returning block to realize that we no
952 // longer branch to them.
953 BB->removePredecessor(Pred);
954 Pred->getInstList().erase(UncondBranch);
955 }
956
957 // If we eliminated all predecessors of the block, delete the block now.
958 if (pred_begin(BB) == pred_end(BB))
959 // We know there are no successors, so just nuke the block.
960 M->getBasicBlockList().erase(BB);
961
Chris Lattnere42732e2004-02-16 06:35:48 +0000962 return true;
963 }
Chris Lattner9f0db322004-04-02 18:13:43 +0000964
965 // Check out all of the conditional branches going to this return
966 // instruction. If any of them just select between returns, change the
967 // branch itself into a select/return pair.
968 while (!CondBranchPreds.empty()) {
969 BranchInst *BI = CondBranchPreds.back();
970 CondBranchPreds.pop_back();
971 BasicBlock *TrueSucc = BI->getSuccessor(0);
972 BasicBlock *FalseSucc = BI->getSuccessor(1);
973 BasicBlock *OtherSucc = TrueSucc == BB ? FalseSucc : TrueSucc;
974
975 // Check to see if the non-BB successor is also a return block.
976 if (isa<ReturnInst>(OtherSucc->getTerminator())) {
977 // Check to see if there are only PHI instructions in this block.
978 BasicBlock::iterator OSI = OtherSucc->getTerminator();
979 if (OSI == OtherSucc->begin() || isa<PHINode>(--OSI)) {
980 // Okay, we found a branch that is going to two return nodes. If
981 // there is no return value for this function, just change the
982 // branch into a return.
983 if (RI->getNumOperands() == 0) {
984 TrueSucc->removePredecessor(BI->getParent());
985 FalseSucc->removePredecessor(BI->getParent());
986 new ReturnInst(0, BI);
987 BI->getParent()->getInstList().erase(BI);
988 return true;
989 }
990
991 // Otherwise, figure out what the true and false return values are
992 // so we can insert a new select instruction.
993 Value *TrueValue = TrueSucc->getTerminator()->getOperand(0);
994 Value *FalseValue = FalseSucc->getTerminator()->getOperand(0);
995
996 // Unwrap any PHI nodes in the return blocks.
997 if (PHINode *TVPN = dyn_cast<PHINode>(TrueValue))
998 if (TVPN->getParent() == TrueSucc)
999 TrueValue = TVPN->getIncomingValueForBlock(BI->getParent());
1000 if (PHINode *FVPN = dyn_cast<PHINode>(FalseValue))
1001 if (FVPN->getParent() == FalseSucc)
1002 FalseValue = FVPN->getIncomingValueForBlock(BI->getParent());
1003
Chris Lattnereed034b2004-04-02 18:15:10 +00001004 TrueSucc->removePredecessor(BI->getParent());
1005 FalseSucc->removePredecessor(BI->getParent());
1006
Chris Lattner9f0db322004-04-02 18:13:43 +00001007 // Insert a new select instruction.
Chris Lattner879ce782004-09-29 05:43:32 +00001008 Value *NewRetVal;
1009 Value *BrCond = BI->getCondition();
1010 if (TrueValue != FalseValue)
1011 NewRetVal = new SelectInst(BrCond, TrueValue,
1012 FalseValue, "retval", BI);
1013 else
1014 NewRetVal = TrueValue;
1015
Chris Lattner9f0db322004-04-02 18:13:43 +00001016 new ReturnInst(NewRetVal, BI);
1017 BI->getParent()->getInstList().erase(BI);
Chris Lattner879ce782004-09-29 05:43:32 +00001018 if (BrCond->use_empty())
1019 if (Instruction *BrCondI = dyn_cast<Instruction>(BrCond))
1020 BrCondI->getParent()->getInstList().erase(BrCondI);
Chris Lattner9f0db322004-04-02 18:13:43 +00001021 return true;
1022 }
1023 }
1024 }
Chris Lattnere42732e2004-02-16 06:35:48 +00001025 }
Chris Lattner3cd98f02004-02-24 05:54:22 +00001026 } else if (UnwindInst *UI = dyn_cast<UnwindInst>(BB->begin())) {
1027 // Check to see if the first instruction in this block is just an unwind.
1028 // If so, replace any invoke instructions which use this as an exception
Chris Lattner5823ac12004-07-20 01:17:38 +00001029 // destination with call instructions, and any unconditional branch
1030 // predecessor with an unwind.
Chris Lattner3cd98f02004-02-24 05:54:22 +00001031 //
1032 std::vector<BasicBlock*> Preds(pred_begin(BB), pred_end(BB));
1033 while (!Preds.empty()) {
1034 BasicBlock *Pred = Preds.back();
Chris Lattner5823ac12004-07-20 01:17:38 +00001035 if (BranchInst *BI = dyn_cast<BranchInst>(Pred->getTerminator())) {
1036 if (BI->isUnconditional()) {
1037 Pred->getInstList().pop_back(); // nuke uncond branch
1038 new UnwindInst(Pred); // Use unwind.
1039 Changed = true;
1040 }
1041 } else if (InvokeInst *II = dyn_cast<InvokeInst>(Pred->getTerminator()))
Chris Lattner3cd98f02004-02-24 05:54:22 +00001042 if (II->getUnwindDest() == BB) {
1043 // Insert a new branch instruction before the invoke, because this
1044 // is now a fall through...
1045 BranchInst *BI = new BranchInst(II->getNormalDest(), II);
1046 Pred->getInstList().remove(II); // Take out of symbol table
Misha Brukmanb1c93172005-04-21 23:48:37 +00001047
Chris Lattner3cd98f02004-02-24 05:54:22 +00001048 // Insert the call now...
1049 std::vector<Value*> Args(II->op_begin()+3, II->op_end());
1050 CallInst *CI = new CallInst(II->getCalledValue(), Args,
1051 II->getName(), BI);
Chris Lattnerbcefcf82005-05-14 12:21:56 +00001052 CI->setCallingConv(II->getCallingConv());
Chris Lattner3cd98f02004-02-24 05:54:22 +00001053 // If the invoke produced a value, the Call now does instead
1054 II->replaceAllUsesWith(CI);
1055 delete II;
1056 Changed = true;
1057 }
Misha Brukmanb1c93172005-04-21 23:48:37 +00001058
Chris Lattner3cd98f02004-02-24 05:54:22 +00001059 Preds.pop_back();
1060 }
Chris Lattner90ea78e2004-02-24 16:09:21 +00001061
1062 // If this block is now dead, remove it.
1063 if (pred_begin(BB) == pred_end(BB)) {
1064 // We know there are no successors, so just nuke the block.
1065 M->getBasicBlockList().erase(BB);
1066 return true;
1067 }
1068
Chris Lattner1cca9592005-02-24 06:17:52 +00001069 } else if (SwitchInst *SI = dyn_cast<SwitchInst>(BB->getTerminator())) {
1070 if (isValueEqualityComparison(SI)) {
1071 // If we only have one predecessor, and if it is a branch on this value,
1072 // see if that predecessor totally determines the outcome of this switch.
1073 if (BasicBlock *OnlyPred = BB->getSinglePredecessor())
1074 if (SimplifyEqualityComparisonWithOnlyPredecessor(SI, OnlyPred))
1075 return SimplifyCFG(BB) || 1;
1076
1077 // If the block only contains the switch, see if we can fold the block
1078 // away into any preds.
1079 if (SI == &BB->front())
1080 if (FoldValueComparisonIntoPredecessors(SI))
1081 return SimplifyCFG(BB) || 1;
1082 }
Chris Lattnerd3e6ae22004-02-28 21:28:10 +00001083 } else if (BranchInst *BI = dyn_cast<BranchInst>(BB->getTerminator())) {
Chris Lattner733d6702005-08-03 00:11:16 +00001084 if (BI->isUnconditional()) {
1085 BasicBlock::iterator BBI = BB->begin(); // Skip over phi nodes...
1086 while (isa<PHINode>(*BBI)) ++BBI;
1087
1088 BasicBlock *Succ = BI->getSuccessor(0);
1089 if (BBI->isTerminator() && // Terminator is the only non-phi instruction!
1090 Succ != BB) // Don't hurt infinite loops!
1091 if (TryToSimplifyUncondBranchFromEmptyBlock(BB, Succ))
1092 return 1;
1093
1094 } else { // Conditional branch
Chris Lattner2e93c422004-05-01 23:35:43 +00001095 if (Value *CompVal = isValueEqualityComparison(BI)) {
Chris Lattner1cca9592005-02-24 06:17:52 +00001096 // If we only have one predecessor, and if it is a branch on this value,
1097 // see if that predecessor totally determines the outcome of this
1098 // switch.
1099 if (BasicBlock *OnlyPred = BB->getSinglePredecessor())
1100 if (SimplifyEqualityComparisonWithOnlyPredecessor(BI, OnlyPred))
1101 return SimplifyCFG(BB) || 1;
1102
Chris Lattner2e93c422004-05-01 23:35:43 +00001103 // This block must be empty, except for the setcond inst, if it exists.
1104 BasicBlock::iterator I = BB->begin();
1105 if (&*I == BI ||
1106 (&*I == cast<Instruction>(BI->getCondition()) &&
1107 &*++I == BI))
1108 if (FoldValueComparisonIntoPredecessors(BI))
1109 return SimplifyCFG(BB) | true;
1110 }
1111
1112 // If this basic block is ONLY a setcc and a branch, and if a predecessor
1113 // branches to us and one of our successors, fold the setcc into the
1114 // predecessor and use logical operations to pick the right destination.
Chris Lattner51a6dbc2004-05-02 05:02:03 +00001115 BasicBlock *TrueDest = BI->getSuccessor(0);
1116 BasicBlock *FalseDest = BI->getSuccessor(1);
Chris Lattnerbe6f0682004-05-02 05:19:36 +00001117 if (BinaryOperator *Cond = dyn_cast<BinaryOperator>(BI->getCondition()))
Chris Lattner2e93c422004-05-01 23:35:43 +00001118 if (Cond->getParent() == BB && &BB->front() == Cond &&
Chris Lattner51a6dbc2004-05-02 05:02:03 +00001119 Cond->getNext() == BI && Cond->hasOneUse() &&
1120 TrueDest != BB && FalseDest != BB)
Chris Lattner2e93c422004-05-01 23:35:43 +00001121 for (pred_iterator PI = pred_begin(BB), E = pred_end(BB); PI!=E; ++PI)
1122 if (BranchInst *PBI = dyn_cast<BranchInst>((*PI)->getTerminator()))
Chris Lattner1e94ed62004-05-02 01:00:44 +00001123 if (PBI->isConditional() && SafeToMergeTerminators(BI, PBI)) {
Chris Lattnerf12c4a32004-06-21 07:19:01 +00001124 BasicBlock *PredBlock = *PI;
Chris Lattner2e93c422004-05-01 23:35:43 +00001125 if (PBI->getSuccessor(0) == FalseDest ||
1126 PBI->getSuccessor(1) == TrueDest) {
1127 // Invert the predecessors condition test (xor it with true),
1128 // which allows us to write this code once.
1129 Value *NewCond =
1130 BinaryOperator::createNot(PBI->getCondition(),
1131 PBI->getCondition()->getName()+".not", PBI);
1132 PBI->setCondition(NewCond);
1133 BasicBlock *OldTrue = PBI->getSuccessor(0);
1134 BasicBlock *OldFalse = PBI->getSuccessor(1);
1135 PBI->setSuccessor(0, OldFalse);
1136 PBI->setSuccessor(1, OldTrue);
1137 }
1138
1139 if (PBI->getSuccessor(0) == TrueDest ||
1140 PBI->getSuccessor(1) == FalseDest) {
Chris Lattnerf12c4a32004-06-21 07:19:01 +00001141 // Clone Cond into the predecessor basic block, and or/and the
Chris Lattner2e93c422004-05-01 23:35:43 +00001142 // two conditions together.
1143 Instruction *New = Cond->clone();
1144 New->setName(Cond->getName());
1145 Cond->setName(Cond->getName()+".old");
Chris Lattnerf12c4a32004-06-21 07:19:01 +00001146 PredBlock->getInstList().insert(PBI, New);
Chris Lattner2e93c422004-05-01 23:35:43 +00001147 Instruction::BinaryOps Opcode =
1148 PBI->getSuccessor(0) == TrueDest ?
1149 Instruction::Or : Instruction::And;
Misha Brukmanb1c93172005-04-21 23:48:37 +00001150 Value *NewCond =
Chris Lattner2e93c422004-05-01 23:35:43 +00001151 BinaryOperator::create(Opcode, PBI->getCondition(),
1152 New, "bothcond", PBI);
1153 PBI->setCondition(NewCond);
1154 if (PBI->getSuccessor(0) == BB) {
Chris Lattnerf12c4a32004-06-21 07:19:01 +00001155 AddPredecessorToBlock(TrueDest, PredBlock, BB);
Chris Lattner2e93c422004-05-01 23:35:43 +00001156 PBI->setSuccessor(0, TrueDest);
1157 }
1158 if (PBI->getSuccessor(1) == BB) {
Chris Lattnerf12c4a32004-06-21 07:19:01 +00001159 AddPredecessorToBlock(FalseDest, PredBlock, BB);
Chris Lattner2e93c422004-05-01 23:35:43 +00001160 PBI->setSuccessor(1, FalseDest);
1161 }
1162 return SimplifyCFG(BB) | 1;
1163 }
1164 }
Chris Lattner2e93c422004-05-01 23:35:43 +00001165
Chris Lattner88da6f72004-05-01 22:36:37 +00001166 // If this block ends with a branch instruction, and if there is one
1167 // predecessor, see if the previous block ended with a branch on the same
1168 // condition, which makes this conditional branch redundant.
Chris Lattner733d6702005-08-03 00:11:16 +00001169 if (BasicBlock *OnlyPred = BB->getSinglePredecessor())
Chris Lattner88da6f72004-05-01 22:36:37 +00001170 if (BranchInst *PBI = dyn_cast<BranchInst>(OnlyPred->getTerminator()))
1171 if (PBI->isConditional() &&
1172 PBI->getCondition() == BI->getCondition() &&
Chris Lattner4cbd1602004-05-01 22:41:51 +00001173 (PBI->getSuccessor(0) != BB || PBI->getSuccessor(1) != BB)) {
Chris Lattner88da6f72004-05-01 22:36:37 +00001174 // Okay, the outcome of this conditional branch is statically
1175 // knowable. Delete the outgoing CFG edge that is impossible to
1176 // execute.
1177 bool CondIsTrue = PBI->getSuccessor(0) == BB;
1178 BI->getSuccessor(CondIsTrue)->removePredecessor(BB);
1179 new BranchInst(BI->getSuccessor(!CondIsTrue), BB);
1180 BB->getInstList().erase(BI);
1181 return SimplifyCFG(BB) | true;
1182 }
Chris Lattnera2ab4892004-02-24 07:23:58 +00001183 }
Chris Lattner5edb2f32004-10-18 04:07:22 +00001184 } else if (isa<UnreachableInst>(BB->getTerminator())) {
1185 // If there are any instructions immediately before the unreachable that can
1186 // be removed, do so.
1187 Instruction *Unreachable = BB->getTerminator();
1188 while (Unreachable != BB->begin()) {
1189 BasicBlock::iterator BBI = Unreachable;
1190 --BBI;
1191 if (isa<CallInst>(BBI)) break;
1192 // Delete this instruction
1193 BB->getInstList().erase(BBI);
1194 Changed = true;
1195 }
1196
1197 // If the unreachable instruction is the first in the block, take a gander
1198 // at all of the predecessors of this instruction, and simplify them.
1199 if (&BB->front() == Unreachable) {
1200 std::vector<BasicBlock*> Preds(pred_begin(BB), pred_end(BB));
1201 for (unsigned i = 0, e = Preds.size(); i != e; ++i) {
1202 TerminatorInst *TI = Preds[i]->getTerminator();
1203
1204 if (BranchInst *BI = dyn_cast<BranchInst>(TI)) {
1205 if (BI->isUnconditional()) {
1206 if (BI->getSuccessor(0) == BB) {
1207 new UnreachableInst(TI);
1208 TI->eraseFromParent();
1209 Changed = true;
1210 }
1211 } else {
1212 if (BI->getSuccessor(0) == BB) {
1213 new BranchInst(BI->getSuccessor(1), BI);
1214 BI->eraseFromParent();
1215 } else if (BI->getSuccessor(1) == BB) {
1216 new BranchInst(BI->getSuccessor(0), BI);
1217 BI->eraseFromParent();
1218 Changed = true;
1219 }
1220 }
1221 } else if (SwitchInst *SI = dyn_cast<SwitchInst>(TI)) {
1222 for (unsigned i = 1, e = SI->getNumCases(); i != e; ++i)
1223 if (SI->getSuccessor(i) == BB) {
Chris Lattner19f9f322005-05-20 22:19:54 +00001224 BB->removePredecessor(SI->getParent());
Chris Lattner5edb2f32004-10-18 04:07:22 +00001225 SI->removeCase(i);
1226 --i; --e;
1227 Changed = true;
1228 }
1229 // If the default value is unreachable, figure out the most popular
1230 // destination and make it the default.
1231 if (SI->getSuccessor(0) == BB) {
1232 std::map<BasicBlock*, unsigned> Popularity;
1233 for (unsigned i = 1, e = SI->getNumCases(); i != e; ++i)
1234 Popularity[SI->getSuccessor(i)]++;
1235
1236 // Find the most popular block.
1237 unsigned MaxPop = 0;
1238 BasicBlock *MaxBlock = 0;
1239 for (std::map<BasicBlock*, unsigned>::iterator
1240 I = Popularity.begin(), E = Popularity.end(); I != E; ++I) {
1241 if (I->second > MaxPop) {
1242 MaxPop = I->second;
1243 MaxBlock = I->first;
1244 }
1245 }
1246 if (MaxBlock) {
1247 // Make this the new default, allowing us to delete any explicit
1248 // edges to it.
1249 SI->setSuccessor(0, MaxBlock);
1250 Changed = true;
1251
Chris Lattner19f9f322005-05-20 22:19:54 +00001252 // If MaxBlock has phinodes in it, remove MaxPop-1 entries from
1253 // it.
1254 if (isa<PHINode>(MaxBlock->begin()))
1255 for (unsigned i = 0; i != MaxPop-1; ++i)
1256 MaxBlock->removePredecessor(SI->getParent());
1257
Chris Lattner5edb2f32004-10-18 04:07:22 +00001258 for (unsigned i = 1, e = SI->getNumCases(); i != e; ++i)
1259 if (SI->getSuccessor(i) == MaxBlock) {
1260 SI->removeCase(i);
1261 --i; --e;
1262 }
1263 }
1264 }
1265 } else if (InvokeInst *II = dyn_cast<InvokeInst>(TI)) {
1266 if (II->getUnwindDest() == BB) {
1267 // Convert the invoke to a call instruction. This would be a good
1268 // place to note that the call does not throw though.
1269 BranchInst *BI = new BranchInst(II->getNormalDest(), II);
1270 II->removeFromParent(); // Take out of symbol table
Misha Brukmanb1c93172005-04-21 23:48:37 +00001271
Chris Lattner5edb2f32004-10-18 04:07:22 +00001272 // Insert the call now...
1273 std::vector<Value*> Args(II->op_begin()+3, II->op_end());
1274 CallInst *CI = new CallInst(II->getCalledValue(), Args,
1275 II->getName(), BI);
Chris Lattnerbcefcf82005-05-14 12:21:56 +00001276 CI->setCallingConv(II->getCallingConv());
Chris Lattner5edb2f32004-10-18 04:07:22 +00001277 // If the invoke produced a value, the Call does now instead.
1278 II->replaceAllUsesWith(CI);
1279 delete II;
1280 Changed = true;
1281 }
1282 }
1283 }
1284
1285 // If this block is now dead, remove it.
1286 if (pred_begin(BB) == pred_end(BB)) {
1287 // We know there are no successors, so just nuke the block.
1288 M->getBasicBlockList().erase(BB);
1289 return true;
1290 }
1291 }
Chris Lattnere42732e2004-02-16 06:35:48 +00001292 }
1293
Chris Lattner466a0492002-05-21 20:50:24 +00001294 // Merge basic blocks into their predecessor if there is only one distinct
1295 // pred, and if there is only one distinct successor of the predecessor, and
1296 // if there are no PHI nodes.
1297 //
Chris Lattner838b8452004-02-11 01:17:07 +00001298 pred_iterator PI(pred_begin(BB)), PE(pred_end(BB));
1299 BasicBlock *OnlyPred = *PI++;
1300 for (; PI != PE; ++PI) // Search all predecessors, see if they are all same
1301 if (*PI != OnlyPred) {
1302 OnlyPred = 0; // There are multiple different predecessors...
1303 break;
1304 }
Chris Lattner88da6f72004-05-01 22:36:37 +00001305
Chris Lattner838b8452004-02-11 01:17:07 +00001306 BasicBlock *OnlySucc = 0;
1307 if (OnlyPred && OnlyPred != BB && // Don't break self loops
1308 OnlyPred->getTerminator()->getOpcode() != Instruction::Invoke) {
1309 // Check to see if there is only one distinct successor...
1310 succ_iterator SI(succ_begin(OnlyPred)), SE(succ_end(OnlyPred));
1311 OnlySucc = BB;
1312 for (; SI != SE; ++SI)
1313 if (*SI != OnlySucc) {
1314 OnlySucc = 0; // There are multiple distinct successors!
Chris Lattner466a0492002-05-21 20:50:24 +00001315 break;
1316 }
Chris Lattner838b8452004-02-11 01:17:07 +00001317 }
1318
1319 if (OnlySucc) {
Chris Lattner32c518e2004-07-15 02:06:12 +00001320 DEBUG(std::cerr << "Merging: " << *BB << "into: " << *OnlyPred);
Chris Lattner838b8452004-02-11 01:17:07 +00001321 TerminatorInst *Term = OnlyPred->getTerminator();
1322
1323 // Resolve any PHI nodes at the start of the block. They are all
1324 // guaranteed to have exactly one entry if they exist, unless there are
1325 // multiple duplicate (but guaranteed to be equal) entries for the
1326 // incoming edges. This occurs when there are multiple edges from
1327 // OnlyPred to OnlySucc.
1328 //
1329 while (PHINode *PN = dyn_cast<PHINode>(&BB->front())) {
1330 PN->replaceAllUsesWith(PN->getIncomingValue(0));
1331 BB->getInstList().pop_front(); // Delete the phi node...
Chris Lattner466a0492002-05-21 20:50:24 +00001332 }
1333
Chris Lattner838b8452004-02-11 01:17:07 +00001334 // Delete the unconditional branch from the predecessor...
1335 OnlyPred->getInstList().pop_back();
Misha Brukmanb1c93172005-04-21 23:48:37 +00001336
Chris Lattner838b8452004-02-11 01:17:07 +00001337 // Move all definitions in the successor to the predecessor...
1338 OnlyPred->getInstList().splice(OnlyPred->end(), BB->getInstList());
Misha Brukmanb1c93172005-04-21 23:48:37 +00001339
Chris Lattner838b8452004-02-11 01:17:07 +00001340 // Make all PHI nodes that referred to BB now refer to Pred as their
1341 // source...
1342 BB->replaceAllUsesWith(OnlyPred);
Chris Lattnerfda72b12002-06-25 16:12:52 +00001343
Chris Lattner838b8452004-02-11 01:17:07 +00001344 std::string OldName = BB->getName();
Chris Lattnerfda72b12002-06-25 16:12:52 +00001345
Misha Brukmanb1c93172005-04-21 23:48:37 +00001346 // Erase basic block from the function...
Chris Lattner838b8452004-02-11 01:17:07 +00001347 M->getBasicBlockList().erase(BB);
Chris Lattnerfda72b12002-06-25 16:12:52 +00001348
Chris Lattner838b8452004-02-11 01:17:07 +00001349 // Inherit predecessors name if it exists...
1350 if (!OldName.empty() && !OnlyPred->hasName())
1351 OnlyPred->setName(OldName);
Misha Brukmanb1c93172005-04-21 23:48:37 +00001352
Chris Lattner838b8452004-02-11 01:17:07 +00001353 return true;
Chris Lattner466a0492002-05-21 20:50:24 +00001354 }
Chris Lattner18d1f192004-02-11 03:36:04 +00001355
Chris Lattner389cfac2004-11-30 00:29:14 +00001356 // Otherwise, if this block only has a single predecessor, and if that block
1357 // is a conditional branch, see if we can hoist any code from this block up
1358 // into our predecessor.
1359 if (OnlyPred)
Chris Lattner4fc998d2004-12-10 17:42:31 +00001360 if (BranchInst *BI = dyn_cast<BranchInst>(OnlyPred->getTerminator()))
1361 if (BI->isConditional()) {
1362 // Get the other block.
1363 BasicBlock *OtherBB = BI->getSuccessor(BI->getSuccessor(0) == BB);
1364 PI = pred_begin(OtherBB);
1365 ++PI;
1366 if (PI == pred_end(OtherBB)) {
1367 // We have a conditional branch to two blocks that are only reachable
1368 // from the condbr. We know that the condbr dominates the two blocks,
1369 // so see if there is any identical code in the "then" and "else"
1370 // blocks. If so, we can hoist it up to the branching block.
1371 Changed |= HoistThenElseCodeToIf(BI);
1372 }
Chris Lattner389cfac2004-11-30 00:29:14 +00001373 }
Chris Lattner389cfac2004-11-30 00:29:14 +00001374
Chris Lattner6f4b45a2004-02-24 05:38:11 +00001375 for (pred_iterator PI = pred_begin(BB), E = pred_end(BB); PI != E; ++PI)
1376 if (BranchInst *BI = dyn_cast<BranchInst>((*PI)->getTerminator()))
1377 // Change br (X == 0 | X == 1), T, F into a switch instruction.
1378 if (BI->isConditional() && isa<Instruction>(BI->getCondition())) {
1379 Instruction *Cond = cast<Instruction>(BI->getCondition());
1380 // If this is a bunch of seteq's or'd together, or if it's a bunch of
1381 // 'setne's and'ed together, collect them.
1382 Value *CompVal = 0;
Chris Lattnerb2b151d2004-06-19 07:02:14 +00001383 std::vector<ConstantInt*> Values;
Chris Lattner6f4b45a2004-02-24 05:38:11 +00001384 bool TrueWhenEqual = GatherValueComparisons(Cond, CompVal, Values);
1385 if (CompVal && CompVal->getType()->isInteger()) {
1386 // There might be duplicate constants in the list, which the switch
1387 // instruction can't handle, remove them now.
Chris Lattnerb2b151d2004-06-19 07:02:14 +00001388 std::sort(Values.begin(), Values.end(), ConstantIntOrdering());
Chris Lattner6f4b45a2004-02-24 05:38:11 +00001389 Values.erase(std::unique(Values.begin(), Values.end()), Values.end());
Misha Brukmanb1c93172005-04-21 23:48:37 +00001390
Chris Lattner6f4b45a2004-02-24 05:38:11 +00001391 // Figure out which block is which destination.
1392 BasicBlock *DefaultBB = BI->getSuccessor(1);
1393 BasicBlock *EdgeBB = BI->getSuccessor(0);
1394 if (!TrueWhenEqual) std::swap(DefaultBB, EdgeBB);
Misha Brukmanb1c93172005-04-21 23:48:37 +00001395
Chris Lattner6f4b45a2004-02-24 05:38:11 +00001396 // Create the new switch instruction now.
Chris Lattnera35dfce2005-01-29 00:38:26 +00001397 SwitchInst *New = new SwitchInst(CompVal, DefaultBB,Values.size(),BI);
Misha Brukmanb1c93172005-04-21 23:48:37 +00001398
Chris Lattner6f4b45a2004-02-24 05:38:11 +00001399 // Add all of the 'cases' to the switch instruction.
1400 for (unsigned i = 0, e = Values.size(); i != e; ++i)
1401 New->addCase(Values[i], EdgeBB);
Misha Brukmanb1c93172005-04-21 23:48:37 +00001402
Chris Lattner6f4b45a2004-02-24 05:38:11 +00001403 // We added edges from PI to the EdgeBB. As such, if there were any
1404 // PHI nodes in EdgeBB, they need entries to be added corresponding to
1405 // the number of edges added.
1406 for (BasicBlock::iterator BBI = EdgeBB->begin();
Reid Spencer66149462004-09-15 17:06:42 +00001407 isa<PHINode>(BBI); ++BBI) {
1408 PHINode *PN = cast<PHINode>(BBI);
Chris Lattner6f4b45a2004-02-24 05:38:11 +00001409 Value *InVal = PN->getIncomingValueForBlock(*PI);
1410 for (unsigned i = 0, e = Values.size()-1; i != e; ++i)
1411 PN->addIncoming(InVal, *PI);
1412 }
1413
1414 // Erase the old branch instruction.
1415 (*PI)->getInstList().erase(BI);
1416
1417 // Erase the potentially condition tree that was used to computed the
1418 // branch condition.
1419 ErasePossiblyDeadInstructionTree(Cond);
1420 return true;
1421 }
1422 }
1423
Chris Lattner18d1f192004-02-11 03:36:04 +00001424 // If there is a trivial two-entry PHI node in this basic block, and we can
1425 // eliminate it, do so now.
1426 if (PHINode *PN = dyn_cast<PHINode>(BB->begin()))
1427 if (PN->getNumIncomingValues() == 2) {
1428 // Ok, this is a two entry PHI node. Check to see if this is a simple "if
1429 // statement", which has a very simple dominance structure. Basically, we
1430 // are trying to find the condition that is being branched on, which
1431 // subsequently causes this merge to happen. We really want control
1432 // dependence information for this check, but simplifycfg can't keep it up
1433 // to date, and this catches most of the cases we care about anyway.
1434 //
1435 BasicBlock *IfTrue, *IfFalse;
1436 if (Value *IfCond = GetIfCondition(BB, IfTrue, IfFalse)) {
Chris Lattner9734fd02004-06-20 01:13:18 +00001437 DEBUG(std::cerr << "FOUND IF CONDITION! " << *IfCond << " T: "
1438 << IfTrue->getName() << " F: " << IfFalse->getName() << "\n");
Chris Lattner18d1f192004-02-11 03:36:04 +00001439
Chris Lattner45c35b12004-10-14 05:13:36 +00001440 // Loop over the PHI's seeing if we can promote them all to select
1441 // instructions. While we are at it, keep track of the instructions
1442 // that need to be moved to the dominating block.
1443 std::set<Instruction*> AggressiveInsts;
1444 bool CanPromote = true;
1445
Chris Lattner18d1f192004-02-11 03:36:04 +00001446 BasicBlock::iterator AfterPHIIt = BB->begin();
Chris Lattner45c35b12004-10-14 05:13:36 +00001447 while (isa<PHINode>(AfterPHIIt)) {
1448 PHINode *PN = cast<PHINode>(AfterPHIIt++);
Chris Lattner5e735292005-06-17 01:45:53 +00001449 if (PN->getIncomingValue(0) == PN->getIncomingValue(1)) {
1450 if (PN->getIncomingValue(0) != PN)
1451 PN->replaceAllUsesWith(PN->getIncomingValue(0));
1452 else
1453 PN->replaceAllUsesWith(UndefValue::get(PN->getType()));
1454 } else if (!DominatesMergePoint(PN->getIncomingValue(0), BB,
1455 &AggressiveInsts) ||
1456 !DominatesMergePoint(PN->getIncomingValue(1), BB,
1457 &AggressiveInsts)) {
Chris Lattner45c35b12004-10-14 05:13:36 +00001458 CanPromote = false;
1459 break;
1460 }
1461 }
Chris Lattner18d1f192004-02-11 03:36:04 +00001462
Chris Lattner45c35b12004-10-14 05:13:36 +00001463 // Did we eliminate all PHI's?
1464 CanPromote |= AfterPHIIt == BB->begin();
Chris Lattner18d1f192004-02-11 03:36:04 +00001465
Chris Lattner45c35b12004-10-14 05:13:36 +00001466 // If we all PHI nodes are promotable, check to make sure that all
1467 // instructions in the predecessor blocks can be promoted as well. If
1468 // not, we won't be able to get rid of the control flow, so it's not
1469 // worth promoting to select instructions.
Reid Spencerfad217c2004-10-22 16:10:39 +00001470 BasicBlock *DomBlock = 0, *IfBlock1 = 0, *IfBlock2 = 0;
Chris Lattner45c35b12004-10-14 05:13:36 +00001471 if (CanPromote) {
1472 PN = cast<PHINode>(BB->begin());
1473 BasicBlock *Pred = PN->getIncomingBlock(0);
1474 if (cast<BranchInst>(Pred->getTerminator())->isUnconditional()) {
1475 IfBlock1 = Pred;
1476 DomBlock = *pred_begin(Pred);
1477 for (BasicBlock::iterator I = Pred->begin();
1478 !isa<TerminatorInst>(I); ++I)
1479 if (!AggressiveInsts.count(I)) {
1480 // This is not an aggressive instruction that we can promote.
1481 // Because of this, we won't be able to get rid of the control
1482 // flow, so the xform is not worth it.
1483 CanPromote = false;
1484 break;
1485 }
1486 }
1487
1488 Pred = PN->getIncomingBlock(1);
Misha Brukmanb1c93172005-04-21 23:48:37 +00001489 if (CanPromote &&
Chris Lattner45c35b12004-10-14 05:13:36 +00001490 cast<BranchInst>(Pred->getTerminator())->isUnconditional()) {
1491 IfBlock2 = Pred;
1492 DomBlock = *pred_begin(Pred);
1493 for (BasicBlock::iterator I = Pred->begin();
1494 !isa<TerminatorInst>(I); ++I)
1495 if (!AggressiveInsts.count(I)) {
1496 // This is not an aggressive instruction that we can promote.
1497 // Because of this, we won't be able to get rid of the control
1498 // flow, so the xform is not worth it.
1499 CanPromote = false;
1500 break;
1501 }
1502 }
1503 }
1504
1505 // If we can still promote the PHI nodes after this gauntlet of tests,
1506 // do all of the PHI's now.
1507 if (CanPromote) {
1508 // Move all 'aggressive' instructions, which are defined in the
1509 // conditional parts of the if's up to the dominating block.
1510 if (IfBlock1) {
1511 DomBlock->getInstList().splice(DomBlock->getTerminator(),
1512 IfBlock1->getInstList(),
1513 IfBlock1->begin(),
1514 IfBlock1->getTerminator());
1515 }
1516 if (IfBlock2) {
1517 DomBlock->getInstList().splice(DomBlock->getTerminator(),
1518 IfBlock2->getInstList(),
1519 IfBlock2->begin(),
1520 IfBlock2->getTerminator());
1521 }
1522
1523 while (PHINode *PN = dyn_cast<PHINode>(BB->begin())) {
1524 // Change the PHI node into a select instruction.
Chris Lattner18d1f192004-02-11 03:36:04 +00001525 Value *TrueVal =
1526 PN->getIncomingValue(PN->getIncomingBlock(0) == IfFalse);
1527 Value *FalseVal =
1528 PN->getIncomingValue(PN->getIncomingBlock(0) == IfTrue);
1529
Chris Lattner81bdcb92004-03-30 19:44:05 +00001530 std::string Name = PN->getName(); PN->setName("");
1531 PN->replaceAllUsesWith(new SelectInst(IfCond, TrueVal, FalseVal,
Chris Lattner45c35b12004-10-14 05:13:36 +00001532 Name, AfterPHIIt));
Chris Lattner81bdcb92004-03-30 19:44:05 +00001533 BB->getInstList().erase(PN);
Chris Lattner18d1f192004-02-11 03:36:04 +00001534 }
Chris Lattner45c35b12004-10-14 05:13:36 +00001535 Changed = true;
Chris Lattner18d1f192004-02-11 03:36:04 +00001536 }
1537 }
1538 }
Misha Brukmanb1c93172005-04-21 23:48:37 +00001539
Chris Lattner031340a2003-08-17 19:41:53 +00001540 return Changed;
Chris Lattner466a0492002-05-21 20:50:24 +00001541}