Make sure that the landing pads themselves have no PHI instructions in them.
[oota-llvm.git] / lib / CodeGen / SjLjEHPrepare.cpp
1 //===- SjLjEHPass.cpp - Eliminate Invoke & Unwind instructions -----------===//
2 //
3 //                     The LLVM Compiler Infrastructure
4 //
5 // This file is distributed under the University of Illinois Open Source
6 // License. See LICENSE.TXT for details.
7 //
8 //===----------------------------------------------------------------------===//
9 //
10 // This transformation is designed for use by code generators which use SjLj
11 // based exception handling.
12 //
13 //===----------------------------------------------------------------------===//
14
15 #define DEBUG_TYPE "sjljehprepare"
16 #include "llvm/Transforms/Scalar.h"
17 #include "llvm/Constants.h"
18 #include "llvm/DerivedTypes.h"
19 #include "llvm/Instructions.h"
20 #include "llvm/Intrinsics.h"
21 #include "llvm/LLVMContext.h"
22 #include "llvm/Module.h"
23 #include "llvm/Pass.h"
24 #include "llvm/CodeGen/Passes.h"
25 #include "llvm/Target/TargetData.h"
26 #include "llvm/Target/TargetLowering.h"
27 #include "llvm/Transforms/Utils/BasicBlockUtils.h"
28 #include "llvm/Transforms/Utils/Local.h"
29 #include "llvm/Support/CommandLine.h"
30 #include "llvm/Support/Debug.h"
31 #include "llvm/Support/IRBuilder.h"
32 #include "llvm/ADT/DenseMap.h"
33 #include "llvm/ADT/SmallVector.h"
34 #include "llvm/ADT/Statistic.h"
35 #include <set>
36 using namespace llvm;
37
38 static cl::opt<bool> DisableOldSjLjEH("disable-old-sjlj-eh", cl::Hidden,
39                                       cl::init(true),
40     cl::desc("Disable the old SjLj EH preparation pass"));
41
42 STATISTIC(NumInvokes, "Number of invokes replaced");
43 STATISTIC(NumUnwinds, "Number of unwinds replaced");
44 STATISTIC(NumSpilled, "Number of registers live across unwind edges");
45
46 namespace {
47   class SjLjEHPass : public FunctionPass {
48     const TargetLowering *TLI;
49     Type *FunctionContextTy;
50     Constant *RegisterFn;
51     Constant *UnregisterFn;
52     Constant *BuiltinSetjmpFn;
53     Constant *FrameAddrFn;
54     Constant *StackAddrFn;
55     Constant *StackRestoreFn;
56     Constant *LSDAAddrFn;
57     Value *PersonalityFn;
58     Constant *SelectorFn;
59     Constant *ExceptionFn;
60     Constant *CallSiteFn;
61     Constant *DispatchSetupFn;
62     Constant *FuncCtxFn;
63     Value *CallSite;
64     DenseMap<InvokeInst*, BasicBlock*> LPadSuccMap;
65   public:
66     static char ID; // Pass identification, replacement for typeid
67     explicit SjLjEHPass(const TargetLowering *tli = NULL)
68       : FunctionPass(ID), TLI(tli) { }
69     bool doInitialization(Module &M);
70     bool runOnFunction(Function &F);
71
72     virtual void getAnalysisUsage(AnalysisUsage &AU) const {}
73     const char *getPassName() const {
74       return "SJLJ Exception Handling preparation";
75     }
76
77   private:
78     bool setupEntryBlockAndCallSites(Function &F);
79     Value *setupFunctionContext(Function &F, ArrayRef<LandingPadInst*> LPads);
80     void lowerIncomingArguments(Function &F);
81     void lowerAcrossUnwindEdges(Function &F, ArrayRef<InvokeInst*> Invokes);
82
83     void insertCallSiteStore(Instruction *I, int Number, Value *CallSite);
84     void markInvokeCallSite(InvokeInst *II, int InvokeNo, Value *CallSite,
85                             SwitchInst *CatchSwitch);
86     void splitLiveRangesAcrossInvokes(SmallVector<InvokeInst*,16> &Invokes);
87     void splitLandingPad(InvokeInst *II);
88     bool insertSjLjEHSupport(Function &F);
89   };
90 } // end anonymous namespace
91
92 char SjLjEHPass::ID = 0;
93
94 // Public Interface To the SjLjEHPass pass.
95 FunctionPass *llvm::createSjLjEHPass(const TargetLowering *TLI) {
96   return new SjLjEHPass(TLI);
97 }
98 // doInitialization - Set up decalarations and types needed to process
99 // exceptions.
100 bool SjLjEHPass::doInitialization(Module &M) {
101   // Build the function context structure.
102   // builtin_setjmp uses a five word jbuf
103   Type *VoidPtrTy = Type::getInt8PtrTy(M.getContext());
104   Type *Int32Ty = Type::getInt32Ty(M.getContext());
105   FunctionContextTy =
106     StructType::get(VoidPtrTy,                        // __prev
107                     Int32Ty,                          // call_site
108                     ArrayType::get(Int32Ty, 4),       // __data
109                     VoidPtrTy,                        // __personality
110                     VoidPtrTy,                        // __lsda
111                     ArrayType::get(VoidPtrTy, 5),     // __jbuf
112                     NULL);
113   RegisterFn = M.getOrInsertFunction("_Unwind_SjLj_Register",
114                                      Type::getVoidTy(M.getContext()),
115                                      PointerType::getUnqual(FunctionContextTy),
116                                      (Type *)0);
117   UnregisterFn =
118     M.getOrInsertFunction("_Unwind_SjLj_Unregister",
119                           Type::getVoidTy(M.getContext()),
120                           PointerType::getUnqual(FunctionContextTy),
121                           (Type *)0);
122   FrameAddrFn = Intrinsic::getDeclaration(&M, Intrinsic::frameaddress);
123   StackAddrFn = Intrinsic::getDeclaration(&M, Intrinsic::stacksave);
124   StackRestoreFn = Intrinsic::getDeclaration(&M, Intrinsic::stackrestore);
125   BuiltinSetjmpFn = Intrinsic::getDeclaration(&M, Intrinsic::eh_sjlj_setjmp);
126   LSDAAddrFn = Intrinsic::getDeclaration(&M, Intrinsic::eh_sjlj_lsda);
127   SelectorFn = Intrinsic::getDeclaration(&M, Intrinsic::eh_selector);
128   ExceptionFn = Intrinsic::getDeclaration(&M, Intrinsic::eh_exception);
129   CallSiteFn = Intrinsic::getDeclaration(&M, Intrinsic::eh_sjlj_callsite);
130   DispatchSetupFn
131     = Intrinsic::getDeclaration(&M, Intrinsic::eh_sjlj_dispatch_setup);
132   FuncCtxFn = Intrinsic::getDeclaration(&M, Intrinsic::eh_sjlj_functioncontext);
133   PersonalityFn = 0;
134
135   return true;
136 }
137
138 /// insertCallSiteStore - Insert a store of the call-site value to the
139 /// function context
140 void SjLjEHPass::insertCallSiteStore(Instruction *I, int Number,
141                                      Value *CallSite) {
142   ConstantInt *CallSiteNoC = ConstantInt::get(Type::getInt32Ty(I->getContext()),
143                                               Number);
144   // Insert a store of the call-site number
145   new StoreInst(CallSiteNoC, CallSite, true, I);  // volatile
146 }
147
148 /// splitLandingPad - Split a landing pad. This takes considerable care because
149 /// of PHIs and other nasties. The problem is that the jump table needs to jump
150 /// to the landing pad block. However, the landing pad block can be jumped to
151 /// only by an invoke instruction. So we clone the landingpad instruction into
152 /// its own basic block, have the invoke jump to there. The landingpad
153 /// instruction's basic block's successor is now the target for the jump table.
154 ///
155 /// But because of PHI nodes, we need to create another basic block for the jump
156 /// table to jump to. This is definitely a hack, because the values for the PHI
157 /// nodes may not be defined on the edge from the jump table. But that's okay,
158 /// because the jump table is simply a construct to mimic what is happening in
159 /// the CFG. So the values are mysteriously there, even though there is no value
160 /// for the PHI from the jump table's edge (hence calling this a hack).
161 void SjLjEHPass::splitLandingPad(InvokeInst *II) {
162   SmallVector<BasicBlock*, 2> NewBBs;
163   SplitLandingPadPredecessors(II->getUnwindDest(), II->getParent(),
164                               ".1", ".2", this, NewBBs);
165
166   // Create an empty block so that the jump table has something to jump to
167   // which doesn't have any PHI nodes.
168   BasicBlock *LPad = NewBBs[0];
169   BasicBlock *Succ = *succ_begin(LPad);
170   BasicBlock *JumpTo = BasicBlock::Create(II->getContext(), "jt.land",
171                                           LPad->getParent(), Succ);
172   LPad->getTerminator()->eraseFromParent();
173   BranchInst::Create(JumpTo, LPad);
174   BranchInst::Create(Succ, JumpTo);
175   LPadSuccMap[II] = JumpTo;
176
177   for (BasicBlock::iterator I = Succ->begin(); isa<PHINode>(I); ++I) {
178     PHINode *PN = cast<PHINode>(I);
179     Value *Val = PN->removeIncomingValue(LPad, false);
180     PN->addIncoming(Val, JumpTo);
181   }
182 }
183
184 /// markInvokeCallSite - Insert code to mark the call_site for this invoke
185 void SjLjEHPass::markInvokeCallSite(InvokeInst *II, int InvokeNo,
186                                     Value *CallSite,
187                                     SwitchInst *CatchSwitch) {
188   ConstantInt *CallSiteNoC= ConstantInt::get(Type::getInt32Ty(II->getContext()),
189                                               InvokeNo);
190   // The runtime comes back to the dispatcher with the call_site - 1 in
191   // the context. Odd, but there it is.
192   ConstantInt *SwitchValC = ConstantInt::get(Type::getInt32Ty(II->getContext()),
193                                              InvokeNo - 1);
194
195   // If the unwind edge has phi nodes, split the edge.
196   if (isa<PHINode>(II->getUnwindDest()->begin())) {
197     // FIXME: New EH - This if-condition will be always true in the new scheme.
198     if (II->getUnwindDest()->isLandingPad())
199       splitLandingPad(II);
200     else
201       SplitCriticalEdge(II, 1, this);
202
203     // If there are any phi nodes left, they must have a single predecessor.
204     while (PHINode *PN = dyn_cast<PHINode>(II->getUnwindDest()->begin())) {
205       PN->replaceAllUsesWith(PN->getIncomingValue(0));
206       PN->eraseFromParent();
207     }
208   }
209
210   // Insert the store of the call site value
211   insertCallSiteStore(II, InvokeNo, CallSite);
212
213   // Record the call site value for the back end so it stays associated with
214   // the invoke.
215   CallInst::Create(CallSiteFn, CallSiteNoC, "", II);
216
217   // Add a switch case to our unwind block.
218   if (BasicBlock *SuccBB = LPadSuccMap[II]) {
219     CatchSwitch->addCase(SwitchValC, SuccBB);
220   } else {
221     CatchSwitch->addCase(SwitchValC, II->getUnwindDest());
222   }
223
224   // We still want this to look like an invoke so we emit the LSDA properly,
225   // so we don't transform the invoke into a call here.
226 }
227
228 /// MarkBlocksLiveIn - Insert BB and all of its predescessors into LiveBBs until
229 /// we reach blocks we've already seen.
230 static void MarkBlocksLiveIn(BasicBlock *BB, std::set<BasicBlock*> &LiveBBs) {
231   if (!LiveBBs.insert(BB).second) return; // already been here.
232
233   for (pred_iterator PI = pred_begin(BB), E = pred_end(BB); PI != E; ++PI)
234     MarkBlocksLiveIn(*PI, LiveBBs);
235 }
236
237 /// splitLiveRangesAcrossInvokes - Each value that is live across an unwind edge
238 /// we spill into a stack location, guaranteeing that there is nothing live
239 /// across the unwind edge.  This process also splits all critical edges
240 /// coming out of invoke's.
241 /// FIXME: Move this function to a common utility file (Local.cpp?) so
242 /// both SjLj and LowerInvoke can use it.
243 void SjLjEHPass::
244 splitLiveRangesAcrossInvokes(SmallVector<InvokeInst*,16> &Invokes) {
245   // First step, split all critical edges from invoke instructions.
246   for (unsigned i = 0, e = Invokes.size(); i != e; ++i) {
247     InvokeInst *II = Invokes[i];
248     SplitCriticalEdge(II, 0, this);
249
250     // FIXME: New EH - This if-condition will be always true in the new scheme.
251     if (II->getUnwindDest()->isLandingPad())
252       splitLandingPad(II);
253     else
254       SplitCriticalEdge(II, 1, this);
255
256     assert(!isa<PHINode>(II->getNormalDest()) &&
257            !isa<PHINode>(II->getUnwindDest()) &&
258            "Critical edge splitting left single entry phi nodes?");
259   }
260
261   Function *F = Invokes.back()->getParent()->getParent();
262
263   // To avoid having to handle incoming arguments specially, we lower each arg
264   // to a copy instruction in the entry block.  This ensures that the argument
265   // value itself cannot be live across the entry block.
266   BasicBlock::iterator AfterAllocaInsertPt = F->begin()->begin();
267   while (isa<AllocaInst>(AfterAllocaInsertPt) &&
268         isa<ConstantInt>(cast<AllocaInst>(AfterAllocaInsertPt)->getArraySize()))
269     ++AfterAllocaInsertPt;
270   for (Function::arg_iterator AI = F->arg_begin(), E = F->arg_end();
271        AI != E; ++AI) {
272     Type *Ty = AI->getType();
273     // Aggregate types can't be cast, but are legal argument types, so we have
274     // to handle them differently. We use an extract/insert pair as a
275     // lightweight method to achieve the same goal.
276     if (isa<StructType>(Ty) || isa<ArrayType>(Ty) || isa<VectorType>(Ty)) {
277       Instruction *EI = ExtractValueInst::Create(AI, 0, "",AfterAllocaInsertPt);
278       Instruction *NI = InsertValueInst::Create(AI, EI, 0);
279       NI->insertAfter(EI);
280       AI->replaceAllUsesWith(NI);
281       // Set the operand of the instructions back to the AllocaInst.
282       EI->setOperand(0, AI);
283       NI->setOperand(0, AI);
284     } else {
285       // This is always a no-op cast because we're casting AI to AI->getType()
286       // so src and destination types are identical. BitCast is the only
287       // possibility.
288       CastInst *NC = new BitCastInst(
289         AI, AI->getType(), AI->getName()+".tmp", AfterAllocaInsertPt);
290       AI->replaceAllUsesWith(NC);
291       // Set the operand of the cast instruction back to the AllocaInst.
292       // Normally it's forbidden to replace a CastInst's operand because it
293       // could cause the opcode to reflect an illegal conversion. However,
294       // we're replacing it here with the same value it was constructed with.
295       // We do this because the above replaceAllUsesWith() clobbered the
296       // operand, but we want this one to remain.
297       NC->setOperand(0, AI);
298     }
299   }
300
301   // Finally, scan the code looking for instructions with bad live ranges.
302   for (Function::iterator BB = F->begin(), E = F->end(); BB != E; ++BB)
303     for (BasicBlock::iterator II = BB->begin(), E = BB->end(); II != E; ++II) {
304       // Ignore obvious cases we don't have to handle.  In particular, most
305       // instructions either have no uses or only have a single use inside the
306       // current block.  Ignore them quickly.
307       Instruction *Inst = II;
308       if (Inst->use_empty()) continue;
309       if (Inst->hasOneUse() &&
310           cast<Instruction>(Inst->use_back())->getParent() == BB &&
311           !isa<PHINode>(Inst->use_back())) continue;
312
313       // If this is an alloca in the entry block, it's not a real register
314       // value.
315       if (AllocaInst *AI = dyn_cast<AllocaInst>(Inst))
316         if (isa<ConstantInt>(AI->getArraySize()) && BB == F->begin())
317           continue;
318
319       // Avoid iterator invalidation by copying users to a temporary vector.
320       SmallVector<Instruction*,16> Users;
321       for (Value::use_iterator UI = Inst->use_begin(), E = Inst->use_end();
322            UI != E; ++UI) {
323         Instruction *User = cast<Instruction>(*UI);
324         if (User->getParent() != BB || isa<PHINode>(User))
325           Users.push_back(User);
326       }
327
328       // Find all of the blocks that this value is live in.
329       std::set<BasicBlock*> LiveBBs;
330       LiveBBs.insert(Inst->getParent());
331       while (!Users.empty()) {
332         Instruction *U = Users.back();
333         Users.pop_back();
334
335         if (!isa<PHINode>(U)) {
336           MarkBlocksLiveIn(U->getParent(), LiveBBs);
337         } else {
338           // Uses for a PHI node occur in their predecessor block.
339           PHINode *PN = cast<PHINode>(U);
340           for (unsigned i = 0, e = PN->getNumIncomingValues(); i != e; ++i)
341             if (PN->getIncomingValue(i) == Inst)
342               MarkBlocksLiveIn(PN->getIncomingBlock(i), LiveBBs);
343         }
344       }
345
346       // Now that we know all of the blocks that this thing is live in, see if
347       // it includes any of the unwind locations.
348       bool NeedsSpill = false;
349       for (unsigned i = 0, e = Invokes.size(); i != e; ++i) {
350         BasicBlock *UnwindBlock = Invokes[i]->getUnwindDest();
351         if (UnwindBlock != BB && LiveBBs.count(UnwindBlock))
352           NeedsSpill = true;
353       }
354
355       // If we decided we need a spill, do it.
356       // FIXME: Spilling this way is overkill, as it forces all uses of
357       // the value to be reloaded from the stack slot, even those that aren't
358       // in the unwind blocks. We should be more selective.
359       if (NeedsSpill) {
360         ++NumSpilled;
361         DemoteRegToStack(*Inst, true);
362       }
363     }
364 }
365
366 /// CreateLandingPadLoad - Load the exception handling values and insert them
367 /// into a structure.
368 static Instruction *CreateLandingPadLoad(Function &F, Value *ExnAddr,
369                                          Value *SelAddr,
370                                          BasicBlock::iterator InsertPt) {
371   Value *Exn = new LoadInst(ExnAddr, "exn", false,
372                             InsertPt);
373   Type *Ty = Type::getInt8PtrTy(F.getContext());
374   Exn = CastInst::Create(Instruction::IntToPtr, Exn, Ty, "", InsertPt);
375   Value *Sel = new LoadInst(SelAddr, "sel", false, InsertPt);
376
377   Ty = StructType::get(Exn->getType(), Sel->getType(), NULL);
378   InsertValueInst *LPadVal = InsertValueInst::Create(llvm::UndefValue::get(Ty),
379                                                      Exn, 0,
380                                                      "lpad.val", InsertPt);
381   return InsertValueInst::Create(LPadVal, Sel, 1, "lpad.val", InsertPt);
382 }
383
384 /// ReplaceLandingPadVal - Replace the landingpad instruction's value with a
385 /// load from the stored values (via CreateLandingPadLoad). This looks through
386 /// PHI nodes, and removes them if they are dead.
387 static void ReplaceLandingPadVal(Function &F, Instruction *Inst, Value *ExnAddr,
388                                  Value *SelAddr) {
389   if (Inst->use_empty()) return;
390
391   while (!Inst->use_empty()) {
392     Instruction *I = cast<Instruction>(Inst->use_back());
393
394     if (PHINode *PN = dyn_cast<PHINode>(I)) {
395       ReplaceLandingPadVal(F, PN, ExnAddr, SelAddr);
396       if (PN->use_empty()) PN->eraseFromParent();
397       continue;
398     }
399
400     I->replaceUsesOfWith(Inst, CreateLandingPadLoad(F, ExnAddr, SelAddr, I));
401   }
402 }
403
404 bool SjLjEHPass::insertSjLjEHSupport(Function &F) {
405   SmallVector<ReturnInst*,16> Returns;
406   SmallVector<UnwindInst*,16> Unwinds;
407   SmallVector<InvokeInst*,16> Invokes;
408
409   // Look through the terminators of the basic blocks to find invokes, returns
410   // and unwinds.
411   for (Function::iterator BB = F.begin(), E = F.end(); BB != E; ++BB) {
412     if (ReturnInst *RI = dyn_cast<ReturnInst>(BB->getTerminator())) {
413       // Remember all return instructions in case we insert an invoke into this
414       // function.
415       Returns.push_back(RI);
416     } else if (InvokeInst *II = dyn_cast<InvokeInst>(BB->getTerminator())) {
417       Invokes.push_back(II);
418     } else if (UnwindInst *UI = dyn_cast<UnwindInst>(BB->getTerminator())) {
419       Unwinds.push_back(UI);
420     }
421   }
422
423   NumInvokes += Invokes.size();
424   NumUnwinds += Unwinds.size();
425
426   // If we don't have any invokes, there's nothing to do.
427   if (Invokes.empty()) return false;
428
429   // Find the eh.selector.*, eh.exception and alloca calls.
430   //
431   // Remember any allocas() that aren't in the entry block, as the
432   // jmpbuf saved SP will need to be updated for them.
433   //
434   // We'll use the first eh.selector to determine the right personality
435   // function to use. For SJLJ, we always use the same personality for the
436   // whole function, not on a per-selector basis.
437   // FIXME: That's a bit ugly. Better way?
438   SmallVector<CallInst*,16> EH_Selectors;
439   SmallVector<CallInst*,16> EH_Exceptions;
440   SmallVector<Instruction*,16> JmpbufUpdatePoints;
441
442   for (Function::iterator BB = F.begin(), E = F.end(); BB != E; ++BB) {
443     // Note: Skip the entry block since there's nothing there that interests
444     // us. eh.selector and eh.exception shouldn't ever be there, and we
445     // want to disregard any allocas that are there.
446     // 
447     // FIXME: This is awkward. The new EH scheme won't need to skip the entry
448     //        block.
449     if (BB == F.begin()) {
450       if (InvokeInst *II = dyn_cast<InvokeInst>(F.begin()->getTerminator())) {
451         // FIXME: This will be always non-NULL in the new EH.
452         if (LandingPadInst *LPI = II->getUnwindDest()->getLandingPadInst())
453           if (!PersonalityFn) PersonalityFn = LPI->getPersonalityFn();
454       }
455
456       continue;
457     }
458
459     for (BasicBlock::iterator I = BB->begin(), E = BB->end(); I != E; ++I) {
460       if (CallInst *CI = dyn_cast<CallInst>(I)) {
461         if (CI->getCalledFunction() == SelectorFn) {
462           if (!PersonalityFn) PersonalityFn = CI->getArgOperand(1);
463           EH_Selectors.push_back(CI);
464         } else if (CI->getCalledFunction() == ExceptionFn) {
465           EH_Exceptions.push_back(CI);
466         } else if (CI->getCalledFunction() == StackRestoreFn) {
467           JmpbufUpdatePoints.push_back(CI);
468         }
469       } else if (AllocaInst *AI = dyn_cast<AllocaInst>(I)) {
470         JmpbufUpdatePoints.push_back(AI);
471       } else if (InvokeInst *II = dyn_cast<InvokeInst>(I)) {
472         // FIXME: This will be always non-NULL in the new EH.
473         if (LandingPadInst *LPI = II->getUnwindDest()->getLandingPadInst())
474           if (!PersonalityFn) PersonalityFn = LPI->getPersonalityFn();
475       }
476     }
477   }
478
479   // If we don't have any eh.selector calls, we can't determine the personality
480   // function. Without a personality function, we can't process exceptions.
481   if (!PersonalityFn) return false;
482
483   // We have invokes, so we need to add register/unregister calls to get this
484   // function onto the global unwind stack.
485   //
486   // First thing we need to do is scan the whole function for values that are
487   // live across unwind edges.  Each value that is live across an unwind edge we
488   // spill into a stack location, guaranteeing that there is nothing live across
489   // the unwind edge.  This process also splits all critical edges coming out of
490   // invoke's.
491   splitLiveRangesAcrossInvokes(Invokes);
492
493
494   SmallVector<LandingPadInst*, 16> LandingPads;
495   for (Function::iterator BB = F.begin(), E = F.end(); BB != E; ++BB) {
496     if (InvokeInst *II = dyn_cast<InvokeInst>(BB->getTerminator()))
497       // FIXME: This will be always non-NULL in the new EH.
498       if (LandingPadInst *LPI = II->getUnwindDest()->getLandingPadInst())
499         LandingPads.push_back(LPI);
500   }
501
502
503   BasicBlock *EntryBB = F.begin();
504   // Create an alloca for the incoming jump buffer ptr and the new jump buffer
505   // that needs to be restored on all exits from the function.  This is an
506   // alloca because the value needs to be added to the global context list.
507   unsigned Align = 4; // FIXME: Should be a TLI check?
508   AllocaInst *FunctionContext =
509     new AllocaInst(FunctionContextTy, 0, Align,
510                    "fcn_context", F.begin()->begin());
511
512   Value *Idxs[2];
513   Type *Int32Ty = Type::getInt32Ty(F.getContext());
514   Value *Zero = ConstantInt::get(Int32Ty, 0);
515   // We need to also keep around a reference to the call_site field
516   Idxs[0] = Zero;
517   Idxs[1] = ConstantInt::get(Int32Ty, 1);
518   CallSite = GetElementPtrInst::Create(FunctionContext, Idxs, "call_site",
519                                        EntryBB->getTerminator());
520
521   // The exception selector comes back in context->data[1]
522   Idxs[1] = ConstantInt::get(Int32Ty, 2);
523   Value *FCData = GetElementPtrInst::Create(FunctionContext, Idxs, "fc_data",
524                                             EntryBB->getTerminator());
525   Idxs[1] = ConstantInt::get(Int32Ty, 1);
526   Value *SelectorAddr = GetElementPtrInst::Create(FCData, Idxs,
527                                                   "exc_selector_gep",
528                                                   EntryBB->getTerminator());
529   // The exception value comes back in context->data[0]
530   Idxs[1] = Zero;
531   Value *ExceptionAddr = GetElementPtrInst::Create(FCData, Idxs,
532                                                    "exception_gep",
533                                                    EntryBB->getTerminator());
534
535   // The result of the eh.selector call will be replaced with a a reference to
536   // the selector value returned in the function context. We leave the selector
537   // itself so the EH analysis later can use it.
538   for (int i = 0, e = EH_Selectors.size(); i < e; ++i) {
539     CallInst *I = EH_Selectors[i];
540     Value *SelectorVal = new LoadInst(SelectorAddr, "select_val", true, I);
541     I->replaceAllUsesWith(SelectorVal);
542   }
543
544   // eh.exception calls are replaced with references to the proper location in
545   // the context. Unlike eh.selector, the eh.exception calls are removed
546   // entirely.
547   for (int i = 0, e = EH_Exceptions.size(); i < e; ++i) {
548     CallInst *I = EH_Exceptions[i];
549     // Possible for there to be duplicates, so check to make sure the
550     // instruction hasn't already been removed.
551     if (!I->getParent()) continue;
552     Value *Val = new LoadInst(ExceptionAddr, "exception", true, I);
553     Type *Ty = Type::getInt8PtrTy(F.getContext());
554     Val = CastInst::Create(Instruction::IntToPtr, Val, Ty, "", I);
555
556     I->replaceAllUsesWith(Val);
557     I->eraseFromParent();
558   }
559
560   for (unsigned i = 0, e = LandingPads.size(); i != e; ++i)
561     ReplaceLandingPadVal(F, LandingPads[i], ExceptionAddr, SelectorAddr);
562
563   // The entry block changes to have the eh.sjlj.setjmp, with a conditional
564   // branch to a dispatch block for non-zero returns. If we return normally,
565   // we're not handling an exception and just register the function context and
566   // continue.
567
568   // Create the dispatch block.  The dispatch block is basically a big switch
569   // statement that goes to all of the invoke landing pads.
570   BasicBlock *DispatchBlock =
571     BasicBlock::Create(F.getContext(), "eh.sjlj.setjmp.catch", &F);
572
573   // Insert a load of the callsite in the dispatch block, and a switch on its
574   // value. By default, we issue a trap statement.
575   BasicBlock *TrapBlock =
576     BasicBlock::Create(F.getContext(), "trapbb", &F);
577   CallInst::Create(Intrinsic::getDeclaration(F.getParent(), Intrinsic::trap),
578                    "", TrapBlock);
579   new UnreachableInst(F.getContext(), TrapBlock);
580
581   Value *DispatchLoad = new LoadInst(CallSite, "invoke.num", true,
582                                      DispatchBlock);
583   SwitchInst *DispatchSwitch =
584     SwitchInst::Create(DispatchLoad, TrapBlock, Invokes.size(),
585                        DispatchBlock);
586   // Split the entry block to insert the conditional branch for the setjmp.
587   BasicBlock *ContBlock = EntryBB->splitBasicBlock(EntryBB->getTerminator(),
588                                                    "eh.sjlj.setjmp.cont");
589
590   // Populate the Function Context
591   //   1. LSDA address
592   //   2. Personality function address
593   //   3. jmpbuf (save SP, FP and call eh.sjlj.setjmp)
594
595   // LSDA address
596   Idxs[0] = Zero;
597   Idxs[1] = ConstantInt::get(Int32Ty, 4);
598   Value *LSDAFieldPtr =
599     GetElementPtrInst::Create(FunctionContext, Idxs, "lsda_gep",
600                               EntryBB->getTerminator());
601   Value *LSDA = CallInst::Create(LSDAAddrFn, "lsda_addr",
602                                  EntryBB->getTerminator());
603   new StoreInst(LSDA, LSDAFieldPtr, true, EntryBB->getTerminator());
604
605   Idxs[1] = ConstantInt::get(Int32Ty, 3);
606   Value *PersonalityFieldPtr =
607     GetElementPtrInst::Create(FunctionContext, Idxs, "lsda_gep",
608                               EntryBB->getTerminator());
609   new StoreInst(PersonalityFn, PersonalityFieldPtr, true,
610                 EntryBB->getTerminator());
611
612   // Save the frame pointer.
613   Idxs[1] = ConstantInt::get(Int32Ty, 5);
614   Value *JBufPtr
615     = GetElementPtrInst::Create(FunctionContext, Idxs, "jbuf_gep",
616                                 EntryBB->getTerminator());
617   Idxs[1] = ConstantInt::get(Int32Ty, 0);
618   Value *FramePtr =
619     GetElementPtrInst::Create(JBufPtr, Idxs, "jbuf_fp_gep",
620                               EntryBB->getTerminator());
621
622   Value *Val = CallInst::Create(FrameAddrFn,
623                                 ConstantInt::get(Int32Ty, 0),
624                                 "fp",
625                                 EntryBB->getTerminator());
626   new StoreInst(Val, FramePtr, true, EntryBB->getTerminator());
627
628   // Save the stack pointer.
629   Idxs[1] = ConstantInt::get(Int32Ty, 2);
630   Value *StackPtr =
631     GetElementPtrInst::Create(JBufPtr, Idxs, "jbuf_sp_gep",
632                               EntryBB->getTerminator());
633
634   Val = CallInst::Create(StackAddrFn, "sp", EntryBB->getTerminator());
635   new StoreInst(Val, StackPtr, true, EntryBB->getTerminator());
636
637   // Call the setjmp instrinsic. It fills in the rest of the jmpbuf.
638   Value *SetjmpArg =
639     CastInst::Create(Instruction::BitCast, JBufPtr,
640                      Type::getInt8PtrTy(F.getContext()), "",
641                      EntryBB->getTerminator());
642   Value *DispatchVal = CallInst::Create(BuiltinSetjmpFn, SetjmpArg,
643                                         "",
644                                         EntryBB->getTerminator());
645
646   // Add a call to dispatch_setup after the setjmp call. This is expanded to any
647   // target-specific setup that needs to be done.
648   CallInst::Create(DispatchSetupFn, DispatchVal, "", EntryBB->getTerminator());
649
650   // check the return value of the setjmp. non-zero goes to dispatcher.
651   Value *IsNormal = new ICmpInst(EntryBB->getTerminator(),
652                                  ICmpInst::ICMP_EQ, DispatchVal, Zero,
653                                  "notunwind");
654   // Nuke the uncond branch.
655   EntryBB->getTerminator()->eraseFromParent();
656
657   // Put in a new condbranch in its place.
658   BranchInst::Create(ContBlock, DispatchBlock, IsNormal, EntryBB);
659
660   // Register the function context and make sure it's known to not throw
661   CallInst *Register =
662     CallInst::Create(RegisterFn, FunctionContext, "",
663                      ContBlock->getTerminator());
664   Register->setDoesNotThrow();
665
666   // At this point, we are all set up, update the invoke instructions to mark
667   // their call_site values, and fill in the dispatch switch accordingly.
668   for (unsigned i = 0, e = Invokes.size(); i != e; ++i)
669     markInvokeCallSite(Invokes[i], i+1, CallSite, DispatchSwitch);
670
671   // Mark call instructions that aren't nounwind as no-action (call_site ==
672   // -1). Skip the entry block, as prior to then, no function context has been
673   // created for this function and any unexpected exceptions thrown will go
674   // directly to the caller's context, which is what we want anyway, so no need
675   // to do anything here.
676   for (Function::iterator BB = F.begin(), E = F.end(); ++BB != E;) {
677     for (BasicBlock::iterator I = BB->begin(), end = BB->end(); I != end; ++I)
678       if (CallInst *CI = dyn_cast<CallInst>(I)) {
679         // Ignore calls to the EH builtins (eh.selector, eh.exception)
680         Constant *Callee = CI->getCalledFunction();
681         if (Callee != SelectorFn && Callee != ExceptionFn
682             && !CI->doesNotThrow())
683           insertCallSiteStore(CI, -1, CallSite);
684       } else if (ResumeInst *RI = dyn_cast<ResumeInst>(I)) {
685         insertCallSiteStore(RI, -1, CallSite);
686       }
687   }
688
689   // Replace all unwinds with a branch to the unwind handler.
690   // ??? Should this ever happen with sjlj exceptions?
691   for (unsigned i = 0, e = Unwinds.size(); i != e; ++i) {
692     BranchInst::Create(TrapBlock, Unwinds[i]);
693     Unwinds[i]->eraseFromParent();
694   }
695
696   // Following any allocas not in the entry block, update the saved SP in the
697   // jmpbuf to the new value.
698   for (unsigned i = 0, e = JmpbufUpdatePoints.size(); i != e; ++i) {
699     Instruction *AI = JmpbufUpdatePoints[i];
700     Instruction *StackAddr = CallInst::Create(StackAddrFn, "sp");
701     StackAddr->insertAfter(AI);
702     Instruction *StoreStackAddr = new StoreInst(StackAddr, StackPtr, true);
703     StoreStackAddr->insertAfter(StackAddr);
704   }
705
706   // Finally, for any returns from this function, if this function contains an
707   // invoke, add a call to unregister the function context.
708   for (unsigned i = 0, e = Returns.size(); i != e; ++i)
709     CallInst::Create(UnregisterFn, FunctionContext, "", Returns[i]);
710
711   return true;
712 }
713
714 /// setupFunctionContext - Allocate the function context on the stack and fill
715 /// it with all of the data that we know at this point.
716 Value *SjLjEHPass::
717 setupFunctionContext(Function &F, ArrayRef<LandingPadInst*> LPads) {
718   BasicBlock *EntryBB = F.begin();
719
720   // Create an alloca for the incoming jump buffer ptr and the new jump buffer
721   // that needs to be restored on all exits from the function. This is an alloca
722   // because the value needs to be added to the global context list.
723   unsigned Align =
724     TLI->getTargetData()->getPrefTypeAlignment(FunctionContextTy);
725   AllocaInst *FuncCtx =
726     new AllocaInst(FunctionContextTy, 0, Align, "fn_context", EntryBB->begin());
727
728   // Fill in the function context structure.
729   Value *Idxs[2];
730   Type *Int32Ty = Type::getInt32Ty(F.getContext());
731   Value *Zero = ConstantInt::get(Int32Ty, 0);
732   Value *One = ConstantInt::get(Int32Ty, 1);
733
734   // Keep around a reference to the call_site field.
735   Idxs[0] = Zero;
736   Idxs[1] = One;
737   CallSite = GetElementPtrInst::Create(FuncCtx, Idxs, "call_site",
738                                        EntryBB->getTerminator());
739
740   // Reference the __data field.
741   Idxs[1] = ConstantInt::get(Int32Ty, 2);
742   Value *FCData = GetElementPtrInst::Create(FuncCtx, Idxs, "__data",
743                                             EntryBB->getTerminator());
744
745   // The exception value comes back in context->__data[0].
746   Idxs[1] = Zero;
747   Value *ExceptionAddr = GetElementPtrInst::Create(FCData, Idxs,
748                                                    "exception_gep",
749                                                    EntryBB->getTerminator());
750
751   // The exception selector comes back in context->__data[1].
752   Idxs[1] = One;
753   Value *SelectorAddr = GetElementPtrInst::Create(FCData, Idxs,
754                                                   "exn_selector_gep",
755                                                   EntryBB->getTerminator());
756
757   for (unsigned I = 0, E = LPads.size(); I != E; ++I) {
758     LandingPadInst *LPI = LPads[I];
759     IRBuilder<> Builder(LPI->getParent()->getFirstInsertionPt());
760
761     Value *ExnVal = Builder.CreateLoad(ExceptionAddr, true, "exn_val");
762     ExnVal = Builder.CreateIntToPtr(ExnVal, Type::getInt8PtrTy(F.getContext()));
763     Value *SelVal = Builder.CreateLoad(SelectorAddr, true, "exn_selector_val");
764
765     Type *LPadType = LPI->getType();
766     Value *LPadVal = UndefValue::get(LPadType);
767     LPadVal = Builder.CreateInsertValue(LPadVal, ExnVal, 0, "lpad.val");
768     LPadVal = Builder.CreateInsertValue(LPadVal, SelVal, 1, "lpad.val");
769
770     LPI->replaceAllUsesWith(LPadVal);
771   }
772
773   // Personality function
774   Idxs[1] = ConstantInt::get(Int32Ty, 3);
775   if (!PersonalityFn)
776     PersonalityFn = LPads[0]->getPersonalityFn();
777   Value *PersonalityFieldPtr =
778     GetElementPtrInst::Create(FuncCtx, Idxs, "pers_fn_gep",
779                               EntryBB->getTerminator());
780   new StoreInst(PersonalityFn, PersonalityFieldPtr, true,
781                 EntryBB->getTerminator());
782
783   // LSDA address
784   Idxs[1] = ConstantInt::get(Int32Ty, 4);
785   Value *LSDAFieldPtr = GetElementPtrInst::Create(FuncCtx, Idxs, "lsda_gep",
786                                                   EntryBB->getTerminator());
787   Value *LSDA = CallInst::Create(LSDAAddrFn, "lsda_addr",
788                                  EntryBB->getTerminator());
789   new StoreInst(LSDA, LSDAFieldPtr, true, EntryBB->getTerminator());
790
791   return FuncCtx;
792 }
793
794 /// lowerIncomingArguments - To avoid having to handle incoming arguments
795 /// specially, we lower each arg to a copy instruction in the entry block. This
796 /// ensures that the argument value itself cannot be live out of the entry
797 /// block.
798 void SjLjEHPass::lowerIncomingArguments(Function &F) {
799   BasicBlock::iterator AfterAllocaInsPt = F.begin()->begin();
800   while (isa<AllocaInst>(AfterAllocaInsPt) &&
801          isa<ConstantInt>(cast<AllocaInst>(AfterAllocaInsPt)->getArraySize()))
802     ++AfterAllocaInsPt;
803
804   for (Function::arg_iterator
805          AI = F.arg_begin(), AE = F.arg_end(); AI != AE; ++AI) {
806     Type *Ty = AI->getType();
807
808     // Aggregate types can't be cast, but are legal argument types, so we have
809     // to handle them differently. We use an extract/insert pair as a
810     // lightweight method to achieve the same goal.
811     if (isa<StructType>(Ty) || isa<ArrayType>(Ty) || isa<VectorType>(Ty)) {
812       Instruction *EI = ExtractValueInst::Create(AI, 0, "", AfterAllocaInsPt);
813       Instruction *NI = InsertValueInst::Create(AI, EI, 0);
814       NI->insertAfter(EI);
815       AI->replaceAllUsesWith(NI);
816
817       // Set the operand of the instructions back to the AllocaInst.
818       EI->setOperand(0, AI);
819       NI->setOperand(0, AI);
820     } else {
821       // This is always a no-op cast because we're casting AI to AI->getType()
822       // so src and destination types are identical. BitCast is the only
823       // possibility.
824       CastInst *NC =
825         new BitCastInst(AI, AI->getType(), AI->getName() + ".tmp",
826                         AfterAllocaInsPt);
827       AI->replaceAllUsesWith(NC);
828
829       // Set the operand of the cast instruction back to the AllocaInst.
830       // Normally it's forbidden to replace a CastInst's operand because it
831       // could cause the opcode to reflect an illegal conversion. However, we're
832       // replacing it here with the same value it was constructed with.  We do
833       // this because the above replaceAllUsesWith() clobbered the operand, but
834       // we want this one to remain.
835       NC->setOperand(0, AI);
836     }
837   }
838 }
839
840 /// lowerAcrossUnwindEdges - Find all variables which are alive across an unwind
841 /// edge and spill them.
842 void SjLjEHPass::lowerAcrossUnwindEdges(Function &F,
843                                         ArrayRef<InvokeInst*> Invokes) {
844   // Finally, scan the code looking for instructions with bad live ranges.
845   for (Function::iterator
846          BB = F.begin(), BBE = F.end(); BB != BBE; ++BB) {
847     for (BasicBlock::iterator
848            II = BB->begin(), IIE = BB->end(); II != IIE; ++II) {
849       // Ignore obvious cases we don't have to handle. In particular, most
850       // instructions either have no uses or only have a single use inside the
851       // current block. Ignore them quickly.
852       Instruction *Inst = II;
853       if (Inst->use_empty()) continue;
854       if (Inst->hasOneUse() &&
855           cast<Instruction>(Inst->use_back())->getParent() == BB &&
856           !isa<PHINode>(Inst->use_back())) continue;
857
858       // If this is an alloca in the entry block, it's not a real register
859       // value.
860       if (AllocaInst *AI = dyn_cast<AllocaInst>(Inst))
861         if (isa<ConstantInt>(AI->getArraySize()) && BB == F.begin())
862           continue;
863
864       // Avoid iterator invalidation by copying users to a temporary vector.
865       SmallVector<Instruction*, 16> Users;
866       for (Value::use_iterator
867              UI = Inst->use_begin(), E = Inst->use_end(); UI != E; ++UI) {
868         Instruction *User = cast<Instruction>(*UI);
869         if (User->getParent() != BB || isa<PHINode>(User))
870           Users.push_back(User);
871       }
872
873       // Find all of the blocks that this value is live in.
874       std::set<BasicBlock*> LiveBBs;
875       LiveBBs.insert(Inst->getParent());
876       while (!Users.empty()) {
877         Instruction *U = Users.back();
878         Users.pop_back();
879
880         if (!isa<PHINode>(U)) {
881           MarkBlocksLiveIn(U->getParent(), LiveBBs);
882         } else {
883           // Uses for a PHI node occur in their predecessor block.
884           PHINode *PN = cast<PHINode>(U);
885           for (unsigned i = 0, e = PN->getNumIncomingValues(); i != e; ++i)
886             if (PN->getIncomingValue(i) == Inst)
887               MarkBlocksLiveIn(PN->getIncomingBlock(i), LiveBBs);
888         }
889       }
890
891       // Now that we know all of the blocks that this thing is live in, see if
892       // it includes any of the unwind locations.
893       bool NeedsSpill = false;
894       for (unsigned i = 0, e = Invokes.size(); i != e; ++i) {
895         BasicBlock *UnwindBlock = Invokes[i]->getUnwindDest();
896         if (UnwindBlock != BB && LiveBBs.count(UnwindBlock)) {
897           NeedsSpill = true;
898         }
899       }
900
901       // If we decided we need a spill, do it.
902       // FIXME: Spilling this way is overkill, as it forces all uses of
903       // the value to be reloaded from the stack slot, even those that aren't
904       // in the unwind blocks. We should be more selective.
905       if (NeedsSpill) {
906         ++NumSpilled;
907         DemoteRegToStack(*Inst, true);
908       }
909     }
910   }
911
912   // Go through the landing pads and remove any PHIs there.
913   for (unsigned i = 0, e = Invokes.size(); i != e; ++i) {
914     BasicBlock *UnwindBlock = Invokes[i]->getUnwindDest();
915     LandingPadInst *LPI = UnwindBlock->getLandingPadInst();
916
917     // Place PHIs into a set to avoid invalidating the iterator.
918     SmallPtrSet<PHINode*, 8> PHIsToDemote;
919     for (BasicBlock::iterator
920            PN = UnwindBlock->begin(); isa<PHINode>(PN); ++PN)
921       PHIsToDemote.insert(cast<PHINode>(PN));
922     if (PHIsToDemote.empty()) continue;
923
924     // Demote the PHIs to the stack.
925     for (SmallPtrSet<PHINode*, 8>::iterator
926            I = PHIsToDemote.begin(), E = PHIsToDemote.end(); I != E; ++I)
927       DemotePHIToStack(*I);
928
929     // Move the landingpad instruction back to the top of the landing pad block.
930     LPI->moveBefore(UnwindBlock->begin());
931   }
932 }
933
934 /// setupEntryBlockAndCallSites - Setup the entry block by creating and filling
935 /// the function context and marking the call sites with the appropriate
936 /// values. These values are used by the DWARF EH emitter.
937 bool SjLjEHPass::setupEntryBlockAndCallSites(Function &F) {
938   SmallVector<ReturnInst*,     16> Returns;
939   SmallVector<InvokeInst*,     16> Invokes;
940   SmallVector<LandingPadInst*, 16> LPads;
941
942   // Look through the terminators of the basic blocks to find invokes.
943   for (Function::iterator BB = F.begin(), E = F.end(); BB != E; ++BB)
944     if (InvokeInst *II = dyn_cast<InvokeInst>(BB->getTerminator())) {
945       Invokes.push_back(II);
946       LPads.push_back(II->getUnwindDest()->getLandingPadInst());
947     } else if (ReturnInst *RI = dyn_cast<ReturnInst>(BB->getTerminator())) {
948       Returns.push_back(RI);
949     }
950
951   if (Invokes.empty()) return false;
952
953   lowerIncomingArguments(F);
954   lowerAcrossUnwindEdges(F, Invokes);
955
956   Value *FuncCtx = setupFunctionContext(F, LPads);
957   BasicBlock *EntryBB = F.begin();
958   Type *Int32Ty = Type::getInt32Ty(F.getContext());
959
960   Value *Idxs[2] = {
961     ConstantInt::get(Int32Ty, 0), 0
962   };
963
964   // Get a reference to the jump buffer.
965   Idxs[1] = ConstantInt::get(Int32Ty, 5);
966   Value *JBufPtr = GetElementPtrInst::Create(FuncCtx, Idxs, "jbuf_gep",
967                                              EntryBB->getTerminator());
968
969   // Save the frame pointer.
970   Idxs[1] = ConstantInt::get(Int32Ty, 0);
971   Value *FramePtr = GetElementPtrInst::Create(JBufPtr, Idxs, "jbuf_fp_gep",
972                                               EntryBB->getTerminator());
973
974   Value *Val = CallInst::Create(FrameAddrFn,
975                                 ConstantInt::get(Int32Ty, 0),
976                                 "fp",
977                                 EntryBB->getTerminator());
978   new StoreInst(Val, FramePtr, true, EntryBB->getTerminator());
979
980   // Save the stack pointer.
981   Idxs[1] = ConstantInt::get(Int32Ty, 2);
982   Value *StackPtr = GetElementPtrInst::Create(JBufPtr, Idxs, "jbuf_sp_gep",
983                                               EntryBB->getTerminator());
984
985   Val = CallInst::Create(StackAddrFn, "sp", EntryBB->getTerminator());
986   new StoreInst(Val, StackPtr, true, EntryBB->getTerminator());
987
988   // Call the setjmp instrinsic. It fills in the rest of the jmpbuf.
989   Value *SetjmpArg = CastInst::Create(Instruction::BitCast, JBufPtr,
990                                       Type::getInt8PtrTy(F.getContext()), "",
991                                       EntryBB->getTerminator());
992   CallInst::Create(BuiltinSetjmpFn, SetjmpArg, "", EntryBB->getTerminator());
993
994   // Store a pointer to the function context so that the back-end will know
995   // where to look for it.
996   Value *FuncCtxArg = CastInst::Create(Instruction::BitCast, FuncCtx,
997                                        Type::getInt8PtrTy(F.getContext()), "",
998                                        EntryBB->getTerminator());
999   CallInst::Create(FuncCtxFn, FuncCtxArg, "", EntryBB->getTerminator());
1000
1001   // At this point, we are all set up, update the invoke instructions to mark
1002   // their call_site values.
1003   for (unsigned I = 0, E = Invokes.size(); I != E; ++I) {
1004     insertCallSiteStore(Invokes[I], I + 1, CallSite);
1005
1006     ConstantInt *CallSiteNum =
1007       ConstantInt::get(Type::getInt32Ty(F.getContext()), I + 1);
1008
1009     // Record the call site value for the back end so it stays associated with
1010     // the invoke.
1011     CallInst::Create(CallSiteFn, CallSiteNum, "", Invokes[I]);
1012   }
1013
1014   // Mark call instructions that aren't nounwind as no-action (call_site ==
1015   // -1). Skip the entry block, as prior to then, no function context has been
1016   // created for this function and any unexpected exceptions thrown will go
1017   // directly to the caller's context, which is what we want anyway, so no need
1018   // to do anything here.
1019   for (Function::iterator BB = F.begin(), E = F.end(); ++BB != E;)
1020     for (BasicBlock::iterator I = BB->begin(), end = BB->end(); I != end; ++I)
1021       if (CallInst *CI = dyn_cast<CallInst>(I)) {
1022         if (!CI->doesNotThrow())
1023           insertCallSiteStore(CI, -1, CallSite);
1024       } else if (ResumeInst *RI = dyn_cast<ResumeInst>(I)) {
1025         insertCallSiteStore(RI, -1, CallSite);
1026       }
1027
1028   // Register the function context and make sure it's known to not throw
1029   CallInst *Register = CallInst::Create(RegisterFn, FuncCtx, "",
1030                                         EntryBB->getTerminator());
1031   Register->setDoesNotThrow();
1032
1033   // Finally, for any returns from this function, if this function contains an
1034   // invoke, add a call to unregister the function context.
1035   for (unsigned I = 0, E = Returns.size(); I != E; ++I)
1036     CallInst::Create(UnregisterFn, FuncCtx, "", Returns[I]);
1037
1038   return true;
1039 }
1040
1041 bool SjLjEHPass::runOnFunction(Function &F) {
1042   bool Res = false;
1043   if (!DisableOldSjLjEH)
1044     Res = insertSjLjEHSupport(F);
1045   else
1046     Res = setupEntryBlockAndCallSites(F);
1047   return Res;
1048 }