[llvm] r239433 - [WinEH] Add 32-bit SEH state table emission prototype

Reid Kleckner reid at kleckner.net
Tue Jun 9 14:42:19 PDT 2015


Author: rnk
Date: Tue Jun  9 16:42:19 2015
New Revision: 239433

URL: http://llvm.org/viewvc/llvm-project?rev=239433&view=rev
Log:
[WinEH] Add 32-bit SEH state table emission prototype

This gets all the handler info through to the asm printer and we can
look at the .xdata tables now. I've convinced one small catch-all test
case to work, but other than that, it would be a stretch to say this is
functional.

The state numbering algorithm avoids doing any scope reconstruction as
we do for C++ to simplify the implementation.

Added:
    llvm/trunk/test/CodeGen/X86/seh-safe-div-win32.ll
Modified:
    llvm/trunk/include/llvm/IR/Intrinsics.td
    llvm/trunk/lib/CodeGen/AsmPrinter/WinException.cpp
    llvm/trunk/lib/CodeGen/AsmPrinter/WinException.h
    llvm/trunk/lib/CodeGen/SelectionDAG/FunctionLoweringInfo.cpp
    llvm/trunk/lib/CodeGen/SelectionDAG/SelectionDAGBuilder.cpp
    llvm/trunk/lib/CodeGen/WinEHPrepare.cpp
    llvm/trunk/lib/Target/X86/X86ISelLowering.cpp
    llvm/trunk/lib/Target/X86/X86WinEHState.cpp
    llvm/trunk/test/CodeGen/X86/seh-catch-all.ll
    llvm/trunk/test/CodeGen/X86/win32-eh.ll

Modified: llvm/trunk/include/llvm/IR/Intrinsics.td
URL: http://llvm.org/viewvc/llvm-project/llvm/trunk/include/llvm/IR/Intrinsics.td?rev=239433&r1=239432&r2=239433&view=diff
==============================================================================
--- llvm/trunk/include/llvm/IR/Intrinsics.td (original)
+++ llvm/trunk/include/llvm/IR/Intrinsics.td Tue Jun  9 16:42:19 2015
@@ -428,8 +428,8 @@ def int_eh_endcatch : Intrinsic<[], []>;
 // Represents the list of actions to take when an exception is thrown.
 def int_eh_actions : Intrinsic<[llvm_ptr_ty], [llvm_vararg_ty], []>;
 
-def int_eh_exceptioncode : Intrinsic<[llvm_i32_ty], []>;
-def int_eh_exceptioninfo : Intrinsic<[llvm_ptr_ty], []>;
+def int_eh_exceptioncode : Intrinsic<[llvm_i32_ty], [], [IntrReadMem]>;
+def int_eh_exceptioninfo : Intrinsic<[llvm_ptr_ty], [], [IntrReadMem]>;
 
 // __builtin_unwind_init is an undocumented GCC intrinsic that causes all
 // callee-saved registers to be saved and restored (regardless of whether they

Modified: llvm/trunk/lib/CodeGen/AsmPrinter/WinException.cpp
URL: http://llvm.org/viewvc/llvm-project/llvm/trunk/lib/CodeGen/AsmPrinter/WinException.cpp?rev=239433&r1=239432&r2=239433&view=diff
==============================================================================
--- llvm/trunk/lib/CodeGen/AsmPrinter/WinException.cpp (original)
+++ llvm/trunk/lib/CodeGen/AsmPrinter/WinException.cpp Tue Jun  9 16:42:19 2015
@@ -144,7 +144,7 @@ void WinException::endFunction(const Mac
     if (Per == EHPersonality::MSVC_Win64SEH)
       emitCSpecificHandlerTable();
     else if (Per == EHPersonality::MSVC_X86SEH)
-      emitCSpecificHandlerTable(); // FIXME
+      emitExceptHandlerTable(MF);
     else if (Per == EHPersonality::MSVC_CXX)
       emitCXXFrameHandler3Table(MF);
     else
@@ -541,3 +541,90 @@ void WinException::extendIP2StateTable(c
     }
   }
 }
