Hannes Siebenhandl pushed to branch wip/fendor/remove-stg_stackDecode at Glasgow Haskell Compiler / GHC
Commits:
-
b6408c03
by fendor at 2025-07-25T10:08:38+02:00
-
43f9ed63
by fendor at 2025-07-25T10:08:38+02:00
-
a08f8b99
by fendor at 2025-07-25T10:08:38+02:00
15 changed files:
- hadrian/src/Rules/ToolArgs.hs
- libraries/base/src/GHC/Stack/CloneStack.hs
- libraries/ghc-internal/cbits/Stack.cmm
- libraries/ghc-internal/cbits/StackCloningDecoding.cmm
- libraries/ghc-internal/jsbits/base.js
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- libraries/ghc-internal/src/GHC/Internal/Stack/CloneStack.hs
- libraries/ghc-internal/src/GHC/Internal/Stack/Decode.hs
- rts/CloneStack.c
- rts/CloneStack.h
- rts/RtsSymbols.c
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
Changes:
| ... | ... | @@ -160,7 +160,7 @@ toolTargets = [ cabalSyntax |
| 160 | 160 | , ghcPlatform
|
| 161 | 161 | , ghcToolchain
|
| 162 | 162 | , ghcToolchainBin
|
| 163 | - , ghcHeap
|
|
| 163 | + -- , ghcHeap -- # depends on ghcInternal library
|
|
| 164 | 164 | , ghci
|
| 165 | 165 | , ghcPkg -- # executable
|
| 166 | 166 | , haddock -- # depends on ghc library
|
| ... | ... | @@ -17,3 +17,4 @@ module GHC.Stack.CloneStack ( |
| 17 | 17 | ) where
|
| 18 | 18 | |
| 19 | 19 | import GHC.Internal.Stack.CloneStack
|
| 20 | +import GHC.Internal.Stack.Decode |
| ... | ... | @@ -146,14 +146,14 @@ isArgGenBigRetFunTypezh(P_ stack, W_ offsetWords) { |
| 146 | 146 | return (type);
|
| 147 | 147 | }
|
| 148 | 148 | |
| 149 | -// (StgInfoTable*) getInfoTableAddrzh(StgStack* stack, StgWord offsetWords)
|
|
| 150 | -getInfoTableAddrzh(P_ stack, W_ offsetWords) {
|
|
| 151 | - P_ p, info;
|
|
| 149 | +// (StgInfoTable*, StgInfoTable*) getInfoTableAddrszh(StgStack* stack, StgWord offsetWords)
|
|
| 150 | +getInfoTableAddrszh(P_ stack, W_ offsetWords) {
|
|
| 151 | + P_ p, info_struct, info_entry;
|
|
| 152 | 152 | p = StgStack_sp(stack) + WDS(offsetWords);
|
| 153 | 153 | ASSERT(LOOKS_LIKE_CLOSURE_PTR(p));
|
| 154 | - info = %GET_STD_INFO(UNTAG(p));
|
|
| 155 | - |
|
| 156 | - return (info);
|
|
| 154 | + info_struct = %GET_STD_INFO(UNTAG(p));
|
|
| 155 | + info_entry = %GET_ENTRY(UNTAG(p));
|
|
| 156 | + return (info_struct, info_entry);
|
|
| 157 | 157 | }
|
| 158 | 158 | |
| 159 | 159 | // (StgInfoTable*) getStackInfoTableAddrzh(StgStack* stack)
|
| ... | ... | @@ -17,10 +17,3 @@ stg_sendCloneStackMessagezh (gcptr threadId, gcptr mVarStablePtr) { |
| 17 | 17 | |
| 18 | 18 | return ();
|
| 19 | 19 | } |
| 20 | - |
|
| 21 | -stg_decodeStackzh (gcptr stgStack) {
|
|
| 22 | - gcptr stackEntries;
|
|
| 23 | - ("ptr" stackEntries) = ccall decodeClonedStack(MyCapability() "ptr", stgStack "ptr");
|
|
| 24 | - |
|
| 25 | - return (stackEntries);
|
|
| 26 | -} |
| ... | ... | @@ -1245,9 +1245,8 @@ function h$mkdir(path, path_offset, mode) { |
| 1245 | 1245 | |
| 1246 | 1246 | // It is required by Google Closure Compiler to be at least defined if
|
| 1247 | 1247 | // somewhere it is used
|
| 1248 | -var h$stg_cloneMyStackzh, h$stg_decodeStackzh
|
|
| 1248 | +var h$stg_cloneMyStackzh
|
|
| 1249 | 1249 | h$stg_cloneMyStackzh
|
| 1250 | - = h$stg_decodeStackzh
|
|
| 1251 | 1250 | = function () {
|
| 1252 | 1251 | throw new Error('Stack Cloning Decoding: Not Implemented Yet')
|
| 1253 | 1252 | } |
| ... | ... | @@ -16,6 +16,7 @@ import qualified GHC.Internal.Stack as HCS |
| 16 | 16 | import qualified GHC.Internal.ExecutionStack as ExecStack
|
| 17 | 17 | import qualified GHC.Internal.ExecutionStack.Internal as ExecStack
|
| 18 | 18 | import qualified GHC.Internal.Stack.CloneStack as CloneStack
|
| 19 | +import qualified GHC.Internal.Stack.Decode as CloneStack
|
|
| 19 | 20 | import qualified GHC.Internal.Stack.CCS as CCS
|
| 20 | 21 | |
| 21 | 22 | -- | How to collect a backtrace when an exception is thrown.
|
| ... | ... | @@ -15,34 +15,20 @@ |
| 15 | 15 | -- @since base-4.17.0.0
|
| 16 | 16 | module GHC.Internal.Stack.CloneStack (
|
| 17 | 17 | StackSnapshot(..),
|
| 18 | - StackEntry(..),
|
|
| 19 | 18 | cloneMyStack,
|
| 20 | 19 | cloneThreadStack,
|
| 21 | - decode,
|
|
| 22 | - prettyStackEntry
|
|
| 23 | 20 | ) where
|
| 24 | 21 | |
| 25 | 22 | import GHC.Internal.MVar
|
| 26 | -import GHC.Internal.Data.Maybe (catMaybes)
|
|
| 27 | 23 | import GHC.Internal.Base
|
| 28 | -import GHC.Internal.Foreign.Storable
|
|
| 29 | 24 | import GHC.Internal.Conc.Sync
|
| 30 | -import GHC.Internal.IO (unsafeInterleaveIO)
|
|
| 31 | -import GHC.Internal.InfoProv.Types (InfoProv (..), ipLoc, lookupIPE, StgInfoTable)
|
|
| 32 | -import GHC.Internal.Num
|
|
| 33 | -import GHC.Internal.Real (div)
|
|
| 34 | 25 | import GHC.Internal.Stable
|
| 35 | -import GHC.Internal.Text.Show
|
|
| 36 | -import GHC.Internal.Ptr
|
|
| 37 | -import GHC.Internal.ClosureTypes
|
|
| 38 | 26 | |
| 39 | 27 | -- | A frozen snapshot of the state of an execution stack.
|
| 40 | 28 | --
|
| 41 | 29 | -- @since base-4.17.0.0
|
| 42 | 30 | data StackSnapshot = StackSnapshot !StackSnapshot#
|
| 43 | 31 | |
| 44 | -foreign import prim "stg_decodeStackzh" decodeStack# :: StackSnapshot# -> State# RealWorld -> (# State# RealWorld, ByteArray# #)
|
|
| 45 | - |
|
| 46 | 32 | foreign import prim "stg_cloneMyStackzh" cloneMyStack# :: State# RealWorld -> (# State# RealWorld, StackSnapshot# #)
|
| 47 | 33 | |
| 48 | 34 | foreign import prim "stg_sendCloneStackMessagezh" sendCloneStackMessage# :: ThreadId# -> StablePtr# PrimMVar -> State# RealWorld -> (# State# RealWorld, (# #) #)
|
| ... | ... | @@ -205,64 +191,3 @@ cloneThreadStack (ThreadId tid#) = do |
| 205 | 191 | IO $ \s -> case sendCloneStackMessage# tid# ptr s of (# s', (# #) #) -> (# s', () #)
|
| 206 | 192 | freeStablePtr boxedPtr
|
| 207 | 193 | takeMVar resultVar |
| 208 | - |
|
| 209 | --- | Representation for the source location where a return frame was pushed on the stack.
|
|
| 210 | --- This happens every time when a @case ... of@ scrutinee is evaluated.
|
|
| 211 | -data StackEntry = StackEntry
|
|
| 212 | - { functionName :: String,
|
|
| 213 | - moduleName :: String,
|
|
| 214 | - srcLoc :: String,
|
|
| 215 | - closureType :: ClosureType
|
|
| 216 | - }
|
|
| 217 | - deriving (Show, Eq)
|
|
| 218 | - |
|
| 219 | --- | Decode a 'StackSnapshot' to a stacktrace (a list of 'StackEntry').
|
|
| 220 | --- The stack trace is created from return frames with according 'InfoProvEnt'
|
|
| 221 | --- entries. To generate them, use the GHC flag @-finfo-table-map@. If there are
|
|
| 222 | --- no 'InfoProvEnt' entries, an empty list is returned.
|
|
| 223 | ---
|
|
| 224 | --- Please note:
|
|
| 225 | ---
|
|
| 226 | --- * To gather 'StackEntry' from libraries, these have to be
|
|
| 227 | --- compiled with @-finfo-table-map@, too.
|
|
| 228 | --- * Due to optimizations by GHC (e.g. inlining) the stacktrace may change
|
|
| 229 | --- with different GHC parameters and versions.
|
|
| 230 | --- * The stack trace is empty (by design) if there are no return frames on
|
|
| 231 | --- the stack. (These are pushed every time when a @case ... of@ scrutinee
|
|
| 232 | --- is evaluated.)
|
|
| 233 | ---
|
|
| 234 | --- @since base-4.17.0.0
|
|
| 235 | -decode :: StackSnapshot -> IO [StackEntry]
|
|
| 236 | -decode stackSnapshot = catMaybes `fmap` getDecodedStackArray stackSnapshot
|
|
| 237 | - |
|
| 238 | -toStackEntry :: InfoProv -> StackEntry
|
|
| 239 | -toStackEntry infoProv =
|
|
| 240 | - StackEntry
|
|
| 241 | - { functionName = ipLabel infoProv,
|
|
| 242 | - moduleName = ipMod infoProv,
|
|
| 243 | - srcLoc = ipLoc infoProv,
|
|
| 244 | - closureType = ipDesc infoProv
|
|
| 245 | - }
|
|
| 246 | - |
|
| 247 | -getDecodedStackArray :: StackSnapshot -> IO [Maybe StackEntry]
|
|
| 248 | -getDecodedStackArray (StackSnapshot s) =
|
|
| 249 | - IO $ \s0 -> case decodeStack# s s0 of
|
|
| 250 | - (# s1, arr #) ->
|
|
| 251 | - let n = I# (sizeofByteArray# arr) `div` wordSize - 1
|
|
| 252 | - in unIO (go arr n) s1
|
|
| 253 | - where
|
|
| 254 | - go :: ByteArray# -> Int -> IO [Maybe StackEntry]
|
|
| 255 | - go _stack (-1) = return []
|
|
| 256 | - go stack i = do
|
|
| 257 | - infoProv <- lookupIPE (stackEntryAt stack i)
|
|
| 258 | - rest <- unsafeInterleaveIO $ go stack (i-1)
|
|
| 259 | - return ((toStackEntry `fmap` infoProv) : rest)
|
|
| 260 | - |
|
| 261 | - stackEntryAt :: ByteArray# -> Int -> Ptr StgInfoTable
|
|
| 262 | - stackEntryAt stack (I# i) = Ptr (indexAddrArray# stack i)
|
|
| 263 | - |
|
| 264 | - wordSize = sizeOf (nullPtr :: Ptr ())
|
|
| 265 | - |
|
| 266 | -prettyStackEntry :: StackEntry -> String
|
|
| 267 | -prettyStackEntry (StackEntry {moduleName=mod_nm, functionName=fun_nm, srcLoc=loc}) =
|
|
| 268 | - " " ++ mod_nm ++ "." ++ fun_nm ++ " (" ++ loc ++ ")" |
| ... | ... | @@ -13,7 +13,17 @@ |
| 13 | 13 | {-# LANGUAGE UnliftedFFITypes #-}
|
| 14 | 14 | |
| 15 | 15 | module GHC.Internal.Stack.Decode (
|
| 16 | + -- * High-level stack decoders
|
|
| 17 | + decode,
|
|
| 16 | 18 | decodeStack,
|
| 19 | + decodeStackWithIpe,
|
|
| 20 | + -- * Stack decoder helpers
|
|
| 21 | + decodeStackWithFrameUnpack,
|
|
| 22 | + -- * StackEntry
|
|
| 23 | + StackEntry(..),
|
|
| 24 | + -- * Pretty printing
|
|
| 25 | + prettyStackFrameWithIpe,
|
|
| 26 | + prettyStackEntry,
|
|
| 17 | 27 | )
|
| 18 | 28 | where
|
| 19 | 29 | |
| ... | ... | @@ -23,7 +33,10 @@ import GHC.Internal.Real |
| 23 | 33 | import GHC.Internal.Word
|
| 24 | 34 | import GHC.Internal.Num
|
| 25 | 35 | import GHC.Internal.Data.Bits
|
| 36 | +import GHC.Internal.Data.Functor
|
|
| 37 | +import GHC.Internal.Data.Maybe (catMaybes)
|
|
| 26 | 38 | import GHC.Internal.Data.List
|
| 39 | +import GHC.Internal.Data.Tuple
|
|
| 27 | 40 | import GHC.Internal.Foreign.Ptr
|
| 28 | 41 | import GHC.Internal.Foreign.Storable
|
| 29 | 42 | import GHC.Internal.Exts
|
| ... | ... | @@ -42,6 +55,7 @@ import GHC.Internal.Heap.Constants (wORD_SIZE_IN_BITS) |
| 42 | 55 | import GHC.Internal.Heap.InfoTable
|
| 43 | 56 | import GHC.Internal.Stack.Constants
|
| 44 | 57 | import GHC.Internal.Stack.CloneStack
|
| 58 | +import GHC.Internal.InfoProv.Types (InfoProv (..), ipLoc, lookupIPE)
|
|
| 45 | 59 | |
| 46 | 60 | {- Note [Decoding the stack]
|
| 47 | 61 | ~~~~~~~~~~~~~~~~~~~~~~~~~
|
| ... | ... | @@ -153,14 +167,17 @@ foreign import prim "getSmallBitmapzh" getSmallBitmap# :: SmallBitmapGetter |
| 153 | 167 | |
| 154 | 168 | foreign import prim "getRetFunSmallBitmapzh" getRetFunSmallBitmap# :: SmallBitmapGetter
|
| 155 | 169 | |
| 156 | -foreign import prim "getInfoTableAddrzh" getInfoTableAddr# :: StackSnapshot# -> Word# -> Addr#
|
|
| 170 | +foreign import prim "getInfoTableAddrszh" getInfoTableAddrs# :: StackSnapshot# -> Word# -> (# Addr#, Addr# #)
|
|
| 157 | 171 | |
| 158 | 172 | foreign import prim "getStackInfoTableAddrzh" getStackInfoTableAddr# :: StackSnapshot# -> Addr#
|
| 159 | 173 | |
| 160 | -getInfoTableOnStack :: StackSnapshot# -> WordOffset -> IO StgInfoTable
|
|
| 174 | +-- | Get the 'StgInfoTable' of the stack frame.
|
|
| 175 | +-- Additionally, provides 'InfoProv' for the 'StgInfoTable' if there is any.
|
|
| 176 | +getInfoTableOnStack :: StackSnapshot# -> WordOffset -> IO (StgInfoTable, Maybe InfoProv)
|
|
| 161 | 177 | getInfoTableOnStack stackSnapshot# index =
|
| 162 | - let infoTablePtr = Ptr (getInfoTableAddr# stackSnapshot# (wordOffsetToWord# index))
|
|
| 163 | - in peekItbl infoTablePtr
|
|
| 178 | + let !(# itbl_struct#, itbl_ptr# #) = getInfoTableAddrs# stackSnapshot# (wordOffsetToWord# index)
|
|
| 179 | + in
|
|
| 180 | + (,) <$> peekItbl (Ptr itbl_struct#) <*> lookupIPE (Ptr itbl_ptr#)
|
|
| 164 | 181 | |
| 165 | 182 | getInfoTableForStack :: StackSnapshot# -> IO StgInfoTable
|
| 166 | 183 | getInfoTableForStack stackSnapshot# =
|
| ... | ... | @@ -279,18 +296,66 @@ decodeSmallBitmap getterFun# stackSnapshot# index relativePayloadOffset = |
| 279 | 296 | (bitmapWordPointerness size bitmap)
|
| 280 | 297 | |
| 281 | 298 | unpackStackFrame :: StackFrameLocation -> IO StackFrame
|
| 282 | -unpackStackFrame (StackSnapshot stackSnapshot#, index) = do
|
|
| 283 | - info <- getInfoTableOnStack stackSnapshot# index
|
|
| 299 | +unpackStackFrame stackFrameLoc = do
|
|
| 300 | + unpackStackFrameTo stackFrameLoc
|
|
| 301 | + (\ info _ nextChunk -> do
|
|
| 302 | + stackClosure <- decodeStack nextChunk
|
|
| 303 | + pure $
|
|
| 304 | + UnderflowFrame
|
|
| 305 | + { info_tbl = info,
|
|
| 306 | + nextChunk = stackClosure
|
|
| 307 | + }
|
|
| 308 | + )
|
|
| 309 | + (\ frame _ -> pure frame)
|
|
| 310 | + |
|
| 311 | +unpackStackFrameWithIpe :: StackFrameLocation -> IO [(StackFrame, Maybe InfoProv)]
|
|
| 312 | +unpackStackFrameWithIpe stackFrameLoc = do
|
|
| 313 | + unpackStackFrameTo stackFrameLoc
|
|
| 314 | + (\ info mIpe nextChunk@(StackSnapshot stack#) -> do
|
|
| 315 | + framesWithIpe <- decodeStackWithIpe nextChunk
|
|
| 316 | + pure
|
|
| 317 | + [ ( UnderflowFrame
|
|
| 318 | + { info_tbl = info,
|
|
| 319 | + nextChunk =
|
|
| 320 | + GenStgStackClosure
|
|
| 321 | + { ssc_info = info,
|
|
| 322 | + ssc_stack_size = getStackFields stack#,
|
|
| 323 | + ssc_stack = map fst framesWithIpe
|
|
| 324 | + }
|
|
| 325 | + }
|
|
| 326 | + , mIpe
|
|
| 327 | + )
|
|
| 328 | + ]
|
|
| 329 | + )
|
|
| 330 | + (\ frame mIpe -> pure [(frame, mIpe)])
|
|
| 331 | + |
|
| 332 | +unpackStackFrameTo ::
|
|
| 333 | + forall a .
|
|
| 334 | + StackFrameLocation ->
|
|
| 335 | + -- ^ Decode the given 'StackFrame'.
|
|
| 336 | + (StgInfoTable -> Maybe InfoProv -> StackSnapshot -> IO a) ->
|
|
| 337 | + -- ^ How to handle 'UNDERFLOW_FRAME's.
|
|
| 338 | + (StackFrame -> Maybe InfoProv -> IO a) ->
|
|
| 339 | + -- ^ How to handle all other 'StackFrame' values.
|
|
| 340 | + IO a
|
|
| 341 | +unpackStackFrameTo (StackSnapshot stackSnapshot#, index) unpackUnderflowFrame finaliseStackFrame = do
|
|
| 342 | + (info, m_info_prov) <- getInfoTableOnStack stackSnapshot# index
|
|
| 284 | 343 | unpackStackFrame' info
|
| 344 | + (unpackUnderflowFrame info m_info_prov)
|
|
| 345 | + (`finaliseStackFrame` m_info_prov)
|
|
| 285 | 346 | where
|
| 286 | - unpackStackFrame' :: StgInfoTable -> IO StackFrame
|
|
| 287 | - unpackStackFrame' info =
|
|
| 347 | + unpackStackFrame' ::
|
|
| 348 | + StgInfoTable ->
|
|
| 349 | + (StackSnapshot -> IO a) ->
|
|
| 350 | + (StackFrame -> IO a) ->
|
|
| 351 | + IO a
|
|
| 352 | + unpackStackFrame' info mkUnderflowResult mkStackFrameResult =
|
|
| 288 | 353 | case tipe info of
|
| 289 | 354 | RET_BCO -> do
|
| 290 | 355 | let bco' = getClosureBox stackSnapshot# (index + offsetStgClosurePayload)
|
| 291 | 356 | -- The arguments begin directly after the payload's one element
|
| 292 | 357 | bcoArgs' <- decodeLargeBitmap getBCOLargeBitmap# stackSnapshot# index (offsetStgClosurePayload + 1)
|
| 293 | - pure
|
|
| 358 | + mkStackFrameResult
|
|
| 294 | 359 | RetBCO
|
| 295 | 360 | { info_tbl = info,
|
| 296 | 361 | bco = bco',
|
| ... | ... | @@ -299,14 +364,14 @@ unpackStackFrame (StackSnapshot stackSnapshot#, index) = do |
| 299 | 364 | RET_SMALL ->
|
| 300 | 365 | let payload' = decodeSmallBitmap getSmallBitmap# stackSnapshot# index offsetStgClosurePayload
|
| 301 | 366 | in
|
| 302 | - pure $
|
|
| 367 | + mkStackFrameResult $
|
|
| 303 | 368 | RetSmall
|
| 304 | 369 | { info_tbl = info,
|
| 305 | 370 | stack_payload = payload'
|
| 306 | 371 | }
|
| 307 | 372 | RET_BIG -> do
|
| 308 | 373 | payload' <- decodeLargeBitmap getLargeBitmap# stackSnapshot# index offsetStgClosurePayload
|
| 309 | - pure $
|
|
| 374 | + mkStackFrameResult $
|
|
| 310 | 375 | RetBig
|
| 311 | 376 | { info_tbl = info,
|
| 312 | 377 | stack_payload = payload'
|
| ... | ... | @@ -318,7 +383,7 @@ unpackStackFrame (StackSnapshot stackSnapshot#, index) = do |
| 318 | 383 | if isArgGenBigRetFunType stackSnapshot# index == True
|
| 319 | 384 | then decodeLargeBitmap getRetFunLargeBitmap# stackSnapshot# index offsetStgRetFunFramePayload
|
| 320 | 385 | else pure $ decodeSmallBitmap getRetFunSmallBitmap# stackSnapshot# index offsetStgRetFunFramePayload
|
| 321 | - pure $
|
|
| 386 | + mkStackFrameResult $
|
|
| 322 | 387 | RetFun
|
| 323 | 388 | { info_tbl = info,
|
| 324 | 389 | retFunSize = retFunSize',
|
| ... | ... | @@ -328,31 +393,26 @@ unpackStackFrame (StackSnapshot stackSnapshot#, index) = do |
| 328 | 393 | UPDATE_FRAME ->
|
| 329 | 394 | let updatee' = getClosureBox stackSnapshot# (index + offsetStgUpdateFrameUpdatee)
|
| 330 | 395 | in
|
| 331 | - pure $
|
|
| 396 | + mkStackFrameResult $
|
|
| 332 | 397 | UpdateFrame
|
| 333 | 398 | { info_tbl = info,
|
| 334 | 399 | updatee = updatee'
|
| 335 | 400 | }
|
| 336 | 401 | CATCH_FRAME -> do
|
| 337 | 402 | let handler' = getClosureBox stackSnapshot# (index + offsetStgCatchFrameHandler)
|
| 338 | - pure $
|
|
| 403 | + mkStackFrameResult $
|
|
| 339 | 404 | CatchFrame
|
| 340 | 405 | { info_tbl = info,
|
| 341 | 406 | handler = handler'
|
| 342 | 407 | }
|
| 343 | 408 | UNDERFLOW_FRAME -> do
|
| 344 | 409 | let nextChunk' = getUnderflowFrameNextChunk stackSnapshot# index
|
| 345 | - stackClosure <- decodeStack nextChunk'
|
|
| 346 | - pure $
|
|
| 347 | - UnderflowFrame
|
|
| 348 | - { info_tbl = info,
|
|
| 349 | - nextChunk = stackClosure
|
|
| 350 | - }
|
|
| 351 | - STOP_FRAME -> pure $ StopFrame {info_tbl = info}
|
|
| 410 | + mkUnderflowResult nextChunk'
|
|
| 411 | + STOP_FRAME -> mkStackFrameResult $ StopFrame {info_tbl = info}
|
|
| 352 | 412 | ATOMICALLY_FRAME -> do
|
| 353 | 413 | let atomicallyFrameCode' = getClosureBox stackSnapshot# (index + offsetStgAtomicallyFrameCode)
|
| 354 | 414 | result' = getClosureBox stackSnapshot# (index + offsetStgAtomicallyFrameResult)
|
| 355 | - pure $
|
|
| 415 | + mkStackFrameResult $
|
|
| 356 | 416 | AtomicallyFrame
|
| 357 | 417 | { info_tbl = info,
|
| 358 | 418 | atomicallyFrameCode = atomicallyFrameCode',
|
| ... | ... | @@ -363,7 +423,7 @@ unpackStackFrame (StackSnapshot stackSnapshot#, index) = do |
| 363 | 423 | first_code' = getClosureBox stackSnapshot# (index + offsetStgCatchRetryFrameRunningFirstCode)
|
| 364 | 424 | alt_code' = getClosureBox stackSnapshot# (index + offsetStgCatchRetryFrameAltCode)
|
| 365 | 425 | in
|
| 366 | - pure $
|
|
| 426 | + mkStackFrameResult $
|
|
| 367 | 427 | CatchRetryFrame
|
| 368 | 428 | { info_tbl = info,
|
| 369 | 429 | running_alt_code = running_alt_code',
|
| ... | ... | @@ -374,7 +434,7 @@ unpackStackFrame (StackSnapshot stackSnapshot#, index) = do |
| 374 | 434 | let catchFrameCode' = getClosureBox stackSnapshot# (index + offsetStgCatchSTMFrameCode)
|
| 375 | 435 | handler' = getClosureBox stackSnapshot# (index + offsetStgCatchSTMFrameHandler)
|
| 376 | 436 | in
|
| 377 | - pure $
|
|
| 437 | + mkStackFrameResult $
|
|
| 378 | 438 | CatchStmFrame
|
| 379 | 439 | { info_tbl = info,
|
| 380 | 440 | catchFrameCode = catchFrameCode',
|
| ... | ... | @@ -393,6 +453,54 @@ intToWord# i = int2Word# (toInt# i) |
| 393 | 453 | wordOffsetToWord# :: WordOffset -> Word#
|
| 394 | 454 | wordOffsetToWord# wo = intToWord# (fromIntegral wo)
|
| 395 | 455 | |
| 456 | +-- ----------------------------------------------------------------------------
|
|
| 457 | +-- Simplified source location representation of provenance information
|
|
| 458 | +-- ----------------------------------------------------------------------------
|
|
| 459 | + |
|
| 460 | +-- | Representation for the source location where a return frame was pushed on the stack.
|
|
| 461 | +-- This happens every time when a @case ... of@ scrutinee is evaluated.
|
|
| 462 | +data StackEntry = StackEntry
|
|
| 463 | + { functionName :: String,
|
|
| 464 | + moduleName :: String,
|
|
| 465 | + srcLoc :: String,
|
|
| 466 | + closureType :: ClosureType
|
|
| 467 | + }
|
|
| 468 | + deriving (Show, Eq)
|
|
| 469 | + |
|
| 470 | +toStackEntry :: InfoProv -> StackEntry
|
|
| 471 | +toStackEntry infoProv =
|
|
| 472 | + StackEntry
|
|
| 473 | + { functionName = ipLabel infoProv,
|
|
| 474 | + moduleName = ipMod infoProv,
|
|
| 475 | + srcLoc = ipLoc infoProv,
|
|
| 476 | + closureType = ipDesc infoProv
|
|
| 477 | + }
|
|
| 478 | + |
|
| 479 | +-- ----------------------------------------------------------------------------
|
|
| 480 | +-- Stack decoders
|
|
| 481 | +-- ----------------------------------------------------------------------------
|
|
| 482 | + |
|
| 483 | +-- | Decode a 'StackSnapshot' to a stacktrace (a list of 'StackEntry').
|
|
| 484 | +-- The stack trace is created from return frames with according 'InfoProvEnt'
|
|
| 485 | +-- entries. To generate them, use the GHC flag @-finfo-table-map@. If there are
|
|
| 486 | +-- no 'InfoProvEnt' entries, an empty list is returned.
|
|
| 487 | +--
|
|
| 488 | +-- Please note:
|
|
| 489 | +--
|
|
| 490 | +-- * To gather 'StackEntry' from libraries, these have to be
|
|
| 491 | +-- compiled with @-finfo-table-map@, too.
|
|
| 492 | +-- * Due to optimizations by GHC (e.g. inlining) the stacktrace may change
|
|
| 493 | +-- with different GHC parameters and versions.
|
|
| 494 | +-- * The stack trace is empty (by design) if there are no return frames on
|
|
| 495 | +-- the stack. (These are pushed every time when a @case ... of@ scrutinee
|
|
| 496 | +-- is evaluated.)
|
|
| 497 | +--
|
|
| 498 | +-- @since base-4.17.0.0
|
|
| 499 | +decode :: StackSnapshot -> IO [StackEntry]
|
|
| 500 | +decode stackSnapshot =
|
|
| 501 | + (map toStackEntry . catMaybes . map snd . reverse) <$> decodeStackWithIpe stackSnapshot
|
|
| 502 | + |
|
| 503 | + |
|
| 396 | 504 | -- | Location of a stackframe on the stack
|
| 397 | 505 | --
|
| 398 | 506 | -- It's defined by the `StackSnapshot` (@StgStack@) and the offset to the bottom
|
| ... | ... | @@ -405,19 +513,31 @@ type StackFrameLocation = (StackSnapshot, WordOffset) |
| 405 | 513 | --
|
| 406 | 514 | -- See /Note [Decoding the stack]/.
|
| 407 | 515 | decodeStack :: StackSnapshot -> IO StgStackClosure
|
| 408 | -decodeStack (StackSnapshot stack#) = do
|
|
| 516 | +decodeStack snapshot@(StackSnapshot stack#) = do
|
|
| 517 | + (stackInfo, ssc_stack) <- decodeStackWithFrameUnpack unpackStackFrame snapshot
|
|
| 518 | + pure
|
|
| 519 | + GenStgStackClosure
|
|
| 520 | + { ssc_info = stackInfo,
|
|
| 521 | + ssc_stack_size = getStackFields stack#,
|
|
| 522 | + ssc_stack = ssc_stack
|
|
| 523 | + }
|
|
| 524 | + |
|
| 525 | +decodeStackWithIpe :: StackSnapshot -> IO [(StackFrame, Maybe InfoProv)]
|
|
| 526 | +decodeStackWithIpe snapshot =
|
|
| 527 | + concat . snd <$> decodeStackWithFrameUnpack unpackStackFrameWithIpe snapshot
|
|
| 528 | + |
|
| 529 | +-- ----------------------------------------------------------------------------
|
|
| 530 | +-- Write your own stack decoder!
|
|
| 531 | +-- ----------------------------------------------------------------------------
|
|
| 532 | + |
|
| 533 | +decodeStackWithFrameUnpack :: (StackFrameLocation -> IO a) -> StackSnapshot -> IO (StgInfoTable, [a])
|
|
| 534 | +decodeStackWithFrameUnpack unpackFrame (StackSnapshot stack#) = do
|
|
| 409 | 535 | info <- getInfoTableForStack stack#
|
| 410 | 536 | case tipe info of
|
| 411 | 537 | STACK -> do
|
| 412 | - let stack_size' = getStackFields stack#
|
|
| 413 | - sfls = stackFrameLocations stack#
|
|
| 414 | - stack' <- mapM unpackStackFrame sfls
|
|
| 415 | - pure $
|
|
| 416 | - GenStgStackClosure
|
|
| 417 | - { ssc_info = info,
|
|
| 418 | - ssc_stack_size = stack_size',
|
|
| 419 | - ssc_stack = stack'
|
|
| 420 | - }
|
|
| 538 | + let sfls = stackFrameLocations stack#
|
|
| 539 | + stack' <- mapM unpackFrame sfls
|
|
| 540 | + pure (info, stack')
|
|
| 421 | 541 | _ -> error $ "Expected STACK closure, got " ++ show info
|
| 422 | 542 | where
|
| 423 | 543 | stackFrameLocations :: StackSnapshot# -> [StackFrameLocation]
|
| ... | ... | @@ -428,3 +548,15 @@ decodeStack (StackSnapshot stack#) = do |
| 428 | 548 | go :: Maybe StackFrameLocation -> [StackFrameLocation]
|
| 429 | 549 | go Nothing = []
|
| 430 | 550 | go (Just r) = r : go (advanceStackFrameLocation r)
|
| 551 | + |
|
| 552 | +-- ----------------------------------------------------------------------------
|
|
| 553 | +-- Pretty printing functions for stack entires, stack frames and provenance info
|
|
| 554 | +-- ----------------------------------------------------------------------------
|
|
| 555 | + |
|
| 556 | +prettyStackFrameWithIpe :: (StackFrame, Maybe InfoProv) -> Maybe String
|
|
| 557 | +prettyStackFrameWithIpe (_frame, mipe) =
|
|
| 558 | + (prettyStackEntry . toStackEntry) <$> mipe
|
|
| 559 | + |
|
| 560 | +prettyStackEntry :: StackEntry -> String
|
|
| 561 | +prettyStackEntry (StackEntry {moduleName=mod_nm, functionName=fun_nm, srcLoc=loc}) =
|
|
| 562 | + mod_nm ++ "." ++ fun_nm ++ " (" ++ loc ++ ")" |
| ... | ... | @@ -26,11 +26,6 @@ |
| 26 | 26 | #include <string.h>
|
| 27 | 27 | |
| 28 | 28 | |
| 29 | -static StgWord getStackFrameCount(StgStack* stack);
|
|
| 30 | -static StgWord getStackChunkClosureCount(StgStack* stack);
|
|
| 31 | -static StgArrBytes* allocateByteArray(Capability *cap, StgWord bytes);
|
|
| 32 | -static void copyPtrsToArray(StgArrBytes* arr, StgStack* stack);
|
|
| 33 | - |
|
| 34 | 29 | static StgStack* cloneStackChunk(Capability* capability, const StgStack* stack)
|
| 35 | 30 | {
|
| 36 | 31 | StgWord spOffset = stack->sp - stack->stack;
|
| ... | ... | @@ -112,94 +107,3 @@ void sendCloneStackMessage(StgTSO *tso STG_UNUSED, HsStablePtr mvar STG_UNUSED) |
| 112 | 107 | }
|
| 113 | 108 | |
| 114 | 109 | #endif // end !defined(THREADED_RTS) |
| 115 | - |
|
| 116 | -// Creates a MutableArray# (Haskell representation) that contains a
|
|
| 117 | -// InfoProvEnt* for every stack frame on the given stack. Thus, the size of the
|
|
| 118 | -// array is the count of stack frames.
|
|
| 119 | -// Each InfoProvEnt* is looked up by lookupIPE(). If there's no IPE for a stack
|
|
| 120 | -// frame it's represented by null.
|
|
| 121 | -StgArrBytes* decodeClonedStack(Capability *cap, StgStack* stack) {
|
|
| 122 | - StgWord closureCount = getStackFrameCount(stack);
|
|
| 123 | - |
|
| 124 | - StgArrBytes* array = allocateByteArray(cap, sizeof(StgInfoTable*) * closureCount);
|
|
| 125 | - |
|
| 126 | - copyPtrsToArray(array, stack);
|
|
| 127 | - |
|
| 128 | - return array;
|
|
| 129 | -}
|
|
| 130 | - |
|
| 131 | -// Count the stack frames that are on the given stack.
|
|
| 132 | -// This is the sum of all stack frames in all stack chunks of this stack.
|
|
| 133 | -StgWord getStackFrameCount(StgStack* stack) {
|
|
| 134 | - StgWord closureCount = 0;
|
|
| 135 | - StgStack *last_stack = stack;
|
|
| 136 | - while (true) {
|
|
| 137 | - closureCount += getStackChunkClosureCount(last_stack);
|
|
| 138 | - |
|
| 139 | - // check whether the stack ends in an underflow frame
|
|
| 140 | - StgUnderflowFrame *frame = (StgUnderflowFrame *) (last_stack->stack
|
|
| 141 | - + last_stack->stack_size - sizeofW(StgUnderflowFrame));
|
|
| 142 | - if (frame->info == &stg_stack_underflow_frame_d_info
|
|
| 143 | - ||frame->info == &stg_stack_underflow_frame_v16_info
|
|
| 144 | - ||frame->info == &stg_stack_underflow_frame_v32_info
|
|
| 145 | - ||frame->info == &stg_stack_underflow_frame_v64_info) {
|
|
| 146 | - last_stack = frame->next_chunk;
|
|
| 147 | - } else {
|
|
| 148 | - break;
|
|
| 149 | - }
|
|
| 150 | - }
|
|
| 151 | - return closureCount;
|
|
| 152 | -}
|
|
| 153 | - |
|
| 154 | -StgWord getStackChunkClosureCount(StgStack* stack) {
|
|
| 155 | - StgWord closureCount = 0;
|
|
| 156 | - StgPtr sp = stack->sp;
|
|
| 157 | - StgPtr spBottom = stack->stack + stack->stack_size;
|
|
| 158 | - for (; sp < spBottom; sp += stack_frame_sizeW((StgClosure *)sp)) {
|
|
| 159 | - closureCount++;
|
|
| 160 | - }
|
|
| 161 | - |
|
| 162 | - return closureCount;
|
|
| 163 | -}
|
|
| 164 | - |
|
| 165 | -// Allocate and initialize memory for a ByteArray# (Haskell representation).
|
|
| 166 | -StgArrBytes* allocateByteArray(Capability *cap, StgWord bytes) {
|
|
| 167 | - // Idea stolen from PrimOps.cmm:stg_newArrayzh()
|
|
| 168 | - StgWord words = sizeofW(StgArrBytes) + bytes;
|
|
| 169 | - |
|
| 170 | - StgArrBytes* array = (StgArrBytes*) allocate(cap, words);
|
|
| 171 | - |
|
| 172 | - SET_HDR(array, &stg_ARR_WORDS_info, CCS_SYSTEM);
|
|
| 173 | - array->bytes = bytes;
|
|
| 174 | - return array;
|
|
| 175 | -}
|
|
| 176 | - |
|
| 177 | -static void copyPtrsToArray(StgArrBytes* arr, StgStack* stack) {
|
|
| 178 | - StgWord index = 0;
|
|
| 179 | - StgStack *last_stack = stack;
|
|
| 180 | - const StgInfoTable **result = (const StgInfoTable **) arr->payload;
|
|
| 181 | - while (true) {
|
|
| 182 | - StgPtr sp = last_stack->sp;
|
|
| 183 | - StgPtr spBottom = last_stack->stack + last_stack->stack_size;
|
|
| 184 | - for (; sp < spBottom; sp += stack_frame_sizeW((StgClosure *)sp)) {
|
|
| 185 | - const StgInfoTable* infoTable = ((StgClosure *)sp)->header.info;
|
|
| 186 | - result[index] = infoTable;
|
|
| 187 | - index++;
|
|
| 188 | - }
|
|
| 189 | - |
|
| 190 | - // Ensure that we didn't overflow the result array
|
|
| 191 | - ASSERT(index-1 < arr->bytes / sizeof(StgInfoTable*));
|
|
| 192 | - |
|
| 193 | - // check whether the stack ends in an underflow frame
|
|
| 194 | - StgUnderflowFrame *frame = (StgUnderflowFrame *) (last_stack->stack
|
|
| 195 | - + last_stack->stack_size - sizeofW(StgUnderflowFrame));
|
|
| 196 | - if (frame->info == &stg_stack_underflow_frame_d_info
|
|
| 197 | - ||frame->info == &stg_stack_underflow_frame_v16_info
|
|
| 198 | - ||frame->info == &stg_stack_underflow_frame_v32_info
|
|
| 199 | - ||frame->info == &stg_stack_underflow_frame_v64_info) {
|
|
| 200 | - last_stack = frame->next_chunk;
|
|
| 201 | - } else {
|
|
| 202 | - break;
|
|
| 203 | - }
|
|
| 204 | - }
|
|
| 205 | -} |
| ... | ... | @@ -15,8 +15,6 @@ StgStack* cloneStack(Capability* capability, const StgStack* stack); |
| 15 | 15 | |
| 16 | 16 | void sendCloneStackMessage(StgTSO *tso, HsStablePtr mvar);
|
| 17 | 17 | |
| 18 | -StgArrBytes* decodeClonedStack(Capability *cap, StgStack* stack);
|
|
| 19 | - |
|
| 20 | 18 | #include "BeginPrivate.h"
|
| 21 | 19 | |
| 22 | 20 | #if defined(THREADED_RTS)
|
| ... | ... | @@ -953,7 +953,6 @@ extern char **environ; |
| 953 | 953 | SymI_HasProto(lookupIPE) \
|
| 954 | 954 | SymI_HasProto(sendCloneStackMessage) \
|
| 955 | 955 | SymI_HasProto(cloneStack) \
|
| 956 | - SymI_HasProto(decodeClonedStack) \
|
|
| 957 | 956 | SymI_HasProto(stg_newPromptTagzh) \
|
| 958 | 957 | SymI_HasProto(stg_promptzh) \
|
| 959 | 958 | SymI_HasProto(stg_control0zh) \
|
| ... | ... | @@ -323,7 +323,7 @@ module Control.Exception.Backtrace where |
| 323 | 323 | type BacktraceMechanism :: *
|
| 324 | 324 | data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
|
| 325 | 325 | type Backtraces :: *
|
| 326 | - data Backtraces = Backtraces {btrCostCentre :: GHC.Internal.Maybe.Maybe (GHC.Internal.Ptr.Ptr GHC.Internal.Stack.CCS.CostCentreStack), btrHasCallStack :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.Types.CallStack, btrExecutionStack :: GHC.Internal.Maybe.Maybe [GHC.Internal.ExecutionStack.Internal.Location], btrIpe :: GHC.Internal.Maybe.Maybe [GHC.Internal.Stack.CloneStack.StackEntry]}
|
|
| 326 | + data Backtraces = Backtraces {btrCostCentre :: GHC.Internal.Maybe.Maybe (GHC.Internal.Ptr.Ptr GHC.Internal.Stack.CCS.CostCentreStack), btrHasCallStack :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.Types.CallStack, btrExecutionStack :: GHC.Internal.Maybe.Maybe [GHC.Internal.ExecutionStack.Internal.Location], btrIpe :: GHC.Internal.Maybe.Maybe [GHC.Internal.Stack.Decode.StackEntry]}
|
|
| 327 | 327 | collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
|
| 328 | 328 | displayBacktraces :: Backtraces -> GHC.Internal.Base.String
|
| 329 | 329 | getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
|
| ... | ... | @@ -11703,7 +11703,7 @@ instance GHC.Internal.Classes.Eq GHC.Internal.Bignum.BigNat.BigNat -- Defined in |
| 11703 | 11703 | instance GHC.Internal.Classes.Eq GHC.Internal.Bignum.Natural.Natural -- Defined in ‘GHC.Internal.Bignum.Natural’
|
| 11704 | 11704 | instance GHC.Internal.Classes.Eq GHC.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.RTS.Flags’
|
| 11705 | 11705 | instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.StableName.StableName a) -- Defined in ‘GHC.Internal.StableName’
|
| 11706 | -instance GHC.Internal.Classes.Eq GHC.Internal.Stack.CloneStack.StackEntry -- Defined in ‘GHC.Internal.Stack.CloneStack’
|
|
| 11706 | +instance GHC.Internal.Classes.Eq GHC.Internal.Stack.Decode.StackEntry -- Defined in ‘GHC.Internal.Stack.Decode’
|
|
| 11707 | 11707 | instance forall (n :: GHC.Internal.TypeNats.Nat). GHC.Internal.Classes.Eq (GHC.Internal.TypeNats.SNat n) -- Defined in ‘GHC.Internal.TypeNats’
|
| 11708 | 11708 | instance GHC.Internal.Classes.Eq GHC.Internal.TypeNats.SomeNat -- Defined in ‘GHC.Internal.TypeNats’
|
| 11709 | 11709 | instance forall (c :: GHC.Internal.Types.Char). GHC.Internal.Classes.Eq (GHC.Internal.TypeLits.SChar c) -- Defined in ‘GHC.Internal.TypeLits’
|
| ... | ... | @@ -13164,7 +13164,8 @@ instance GHC.Internal.Show.Show GHC.RTS.Flags.ProfFlags -- Defined in ‘GHC.RTS |
| 13164 | 13164 | instance GHC.Internal.Show.Show GHC.RTS.Flags.RTSFlags -- Defined in ‘GHC.RTS.Flags’
|
| 13165 | 13165 | instance GHC.Internal.Show.Show GHC.RTS.Flags.TickyFlags -- Defined in ‘GHC.RTS.Flags’
|
| 13166 | 13166 | instance GHC.Internal.Show.Show GHC.RTS.Flags.TraceFlags -- Defined in ‘GHC.RTS.Flags’
|
| 13167 | -instance GHC.Internal.Show.Show GHC.Internal.Stack.CloneStack.StackEntry -- Defined in ‘GHC.Internal.Stack.CloneStack’
|
|
| 13167 | +instance GHC.Internal.Show.Show GHC.Internal.Stack.Decode.Pointerness -- Defined in ‘GHC.Internal.Stack.Decode’
|
|
| 13168 | +instance GHC.Internal.Show.Show GHC.Internal.Stack.Decode.StackEntry -- Defined in ‘GHC.Internal.Stack.Decode’
|
|
| 13168 | 13169 | instance GHC.Internal.Show.Show GHC.Internal.StaticPtr.StaticPtrInfo -- Defined in ‘GHC.Internal.StaticPtr’
|
| 13169 | 13170 | instance [safe] GHC.Internal.Show.Show GHC.Stats.GCDetails -- Defined in ‘GHC.Stats’
|
| 13170 | 13171 | instance [safe] GHC.Internal.Show.Show GHC.Stats.RTSStats -- Defined in ‘GHC.Stats’
|
| ... | ... | @@ -323,7 +323,7 @@ module Control.Exception.Backtrace where |
| 323 | 323 | type BacktraceMechanism :: *
|
| 324 | 324 | data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
|
| 325 | 325 | type Backtraces :: *
|
| 326 | - data Backtraces = Backtraces {btrCostCentre :: GHC.Internal.Maybe.Maybe (GHC.Internal.Ptr.Ptr GHC.Internal.Stack.CCS.CostCentreStack), btrHasCallStack :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.Types.CallStack, btrExecutionStack :: GHC.Internal.Maybe.Maybe [GHC.Internal.ExecutionStack.Internal.Location], btrIpe :: GHC.Internal.Maybe.Maybe [GHC.Internal.Stack.CloneStack.StackEntry]}
|
|
| 326 | + data Backtraces = Backtraces {btrCostCentre :: GHC.Internal.Maybe.Maybe (GHC.Internal.Ptr.Ptr GHC.Internal.Stack.CCS.CostCentreStack), btrHasCallStack :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.Types.CallStack, btrExecutionStack :: GHC.Internal.Maybe.Maybe [GHC.Internal.ExecutionStack.Internal.Location], btrIpe :: GHC.Internal.Maybe.Maybe [GHC.Internal.Stack.Decode.StackEntry]}
|
|
| 327 | 327 | collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
|
| 328 | 328 | displayBacktraces :: Backtraces -> GHC.Internal.Base.String
|
| 329 | 329 | getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
|
| ... | ... | @@ -14738,7 +14738,7 @@ instance GHC.Internal.Classes.Eq GHC.Internal.Bignum.BigNat.BigNat -- Defined in |
| 14738 | 14738 | instance GHC.Internal.Classes.Eq GHC.Internal.Bignum.Natural.Natural -- Defined in ‘GHC.Internal.Bignum.Natural’
|
| 14739 | 14739 | instance GHC.Internal.Classes.Eq GHC.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.RTS.Flags’
|
| 14740 | 14740 | instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.StableName.StableName a) -- Defined in ‘GHC.Internal.StableName’
|
| 14741 | -instance GHC.Internal.Classes.Eq GHC.Internal.Stack.CloneStack.StackEntry -- Defined in ‘GHC.Internal.Stack.CloneStack’
|
|
| 14741 | +instance GHC.Internal.Classes.Eq GHC.Internal.Stack.Decode.StackEntry -- Defined in ‘GHC.Internal.Stack.Decode’
|
|
| 14742 | 14742 | instance forall (n :: GHC.Internal.TypeNats.Nat). GHC.Internal.Classes.Eq (GHC.Internal.TypeNats.SNat n) -- Defined in ‘GHC.Internal.TypeNats’
|
| 14743 | 14743 | instance GHC.Internal.Classes.Eq GHC.Internal.TypeNats.SomeNat -- Defined in ‘GHC.Internal.TypeNats’
|
| 14744 | 14744 | instance forall (c :: GHC.Internal.Types.Char). GHC.Internal.Classes.Eq (GHC.Internal.TypeLits.SChar c) -- Defined in ‘GHC.Internal.TypeLits’
|
| ... | ... | @@ -16196,7 +16196,8 @@ instance GHC.Internal.Show.Show GHC.RTS.Flags.ProfFlags -- Defined in ‘GHC.RTS |
| 16196 | 16196 | instance GHC.Internal.Show.Show GHC.RTS.Flags.RTSFlags -- Defined in ‘GHC.RTS.Flags’
|
| 16197 | 16197 | instance GHC.Internal.Show.Show GHC.RTS.Flags.TickyFlags -- Defined in ‘GHC.RTS.Flags’
|
| 16198 | 16198 | instance GHC.Internal.Show.Show GHC.RTS.Flags.TraceFlags -- Defined in ‘GHC.RTS.Flags’
|
| 16199 | -instance GHC.Internal.Show.Show GHC.Internal.Stack.CloneStack.StackEntry -- Defined in ‘GHC.Internal.Stack.CloneStack’
|
|
| 16199 | +instance GHC.Internal.Show.Show GHC.Internal.Stack.Decode.Pointerness -- Defined in ‘GHC.Internal.Stack.Decode’
|
|
| 16200 | +instance GHC.Internal.Show.Show GHC.Internal.Stack.Decode.StackEntry -- Defined in ‘GHC.Internal.Stack.Decode’
|
|
| 16200 | 16201 | instance GHC.Internal.Show.Show GHC.Internal.StaticPtr.StaticPtrInfo -- Defined in ‘GHC.Internal.StaticPtr’
|
| 16201 | 16202 | instance [safe] GHC.Internal.Show.Show GHC.Stats.GCDetails -- Defined in ‘GHC.Stats’
|
| 16202 | 16203 | instance [safe] GHC.Internal.Show.Show GHC.Stats.RTSStats -- Defined in ‘GHC.Stats’
|
| ... | ... | @@ -323,7 +323,7 @@ module Control.Exception.Backtrace where |
| 323 | 323 | type BacktraceMechanism :: *
|
| 324 | 324 | data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
|
| 325 | 325 | type Backtraces :: *
|
| 326 | - data Backtraces = Backtraces {btrCostCentre :: GHC.Internal.Maybe.Maybe (GHC.Internal.Ptr.Ptr GHC.Internal.Stack.CCS.CostCentreStack), btrHasCallStack :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.Types.CallStack, btrExecutionStack :: GHC.Internal.Maybe.Maybe [GHC.Internal.ExecutionStack.Internal.Location], btrIpe :: GHC.Internal.Maybe.Maybe [GHC.Internal.Stack.CloneStack.StackEntry]}
|
|
| 326 | + data Backtraces = Backtraces {btrCostCentre :: GHC.Internal.Maybe.Maybe (GHC.Internal.Ptr.Ptr GHC.Internal.Stack.CCS.CostCentreStack), btrHasCallStack :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.Types.CallStack, btrExecutionStack :: GHC.Internal.Maybe.Maybe [GHC.Internal.ExecutionStack.Internal.Location], btrIpe :: GHC.Internal.Maybe.Maybe [GHC.Internal.Stack.Decode.StackEntry]}
|
|
| 327 | 327 | collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
|
| 328 | 328 | displayBacktraces :: Backtraces -> GHC.Internal.Base.String
|
| 329 | 329 | getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
|
| ... | ... | @@ -11959,7 +11959,7 @@ instance GHC.Internal.Classes.Eq GHC.Internal.Bignum.BigNat.BigNat -- Defined in |
| 11959 | 11959 | instance GHC.Internal.Classes.Eq GHC.Internal.Bignum.Natural.Natural -- Defined in ‘GHC.Internal.Bignum.Natural’
|
| 11960 | 11960 | instance GHC.Internal.Classes.Eq GHC.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.RTS.Flags’
|
| 11961 | 11961 | instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.StableName.StableName a) -- Defined in ‘GHC.Internal.StableName’
|
| 11962 | -instance GHC.Internal.Classes.Eq GHC.Internal.Stack.CloneStack.StackEntry -- Defined in ‘GHC.Internal.Stack.CloneStack’
|
|
| 11962 | +instance GHC.Internal.Classes.Eq GHC.Internal.Stack.Decode.StackEntry -- Defined in ‘GHC.Internal.Stack.Decode’
|
|
| 11963 | 11963 | instance forall (n :: GHC.Internal.TypeNats.Nat). GHC.Internal.Classes.Eq (GHC.Internal.TypeNats.SNat n) -- Defined in ‘GHC.Internal.TypeNats’
|
| 11964 | 11964 | instance GHC.Internal.Classes.Eq GHC.Internal.TypeNats.SomeNat -- Defined in ‘GHC.Internal.TypeNats’
|
| 11965 | 11965 | instance forall (c :: GHC.Internal.Types.Char). GHC.Internal.Classes.Eq (GHC.Internal.TypeLits.SChar c) -- Defined in ‘GHC.Internal.TypeLits’
|
| ... | ... | @@ -13436,7 +13436,8 @@ instance GHC.Internal.Show.Show GHC.RTS.Flags.ProfFlags -- Defined in ‘GHC.RTS |
| 13436 | 13436 | instance GHC.Internal.Show.Show GHC.RTS.Flags.RTSFlags -- Defined in ‘GHC.RTS.Flags’
|
| 13437 | 13437 | instance GHC.Internal.Show.Show GHC.RTS.Flags.TickyFlags -- Defined in ‘GHC.RTS.Flags’
|
| 13438 | 13438 | instance GHC.Internal.Show.Show GHC.RTS.Flags.TraceFlags -- Defined in ‘GHC.RTS.Flags’
|
| 13439 | -instance GHC.Internal.Show.Show GHC.Internal.Stack.CloneStack.StackEntry -- Defined in ‘GHC.Internal.Stack.CloneStack’
|
|
| 13439 | +instance GHC.Internal.Show.Show GHC.Internal.Stack.Decode.Pointerness -- Defined in ‘GHC.Internal.Stack.Decode’
|
|
| 13440 | +instance GHC.Internal.Show.Show GHC.Internal.Stack.Decode.StackEntry -- Defined in ‘GHC.Internal.Stack.Decode’
|
|
| 13440 | 13441 | instance GHC.Internal.Show.Show GHC.Internal.StaticPtr.StaticPtrInfo -- Defined in ‘GHC.Internal.StaticPtr’
|
| 13441 | 13442 | instance [safe] GHC.Internal.Show.Show GHC.Stats.GCDetails -- Defined in ‘GHC.Stats’
|
| 13442 | 13443 | instance [safe] GHC.Internal.Show.Show GHC.Stats.RTSStats -- Defined in ‘GHC.Stats’
|
| ... | ... | @@ -323,7 +323,7 @@ module Control.Exception.Backtrace where |
| 323 | 323 | type BacktraceMechanism :: *
|
| 324 | 324 | data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
|
| 325 | 325 | type Backtraces :: *
|
| 326 | - data Backtraces = Backtraces {btrCostCentre :: GHC.Internal.Maybe.Maybe (GHC.Internal.Ptr.Ptr GHC.Internal.Stack.CCS.CostCentreStack), btrHasCallStack :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.Types.CallStack, btrExecutionStack :: GHC.Internal.Maybe.Maybe [GHC.Internal.ExecutionStack.Internal.Location], btrIpe :: GHC.Internal.Maybe.Maybe [GHC.Internal.Stack.CloneStack.StackEntry]}
|
|
| 326 | + data Backtraces = Backtraces {btrCostCentre :: GHC.Internal.Maybe.Maybe (GHC.Internal.Ptr.Ptr GHC.Internal.Stack.CCS.CostCentreStack), btrHasCallStack :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.Types.CallStack, btrExecutionStack :: GHC.Internal.Maybe.Maybe [GHC.Internal.ExecutionStack.Internal.Location], btrIpe :: GHC.Internal.Maybe.Maybe [GHC.Internal.Stack.Decode.StackEntry]}
|
|
| 327 | 327 | collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
|
| 328 | 328 | displayBacktraces :: Backtraces -> GHC.Internal.Base.String
|
| 329 | 329 | getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
|
| ... | ... | @@ -11703,7 +11703,7 @@ instance GHC.Internal.Classes.Eq GHC.Internal.Bignum.BigNat.BigNat -- Defined in |
| 11703 | 11703 | instance GHC.Internal.Classes.Eq GHC.Internal.Bignum.Natural.Natural -- Defined in ‘GHC.Internal.Bignum.Natural’
|
| 11704 | 11704 | instance GHC.Internal.Classes.Eq GHC.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.RTS.Flags’
|
| 11705 | 11705 | instance forall a. GHC.Internal.Classes.Eq (GHC.Internal.StableName.StableName a) -- Defined in ‘GHC.Internal.StableName’
|
| 11706 | -instance GHC.Internal.Classes.Eq GHC.Internal.Stack.CloneStack.StackEntry -- Defined in ‘GHC.Internal.Stack.CloneStack’
|
|
| 11706 | +instance GHC.Internal.Classes.Eq GHC.Internal.Stack.Decode.StackEntry -- Defined in ‘GHC.Internal.Stack.Decode’
|
|
| 11707 | 11707 | instance forall (n :: GHC.Internal.TypeNats.Nat). GHC.Internal.Classes.Eq (GHC.Internal.TypeNats.SNat n) -- Defined in ‘GHC.Internal.TypeNats’
|
| 11708 | 11708 | instance GHC.Internal.Classes.Eq GHC.Internal.TypeNats.SomeNat -- Defined in ‘GHC.Internal.TypeNats’
|
| 11709 | 11709 | instance forall (c :: GHC.Internal.Types.Char). GHC.Internal.Classes.Eq (GHC.Internal.TypeLits.SChar c) -- Defined in ‘GHC.Internal.TypeLits’
|
| ... | ... | @@ -13164,7 +13164,8 @@ instance GHC.Internal.Show.Show GHC.RTS.Flags.ProfFlags -- Defined in ‘GHC.RTS |
| 13164 | 13164 | instance GHC.Internal.Show.Show GHC.RTS.Flags.RTSFlags -- Defined in ‘GHC.RTS.Flags’
|
| 13165 | 13165 | instance GHC.Internal.Show.Show GHC.RTS.Flags.TickyFlags -- Defined in ‘GHC.RTS.Flags’
|
| 13166 | 13166 | instance GHC.Internal.Show.Show GHC.RTS.Flags.TraceFlags -- Defined in ‘GHC.RTS.Flags’
|
| 13167 | -instance GHC.Internal.Show.Show GHC.Internal.Stack.CloneStack.StackEntry -- Defined in ‘GHC.Internal.Stack.CloneStack’
|
|
| 13167 | +instance GHC.Internal.Show.Show GHC.Internal.Stack.Decode.Pointerness -- Defined in ‘GHC.Internal.Stack.Decode’
|
|
| 13168 | +instance GHC.Internal.Show.Show GHC.Internal.Stack.Decode.StackEntry -- Defined in ‘GHC.Internal.Stack.Decode’
|
|
| 13168 | 13169 | instance GHC.Internal.Show.Show GHC.Internal.StaticPtr.StaticPtrInfo -- Defined in ‘GHC.Internal.StaticPtr’
|
| 13169 | 13170 | instance [safe] GHC.Internal.Show.Show GHC.Stats.GCDetails -- Defined in ‘GHC.Stats’
|
| 13170 | 13171 | instance [safe] GHC.Internal.Show.Show GHC.Stats.RTSStats -- Defined in ‘GHC.Stats’
|