Skip to content
Snippets Groups Projects

Stack unwinding (#18163)

Closed Sven Tennie requested to merge wip/stack-unwinding into master

This MR enables GHC to provide backtraces/stacktraces by using the Info Table Provenance Entry Table (IPE table). For this neither DWARF nor profiling support is used.

The basic idea is:

  • The IPE table provides a map from Info Table pointers (addresses) to a descriptive source locations
  • GHC emits an IPE for every return frame at compile time
  • To get a stacktrace:
    • Clone the stack (to avoid concurrent modification issues)
    • Traverse the cloned stack and lookup the IPE for every return frame's info table (pointer)

The best entry to this MR is the user facing API: libraries/base/GHC/Stack/CloneStack.hs

A Quick Summary of the API

libraries/base/GHC/Stack/CloneStack.hs reduced to the most important type signatures:

-- | A frozen snapshot of the state of an execution stack.
--
-- @since 2.16.0.0
data StackSnapshot = StackSnapshot !StackSnapshot#

foreign import prim "stg_decodeStackzh" decodeStack# :: StackSnapshot# -> State# RealWorld -> (# State# RealWorld, Array# (Ptr InfoProvEnt) #)

foreign import prim "stg_cloneMyStackzh" cloneMyStack# :: State# RealWorld -> (# State# RealWorld, StackSnapshot# #)

foreign import prim "stg_sendCloneStackMessagezh" sendCloneStackMessage# :: ThreadId# -> StablePtr# PrimMVar -> State# RealWorld -> (# State# RealWorld, (# #) #)

-- | Clone the stack of the executing thread
--
-- @since 2.16.0.0
cloneMyStack :: IO StackSnapshot

-- | Clone the stack of a thread identified by its 'ThreadId'
--
-- @since 2.16.0.0
cloneThreadStack :: ThreadId -> IO StackSnapshot

-- | Represetation for the source location where a return frame was pushed on the stack.
-- This happens every time when a @case ... of@ scrutinee is evaluated.
data StackEntry = StackEntry
  { functionName :: String,
    moduleName :: String,
    srcLoc :: String,
    closureType :: Word
  }
  deriving (Show, Eq)

-- | Decode a 'StackSnapshot' to a stacktrace (a list of 'StackEntry').
-- The stacktrace is created from return frames with according 'InfoProv'
-- entries. To generate them, use the GHC flag @-finfo-table-map@. If there are
-- no 'InfoProv' entries, an empty list is returned.
--
-- @since 2.16.0.0
decode :: StackSnapshot -> IO [StackEntry]

Source Notes

The approach is documented in several source notes. The reviewer might want to read them after understanding the API described before.

Tests

The tests provide working examples of the API usage. Most significant is testsuite/tests/rts/decodeMyStack.hs.


The initial design was described by @bgamari in this comment: #18741 (comment 342188)


To get meaningful source locations from GHC's libraries, you need to use -finfo-table-map for them in Hadrian. For source locations in user code, it's sufficient to compile it with -finfo-table-map (no special build of GHC needed).


ToDo

  • cloneStack# should be an ordinary C function (no primop) (Not possible)
  • Update Notes to describe the C interface
  • Decide if cloning and decoding should be two separate operations or not
  • Use Array# instead of MutableArray# to return decoding results
  • Return an array of Ptr InfoProvEnt on decoding (do lookupIPE directly in the RTS while decoding)
Edited by Sven Tennie

Merge request reports

Loading
Loading

Activity

Filter activity
  • Approvals
  • Assignees & reviewers
  • Comments (from bots)
  • Comments (from users)
  • Commits & branches
  • Edits
  • Labels
  • Lock status
  • Mentions
  • Merge request status
  • Tracking
  • Ben Gamari
  • Ben Gamari
    Ben Gamari @bgamari started a thread on an outdated change in commit 5c76f80e
  • 68 72 freeStablePtr ptr
    69 73 takeMVar resultVar
    70 74
    75 -- TODO: Cannot use `import GHC.Exts.Heap (StgInfoTable(..))` -> hidden package
    76 type InfoTable = Word
  • Ben Gamari
  • Sven Tennie added 1 commit

    added 1 commit

    • e78bed6d - Generate InfoTable provenances after the Cmm Pipeline ran

    Compare with previous version

  • Sven Tennie added 1 commit

    added 1 commit

    Compare with previous version

  • Sven Tennie added 97 commits

    added 97 commits

    Compare with previous version

  • Sven Tennie added 1 commit

    added 1 commit

    • cafd1d3a - Emit meaningful provenances for return frame info tables

    Compare with previous version

  • assigned to @supersven

  • Sven Tennie changed the description

    changed the description

  • Sven Tennie added 1 commit

    added 1 commit

    Compare with previous version

  • Sven Tennie added 1 commit

    added 1 commit

    • 430c0652 - Extract GHC.Driver.GenerateCgIPEStub

    Compare with previous version

  • Sven Tennie added 3 commits

    added 3 commits

    Compare with previous version

  • Sven Tennie added 1 commit

    added 1 commit

    • 60b7715a - Ensure that no provenance entries are emitted when -finfo-table-map is turned off

    Compare with previous version

  • Sven Tennie added 47 commits

    added 47 commits

    • 60b7715a...d2399a46 - 31 commits from branch master
    • 0a2face3 - deriveConstants: Add hie.yaml
    • 19eeeda8 - base: Generalize newStablePtrPrimMVar
    • 89cfdf15 - Introduce snapshotting of thread's own stack
    • 372389fd - Introduce cloning of other threads' stacks
    • a9d5504a - Add another test for stack cloning
    • 475ca2e2 - Assure that cloned RET_BIG closures are valid (#18741 (closed))
    • cd73930f - Provide StgInfoTable* as list of pointers
    • 39b17fec - Generate InfoTable provenances after the Cmm Pipeline ran
    • d062fb94 - Cleanup
    • d10dcc95 - Emit meaningful provenances for return frame info tables
    • 65b13bbd - Cleanup
    • a84689b1 - Extract GHC.Driver.GenerateCgIPEStub
    • d9a0e202 - Filter for CmmInfoTables with stack representation
    • b2d0ea86 - Format tests
    • f11024fe - Implement decode
    • cb5aa8a1 - Ensure that no provenance entries are emitted when -finfo-table-map is turned off

    Compare with previous version

  • Sven Tennie added 1 commit

    added 1 commit

    • 09127151 - Fix: Emit info table provenances not only for stack replicated info tables

    Compare with previous version

  • Sven Tennie added 1 commit

    added 1 commit

    • 034b7f1d - Only lookup tickishes for stack rep info tables, only emit IPEs when...

    Compare with previous version

  • Loading
  • Loading
  • Loading
  • Loading
  • Loading
  • Loading
  • Loading
  • Loading
  • Loading
  • Loading
  • Please register or sign in to reply
    Loading