+
+/// Emit the language-specific data that _except_handler3 and 4 expect. This is
+/// functionally equivalent to the __C_specific_handler table, except it is
+/// indexed by state number instead of IP.
+void WinException::emitExceptHandlerTable(const MachineFunction *MF) {
+  auto &OS = *Asm->OutStreamer;
+
+  // Emit the __ehtable label that we use for llvm.x86.seh.lsda.
+  const Function *F = MF->getFunction();
+  StringRef FLinkageName = GlobalValue::getRealLinkageName(F->getName());
+  MCSymbol *LSDALabel = Asm->OutContext.getOrCreateLSDASymbol(FLinkageName);
+  OS.EmitLabel(LSDALabel);
+
+  const Function *Per = MMI->getPersonality();
+  StringRef PerName = Per->getName();
+  int BaseState = -1;
+  if (PerName == "_except_handler4") {
+    // The LSDA for _except_handler4 starts with this struct, followed by the
+    // scope table:
+    //
+    // struct EH4ScopeTable {
+    //   int32_t GSCookieOffset;
+    //   int32_t GSCookieXOROffset;
+    //   int32_t EHCookieOffset;
+    //   int32_t EHCookieXOROffset;
+    //   ScopeTableEntry ScopeRecord[];
+    // };
+    //
+    // Only the EHCookieOffset field appears to vary, and it appears to be the
+    // offset from the final saved SP value to the retaddr.
+    OS.EmitIntValue(-2, 4);
+    OS.EmitIntValue(0, 4);
+    // FIXME: Calculate.
+    OS.EmitIntValue(9999, 4);
+    OS.EmitIntValue(0, 4);
+    BaseState = -2;
+  }
+
+  // Build a list of pointers to LandingPadInfos and then sort by WinEHState.
+  const std::vector<LandingPadInfo> &PadInfos = MMI->getLandingPads();
+  SmallVector<const LandingPadInfo *, 4> LPads;
+  LPads.reserve((PadInfos.size()));
+  for (const LandingPadInfo &LPInfo : PadInfos)
+    LPads.push_back(&LPInfo);
+  std::sort(LPads.begin(), LPads.end(),
+            [](const LandingPadInfo *L, const LandingPadInfo *R) {
+              return L->WinEHState < R->WinEHState;
+            });
+
+  // For each action in each lpad, emit one of these:
+  // struct ScopeTableEntry {
+  //   int32_t EnclosingLevel;
+  //   int32_t (__cdecl *FilterOrFinally)();
+  //   void *HandlerLabel;
+  // };
+  //
+  // The "outermost" action will use BaseState as its enclosing level. Each
+  // other action will refer to the previous state as its enclosing level.
+  int CurState = 0;
+  for (const LandingPadInfo *LPInfo : LPads) {
+    int EnclosingLevel = BaseState;
+    assert(CurState + LPInfo->SEHHandlers.size() - 1 == LPInfo->WinEHState &&
+           "gaps in the SEH scope table");
+    for (const SEHHandler &Handler : LPInfo->SEHHandlers) {
+      // Emit the filter or finally function pointer, if present. Otherwise,
+      // emit '1' to indicate a catch-all.
+      const MCExpr *FilterOrFinally;
+      if (const Function *F = Handler.FilterOrFinally)
+        FilterOrFinally = create32bitRef(Asm->getSymbol(F));
+      else
+        FilterOrFinally = MCConstantExpr::create(1, Asm->OutContext);
+
+      // Compute the recovery address, which is a block address or null.
+      const BlockAddress *BA = Handler.RecoverBA;
+      const MCExpr *RecoverBBOrNull =
+          create32bitRef(BA ? Asm->GetBlockAddressSymbol(BA) : nullptr);
+
+      OS.EmitIntValue(EnclosingLevel, 4);
+      OS.EmitValue(FilterOrFinally, 4);
+      OS.EmitValue(RecoverBBOrNull, 4);
+
+      // The next state unwinds to this state.
+      EnclosingLevel = CurState;
+      CurState++;
+    }
+  }
+}

Modified: llvm/trunk/lib/CodeGen/AsmPrinter/WinException.h
URL: http://llvm.org/viewvc/llvm-project/llvm/trunk/lib/CodeGen/AsmPrinter/WinException.h?rev=239433&r1=239432&r2=239433&view=diff
==============================================================================
--- llvm/trunk/lib/CodeGen/AsmPrinter/WinException.h (original)
+++ llvm/trunk/lib/CodeGen/AsmPrinter/WinException.h Tue Jun  9 16:42:19 2015
@@ -38,8 +38,15 @@ class WinException : public EHStreamer {
 
   void emitCSpecificHandlerTable();
 
+  /// Emit the EH table data for 32-bit and 64-bit functions using
+  /// the __CxxFrameHandler3 personality.
   void emitCXXFrameHandler3Table(const MachineFunction *MF);
 
+  /// Emit the EH table data for _except_handler3 and _except_handler4
+  /// personality functions. These are only used on 32-bit and do not use CFI
+  /// tables.
+  void emitExceptHandlerTable(const MachineFunction *MF);
+
   void extendIP2StateTable(const MachineFunction *MF, const Function *ParentF,
                            WinEHFuncInfo &FuncInfo);
 

Modified: llvm/trunk/lib/CodeGen/SelectionDAG/FunctionLoweringInfo.cpp
URL: http://llvm.org/viewvc/llvm-project/llvm/trunk/lib/CodeGen/SelectionDAG/FunctionLoweringInfo.cpp?rev=239433&r1=239432&r2=239433&view=diff
==============================================================================
--- llvm/trunk/lib/CodeGen/SelectionDAG/FunctionLoweringInfo.cpp (original)
+++ llvm/trunk/lib/CodeGen/SelectionDAG/FunctionLoweringInfo.cpp Tue Jun  9 16:42:19 2015
@@ -264,15 +264,22 @@ void FunctionLoweringInfo::set(const Fun
   if (!isMSVCEHPersonality(Personality))
     return;
 
-  if (Personality == EHPersonality::MSVC_Win64SEH) {
+  if (Personality == EHPersonality::MSVC_Win64SEH ||
+      Personality == EHPersonality::MSVC_X86SEH) {
     addSEHHandlersForLPads(LPads);
-  } else if (Personality == EHPersonality::MSVC_CXX) {
+  }
+
+  WinEHFuncInfo &EHInfo = MMI.getWinEHFuncInfo(&fn);
+  if (Personality == EHPersonality::MSVC_CXX) {
     const Function *WinEHParentFn = MMI.getWinEHParent(&fn);
-    WinEHFuncInfo &EHInfo = MMI.getWinEHFuncInfo(WinEHParentFn);
     calculateWinCXXEHStateNumbers(WinEHParentFn, EHInfo);
+  }
 
-    // Copy the state numbers to LandingPadInfo for the current function, which
-    // could be a handler or the parent.
+  // Copy the state numbers to LandingPadInfo for the current function, which
+  // could be a handler or the parent. This should happen for 32-bit SEH and
+  // C++ EH.
+  if (Personality == EHPersonality::MSVC_CXX ||
+      Personality == EHPersonality::MSVC_X86SEH) {
     for (const LandingPadInst *LP : LPads) {
       MachineBasicBlock *LPadMBB = MBBMap[LP->getParent()];
       MMI.addWinEHState(LPadMBB, EHInfo.LandingPadStateMap[LP]);

Modified: llvm/trunk/lib/CodeGen/SelectionDAG/SelectionDAGBuilder.cpp
URL: http://llvm.org/viewvc/llvm-project/llvm/trunk/lib/CodeGen/SelectionDAG/SelectionDAGBuilder.cpp?rev=239433&r1=239432&r2=239433&view=diff
==============================================================================
--- llvm/trunk/lib/CodeGen/SelectionDAG/SelectionDAGBuilder.cpp (original)
+++ llvm/trunk/lib/CodeGen/SelectionDAG/SelectionDAGBuilder.cpp Tue Jun  9 16:42:19 2015
@@ -4983,6 +4983,7 @@ SelectionDAGBuilder::visitIntrinsicCall(
     assert(Reg && "cannot get exception code on this platform");
     MVT PtrVT = TLI.getPointerTy();
     const TargetRegisterClass *PtrRC = TLI.getRegClassFor(PtrVT);
+    assert(FuncInfo.MBB->isLandingPad() && "eh.exceptioncode in non-lpad");
     unsigned VReg = FuncInfo.MBB->addLiveIn(Reg, PtrRC);
     SDValue N =
         DAG.getCopyFromReg(DAG.getEntryNode(), getCurSDLoc(), VReg, PtrVT);

Modified: llvm/trunk/lib/CodeGen/WinEHPrepare.cpp
URL: http://llvm.org/viewvc/llvm-project/llvm/trunk/lib/CodeGen/WinEHPrepare.cpp?rev=239433&r1=239432&r2=239433&view=diff
==============================================================================
--- llvm/trunk/lib/CodeGen/WinEHPrepare.cpp (original)
+++ llvm/trunk/lib/CodeGen/WinEHPrepare.cpp Tue Jun  9 16:42:19 2015
@@ -24,6 +24,7 @@
 #include "llvm/ADT/Triple.h"
 #include "llvm/ADT/TinyPtrVector.h"
 #include "llvm/Analysis/LibCallSemantics.h"
+#include "llvm/Analysis/TargetLibraryInfo.h"
 #include "llvm/CodeGen/WinEHFuncInfo.h"
 #include "llvm/IR/Dominators.h"
 #include "llvm/IR/Function.h"
@@ -124,6 +125,7 @@ private:
 
   // All fields are reset by runOnFunction.
   DominatorTree *DT = nullptr;
+  const TargetLibraryInfo *LibInfo = nullptr;
   EHPersonality Personality = EHPersonality::Unknown;
   CatchHandlerMapTy CatchHandlerMap;
   CleanupHandlerMapTy CleanupHandlerMap;
@@ -384,6 +386,7 @@ bool WinEHPrepare::runOnFunction(Functio
     return false;
 
   DT = &getAnalysis<DominatorTreeWrapperPass>().getDomTree();
+  LibInfo = &getAnalysis<TargetLibraryInfoWrapperPass>().getTLI();
 
   // If there were any landing pads, prepareExceptionHandlers will make changes.
   prepareExceptionHandlers(Fn, LPads);
@@ -394,6 +397,7 @@ bool WinEHPrepare::doFinalization(Module
 
 void WinEHPrepare::getAnalysisUsage(AnalysisUsage &AU) const {
   AU.addRequired<DominatorTreeWrapperPass>();
+  AU.addRequired<TargetLibraryInfoWrapperPass>();
 }
 
 static bool isSelectorDispatch(BasicBlock *BB, BasicBlock *&CatchHandler,
@@ -1016,10 +1020,17 @@ bool WinEHPrepare::prepareExceptionHandl
   Builder.CreateCall(FrameEscapeFn, AllocasToEscape);
 
   if (SEHExceptionCodeSlot) {
-    if (SEHExceptionCodeSlot->hasNUses(0))
-      SEHExceptionCodeSlot->eraseFromParent();
-    else if (isAllocaPromotable(SEHExceptionCodeSlot))
+    if (isAllocaPromotable(SEHExceptionCodeSlot)) {
+      SmallPtrSet<BasicBlock *, 4> UserBlocks;
+      for (User *U : SEHExceptionCodeSlot->users()) {
+        if (auto *Inst = dyn_cast<Instruction>(U))
+          UserBlocks.insert(Inst->getParent());
+      }
       PromoteMemToReg(SEHExceptionCodeSlot, *DT);
+      // After the promotion, kill off dead instructions.
+      for (BasicBlock *BB : UserBlocks)
+        SimplifyInstructionsInBlock(BB, LibInfo);
+    }
   }
 
   // Clean up the handler action maps we created for this function
@@ -1029,6 +1040,7 @@ bool WinEHPrepare::prepareExceptionHandl
   CleanupHandlerMap.clear();
   HandlerToParentFP.clear();
   DT = nullptr;
+  LibInfo = nullptr;
   SEHExceptionCodeSlot = nullptr;
   EHBlocks.clear();
   NormalBlocks.clear();
@@ -1143,7 +1155,6 @@ void WinEHPrepare::completeNestedLanding
   ++II;
   // The instruction after the landing pad should now be a call to eh.actions.
   const Instruction *Recover = II;
-  assert(match(Recover, m_Intrinsic<Intrinsic::eh_actions>()));
   const IntrinsicInst *EHActions = cast<IntrinsicInst>(Recover);
 
   // Remap the return target in the nested handler.
@@ -2454,6 +2465,8 @@ void WinEHPrepare::findCleanupHandlers(L
 void llvm::parseEHActions(
     const IntrinsicInst *II,
     SmallVectorImpl<std::unique_ptr<ActionHandler>> &Actions) {
+  assert(II->getIntrinsicID() == Intrinsic::eh_actions &&
+         "attempted to parse non eh.actions intrinsic");
   for (unsigned I = 0, E = II->getNumArgOperands(); I != E;) {
     uint64_t ActionKind =
         cast<ConstantInt>(II->getArgOperand(I))->getZExtValue();
@@ -2766,7 +2779,6 @@ void WinEHNumbering::calculateStateNumbe
     auto *ActionsCall = dyn_cast<IntrinsicInst>(LPI->getNextNode());
     if (!ActionsCall)
       continue;
-    assert(ActionsCall->getIntrinsicID() == Intrinsic::eh_actions);
     parseEHActions(ActionsCall, ActionList);
     if (ActionList.empty())
       continue;

Modified: llvm/trunk/lib/Target/X86/X86ISelLowering.cpp
URL: http://llvm.org/viewvc/llvm-project/llvm/trunk/lib/Target/X86/X86ISelLowering.cpp?rev=239433&r1=239432&r2=239433&view=diff
==============================================================================
--- llvm/trunk/lib/Target/X86/X86ISelLowering.cpp (original)
+++ llvm/trunk/lib/Target/X86/X86ISelLowering.cpp Tue Jun  9 16:42:19 2015
@@ -15506,6 +15506,23 @@ static SDValue LowerINTRINSIC_WO_CHAIN(S
         DAG.getTargetExternalSymbol(Name.data(), VT, X86II::MO_NOPREFIX);
     return DAG.getNode(X86ISD::Wrapper, dl, VT, Result);
   }
+
+  case Intrinsic::eh_exceptioninfo: {
+    // Compute the symbol for the LSDA. We know it'll get emitted later.
+    MachineFunction &MF = DAG.getMachineFunction();
+    SDValue Op1 = Op.getOperand(1);
+    auto *Fn = cast<Function>(cast<GlobalAddressSDNode>(Op1)->getGlobal());
+    MCSymbol *LSDASym = MF.getMMI().getContext().getOrCreateLSDASymbol(
+        GlobalValue::getRealLinkageName(Fn->getName()));
+    StringRef Name = LSDASym->getName();
+    assert(Name.data()[Name.size()] == '\0' && "not null terminated");
+
+    // Generate a simple absolute symbol reference. This intrinsic is only
+    // supported on 32-bit Windows, which isn't PIC.
+    SDValue Result =
+        DAG.getTargetExternalSymbol(Name.data(), VT, X86II::MO_NOPREFIX);
+    return DAG.getNode(X86ISD::Wrapper, dl, VT, Result);
+  }
   }
 }
 

Modified: llvm/trunk/lib/Target/X86/X86WinEHState.cpp
URL: http://llvm.org/viewvc/llvm-project/llvm/trunk/lib/Target/X86/X86WinEHState.cpp?rev=239433&r1=239432&r2=239433&view=diff
==============================================================================
--- llvm/trunk/lib/Target/X86/X86WinEHState.cpp (original)
+++ llvm/trunk/lib/Target/X86/X86WinEHState.cpp Tue Jun  9 16:42:19 2015
@@ -63,9 +63,12 @@ private:
   void linkExceptionRegistration(IRBuilder<> &Builder, Value *Handler);
   void unlinkExceptionRegistration(IRBuilder<> &Builder);
   void addCXXStateStores(Function &F, MachineModuleInfo &MMI);
+  void addSEHStateStores(Function &F, MachineModuleInfo &MMI);
   void addCXXStateStoresToFunclet(Value *ParentRegNode, WinEHFuncInfo &FuncInfo,
                                   Function &F, int BaseState);
   void insertStateNumberStore(Value *ParentRegNode, Instruction *IP, int State);
+  iplist<Instruction>::iterator
+  rewriteExceptionInfoIntrinsics(IntrinsicInst *Intrin);
 
   Value *emitEHLSDA(IRBuilder<> &Builder, Function *F);
 
@@ -171,8 +174,10 @@ bool WinEHStatePass::runOnFunction(Funct
   auto *MMIPtr = getAnalysisIfAvailable<MachineModuleInfo>();
   assert(MMIPtr && "MachineModuleInfo should always be available");
   MachineModuleInfo &MMI = *MMIPtr;
-  if (Personality == EHPersonality::MSVC_CXX) {
-    addCXXStateStores(F, MMI);
+  switch (Personality) {
+  default: llvm_unreachable("unexpected personality function");
+  case EHPersonality::MSVC_CXX:    addCXXStateStores(F, MMI); break;
+  case EHPersonality::MSVC_X86SEH: addSEHStateStores(F, MMI); break;
   }
 
   // Reset per-function state.
@@ -472,6 +477,76 @@ void WinEHStatePass::addCXXStateStoresTo
   }
 }
 
+/// Assign every distinct landingpad a unique state number for SEH. Unlike C++
+/// EH, we can use this very simple algorithm while C++ EH cannot because catch
+/// handlers aren't outlined and the runtime doesn't have to figure out which
+/// catch handler frame to unwind to.
+/// FIXME: __finally blocks are outlined, so this approach may break down there.
+void WinEHStatePass::addSEHStateStores(Function &F, MachineModuleInfo &MMI) {
+  WinEHFuncInfo &FuncInfo = MMI.getWinEHFuncInfo(&F);
+
+  // Iterate all the instructions and emit state number stores.
+  int CurState = 0;
+  for (BasicBlock &BB : F) {
+    for (auto I = BB.begin(), E = BB.end(); I != E; ++I) {
+      if (auto *CI = dyn_cast<CallInst>(I)) {
+        auto *Intrin = dyn_cast<IntrinsicInst>(CI);
+        if (Intrin) {
+          I = rewriteExceptionInfoIntrinsics(Intrin);
+          // Calls that "don't throw" are considered to be able to throw asynch
+          // exceptions, but intrinsics cannot.
+          continue;
+        }
+        insertStateNumberStore(RegNode, CI, -1);
+      } else if (auto *II = dyn_cast<InvokeInst>(I)) {
+        // Look up the state number of the landingpad this unwinds to.
+        LandingPadInst *LPI = II->getUnwindDest()->getLandingPadInst();
+        auto InsertionPair =
+            FuncInfo.LandingPadStateMap.insert(std::make_pair(LPI, 0));
+        auto Iter = InsertionPair.first;
+        int &State = Iter->second;
+        bool Inserted = InsertionPair.second;
+        if (Inserted) {
+          // Each action consumes a state number.
+          auto *EHActions = cast<IntrinsicInst>(LPI->getNextNode());
+          SmallVector<std::unique_ptr<ActionHandler>, 4> ActionList;
+          parseEHActions(EHActions, ActionList);
+          assert(!ActionList.empty());
+          CurState += ActionList.size();
+          State += ActionList.size() - 1;
+        }
+        insertStateNumberStore(RegNode, II, State);
+      }
+    }
+  }
+}
+
+/// Rewrite llvm.eh.exceptioncode and llvm.eh.exceptioninfo to memory loads in
+/// IR.
+iplist<Instruction>::iterator
+WinEHStatePass::rewriteExceptionInfoIntrinsics(IntrinsicInst *Intrin) {
+  Intrinsic::ID ID = Intrin->getIntrinsicID();
+  if (ID != Intrinsic::eh_exceptioncode && ID != Intrinsic::eh_exceptioninfo)
+    return Intrin;
+
+  // RegNode->ExceptionPointers
+  IRBuilder<> Builder(Intrin);
+  Value *Ptrs =
+      Builder.CreateLoad(Builder.CreateStructGEP(RegNodeTy, RegNode, 1));
+  Value *Res;
+  if (ID == Intrinsic::eh_exceptioncode) {
+    // Ptrs->ExceptionRecord->Code
+    Ptrs = Builder.CreateBitCast(
+        Ptrs, Builder.getInt32Ty()->getPointerTo()->getPointerTo());
+    Value *Rec = Builder.CreateLoad(Ptrs);
+    Res = Builder.CreateLoad(Rec);
+  } else {
+    Res = Ptrs;
+  }
+  Intrin->replaceAllUsesWith(Res);
+  return Intrin->eraseFromParent();
+}
+
 void WinEHStatePass::insertStateNumberStore(Value *ParentRegNode,
                                             Instruction *IP, int State) {
   IRBuilder<> Builder(IP);

Modified: llvm/trunk/test/CodeGen/X86/seh-catch-all.ll
URL: http://llvm.org/viewvc/llvm-project/llvm/trunk/test/CodeGen/X86/seh-catch-all.ll?rev=239433&r1=239432&r2=239433&view=diff
==============================================================================
--- llvm/trunk/test/CodeGen/X86/seh-catch-all.ll (original)
+++ llvm/trunk/test/CodeGen/X86/seh-catch-all.ll Tue Jun  9 16:42:19 2015
@@ -1,4 +1,6 @@
-; RUN: llc -mtriple=x86_64-windows-msvc < %s | FileCheck %s
+; RUN: llc -mtriple=x86_64-windows-msvc < %s | FileCheck %s --check-prefix=X64
+; RUN: sed -e 's/__C_specific_handler/_except_handler3/' %s | \
+; RUN:         llc -mtriple=i686-windows-msvc | FileCheck %s --check-prefix=X86
 
 @str = linkonce_odr unnamed_addr constant [27 x i8] c"GetExceptionCode(): 0x%lx\0A\00", align 1
 
@@ -29,16 +31,41 @@ eh.resume:
 
 ; Check that we can get the exception code from eax to the printf.
 
-; CHECK-LABEL: main:
-; CHECK: retq
-; CHECK: # Block address taken
-; CHECK: leaq str(%rip), %rcx
-; CHECK: movl %eax, %edx
-; CHECK: callq printf
-
-; CHECK: .seh_handlerdata
-; CHECK-NEXT: .long 1
-; CHECK-NEXT: .Ltmp{{[0-9]+}}@IMGREL
-; CHECK-NEXT: .Ltmp{{[0-9]+}}@IMGREL+1
-; CHECK-NEXT: 1
-; CHECK-NEXT: .Ltmp{{[0-9]+}}@IMGREL
+; X64-LABEL: main:
+; X64: callq crash
+; X64: retq
+; X64: # Block address taken
+; X64: leaq str(%rip), %rcx
+; X64: movl %eax, %edx
+; X64: callq printf
+
+; X64: .seh_handlerdata
+; X64-NEXT: .long 1
+; X64-NEXT: .long .Ltmp{{[0-9]+}}@IMGREL
+; X64-NEXT: .long .Ltmp{{[0-9]+}}@IMGREL+1
+; X64-NEXT: .long 1
+; X64-NEXT: .long .Ltmp{{[0-9]+}}@IMGREL
+
+; X86-LABEL: _main:
+; 	The EH code load should be this offset +4.
+; X86: movl %esp, -24(%ebp)
+; X86: movl $L__ehtable$main,
+; 	EH state 0
+; X86: movl $0, -4(%ebp)
+; X86: calll _crash
+; X86: retl
+; X86: # Block address taken
+; X86: movl -20(%ebp), %[[ptrs:[^ ,]*]]
+; X86: movl (%[[ptrs]]), %[[rec:[^ ,]*]]
+; X86: movl (%[[rec]]), %[[code:[^ ,]*]]
+; 	EH state -1
+; X86: movl $-1, -4(%ebp)
+; X86-DAG: movl %[[code]], 4(%esp)
+; X86-DAG: movl $_str, (%esp)
+; X86: calll _printf
+
+; X86: .section .xdata,"dr"
+; X86-NEXT: L__ehtable$main
+; X86-NEXT: .long -1
+; X86-NEXT: .long 1
+; X86-NEXT: .long Ltmp{{[0-9]+}}

Added: llvm/trunk/test/CodeGen/X86/seh-safe-div-win32.ll
URL: http://llvm.org/viewvc/llvm-project/llvm/trunk/test/CodeGen/X86/seh-safe-div-win32.ll?rev=239433&view=auto
==============================================================================
--- llvm/trunk/test/CodeGen/X86/seh-safe-div-win32.ll (added)
+++ llvm/trunk/test/CodeGen/X86/seh-safe-div-win32.ll Tue Jun  9 16:42:19 2015
@@ -0,0 +1,168 @@
+; RUN: llc -mtriple i686-pc-windows-msvc < %s | FileCheck %s
+
+; This test case is also intended to be run manually as a complete functional
+; test. It should link, print something, and exit zero rather than crashing.
+; It is the hypothetical lowering of a C source program that looks like:
+;
+;   int safe_div(int *n, int *d) {
+;     int r;
+;     __try {
+;       __try {
+;         r = *n / *d;
+;       } __except(GetExceptionCode() == EXCEPTION_ACCESS_VIOLATION) {
+;         puts("EXCEPTION_ACCESS_VIOLATION");
+;         r = -1;
+;       }
+;     } __except(GetExceptionCode() == EXCEPTION_INT_DIVIDE_BY_ZERO) {
+;       puts("EXCEPTION_INT_DIVIDE_BY_ZERO");
+;       r = -2;
+;     }
+;     return r;
+;   }
+
+ at str1 = internal constant [27 x i8] c"EXCEPTION_ACCESS_VIOLATION\00"
+ at str2 = internal constant [29 x i8] c"EXCEPTION_INT_DIVIDE_BY_ZERO\00"
+
+define i32 @safe_div(i32* %n, i32* %d) {
+entry:
+  %r = alloca i32, align 4
+  store i32 42, i32* %r
+  invoke void @try_body(i32* %r, i32* %n, i32* %d)
+          to label %__try.cont unwind label %lpad
+
+lpad:
+  %vals = landingpad { i8*, i32 } personality i8* bitcast (i32 (...)* @_except_handler3 to i8*)
+          catch i8* bitcast (i32 ()* @safe_div_filt0 to i8*)
+          catch i8* bitcast (i32 ()* @safe_div_filt1 to i8*)
+  %ehptr = extractvalue { i8*, i32 } %vals, 0
+  %sel = extractvalue { i8*, i32 } %vals, 1
+  %filt0_val = call i32 @llvm.eh.typeid.for(i8* bitcast (i32 ()* @safe_div_filt0 to i8*))
+  %is_filt0 = icmp eq i32 %sel, %filt0_val
+  br i1 %is_filt0, label %handler0, label %eh.dispatch1
+
+eh.dispatch1:
+  %filt1_val = call i32 @llvm.eh.typeid.for(i8* bitcast (i32 ()* @safe_div_filt1 to i8*))
+  %is_filt1 = icmp eq i32 %sel, %filt1_val
+  br i1 %is_filt1, label %handler1, label %eh.resume
+
+handler0:
+  call void @puts(i8* getelementptr ([27 x i8], [27 x i8]* @str1, i32 0, i32 0))
+  store i32 -1, i32* %r, align 4
+  br label %__try.cont
+
+handler1:
+  call void @puts(i8* getelementptr ([29 x i8], [29 x i8]* @str2, i32 0, i32 0))
+  store i32 -2, i32* %r, align 4
+  br label %__try.cont
+
+eh.resume:
+  resume { i8*, i32 } %vals
+
+__try.cont:
+  %safe_ret = load i32, i32* %r, align 4
+  ret i32 %safe_ret
+}
+
+; Normal path code
+
+; CHECK: {{^}}_safe_div:
+; CHECK: movl $42, [[rloc:.*\(%ebp\)]]
+; CHECK: leal [[rloc]],
+; CHECK: calll _try_body
+; CHECK: [[cont_bb:LBB0_[0-9]+]]:
+; CHECK: movl [[rloc]], %eax
+; CHECK: retl
+
+; Landing pad code
+
+; CHECK: [[handler0:Ltmp[0-9]+]]: # Block address taken
+; CHECK: # %handler0
+; CHECK: calll _puts
+; CHECK: jmp [[cont_bb]]
+
+; CHECK: [[handler1:Ltmp[0-9]+]]: # Block address taken
+; CHECK: # %handler1
+; CHECK: calll _puts
+; CHECK: jmp [[cont_bb]]
+
+; CHECK: .section .xdata,"dr"
+; CHECK-NEXT: L__ehtable$safe_div:
+; CHECK-NEXT: .long -1
+; CHECK-NEXT: .long _safe_div_filt0
+; CHECK-NEXT: .long [[handler0]]
+; CHECK-NEXT: .long 0
+; CHECK-NEXT: .long _safe_div_filt1
+; CHECK-NEXT: .long [[handler1]]
+
+define void @try_body(i32* %r, i32* %n, i32* %d) {
+entry:
+  %0 = load i32, i32* %n, align 4
+  %1 = load i32, i32* %d, align 4
+  %div = sdiv i32 %0, %1
+  store i32 %div, i32* %r, align 4
+  ret void
+}
+
+; The prototype of these filter functions is:
+; int filter(EXCEPTION_POINTERS *eh_ptrs, void *rbp);
+
+; The definition of EXCEPTION_POINTERS is:
+;   typedef struct _EXCEPTION_POINTERS {
+;     EXCEPTION_RECORD *ExceptionRecord;
+;     CONTEXT          *ContextRecord;
+;   } EXCEPTION_POINTERS;
+
+; The definition of EXCEPTION_RECORD is:
+;   typedef struct _EXCEPTION_RECORD {
+;     DWORD ExceptionCode;
+;     ...
+;   } EXCEPTION_RECORD;
+
+; FIXME: Use llvm.eh.exceptioninfo for this.
+declare i32 @safe_div_filt0()
+declare i32 @safe_div_filt1()
+; define i32 @safe_div_filt0() {
+;   %eh_ptrs_c = bitcast i8* %eh_ptrs to i32**
+;   %eh_rec = load i32*, i32** %eh_ptrs_c
+;   %eh_code = load i32, i32* %eh_rec
+;   ; EXCEPTION_ACCESS_VIOLATION = 0xC0000005
+;   %cmp = icmp eq i32 %eh_code, 3221225477
+;   %filt.res = zext i1 %cmp to i32
+;   ret i32 %filt.res
+; }
+; define i32 @safe_div_filt1() {
+;   %eh_ptrs_c = bitcast i8* %eh_ptrs to i32**
+;   %eh_rec = load i32*, i32** %eh_ptrs_c
+;   %eh_code = load i32, i32* %eh_rec
+;   ; EXCEPTION_INT_DIVIDE_BY_ZERO = 0xC0000094
+;   %cmp = icmp eq i32 %eh_code, 3221225620
+;   %filt.res = zext i1 %cmp to i32
+;   ret i32 %filt.res
+; }
+
+ at str_result = internal constant [21 x i8] c"safe_div result: %d\0A\00"
+
+define i32 @main() {
+  %d.addr = alloca i32, align 4
+  %n.addr = alloca i32, align 4
+
+  store i32 10, i32* %n.addr, align 4
+  store i32 2, i32* %d.addr, align 4
+  %r1 = call i32 @safe_div(i32* %n.addr, i32* %d.addr)
+  call void (i8*, ...) @printf(i8* getelementptr ([21 x i8], [21 x i8]* @str_result, i32 0, i32 0), i32 %r1)
+
+  store i32 10, i32* %n.addr, align 4
+  store i32 0, i32* %d.addr, align 4
+  %r2 = call i32 @safe_div(i32* %n.addr, i32* %d.addr)
+  call void (i8*, ...) @printf(i8* getelementptr ([21 x i8], [21 x i8]* @str_result, i32 0, i32 0), i32 %r2)
+
+  %r3 = call i32 @safe_div(i32* %n.addr, i32* null)
+  call void (i8*, ...) @printf(i8* getelementptr ([21 x i8], [21 x i8]* @str_result, i32 0, i32 0), i32 %r3)
+  ret i32 0
+}
+
+declare i32 @_except_handler3(...)
+declare i32 @llvm.eh.typeid.for(i8*) readnone nounwind
+declare void @puts(i8*)
+declare void @printf(i8*, ...)
+declare void @abort()

Modified: llvm/trunk/test/CodeGen/X86/win32-eh.ll
URL: http://llvm.org/viewvc/llvm-project/llvm/trunk/test/CodeGen/X86/win32-eh.ll?rev=239433&r1=239432&r2=239433&view=diff
==============================================================================
--- llvm/trunk/test/CodeGen/X86/win32-eh.ll (original)
+++ llvm/trunk/test/CodeGen/X86/win32-eh.ll Tue Jun  9 16:42:19 2015
@@ -34,6 +34,12 @@ catchall:
 ; CHECK: movl %[[next]], %fs:0
 ; CHECK: retl
 
+; CHECK: .section .xdata,"dr"
+; CHECK-LABEL: L__ehtable$use_except_handler3:
+; CHECK-NEXT:  .long   -1
+; CHECK-NEXT:  .long   1
+; CHECK-NEXT:  .long   Ltmp{{[0-9]+}}
+
 define void @use_except_handler4() {
   invoke void @may_throw_or_crash()
       to label %cont unwind label %catchall
@@ -64,6 +70,16 @@ catchall:
 ; CHECK: movl %[[next]], %fs:0
 ; CHECK: retl
 
+; CHECK: .section .xdata,"dr"
+; CHECK-LABEL: L__ehtable$use_except_handler4:
+; CHECK-NEXT:  .long   -2
+; CHECK-NEXT:  .long   0
+; CHECK-NEXT:  .long   9999
+; CHECK-NEXT:  .long   0
+; CHECK-NEXT:  .long   -2
+; CHECK-NEXT:  .long   1
+; CHECK-NEXT:  .long   Ltmp{{[0-9]+}}
+
 define void @use_CxxFrameHandler3() {
   invoke void @may_throw_or_crash()
       to label %cont unwind label %catchall





More information about the llvm-commits mailing list