Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- module GHC.Debug.Types.Ptr
- module GHC.Debug.Types.Closures
- data Request a where
- RequestVersion :: Request Word32
- RequestPause :: ForkOrPause -> Request ()
- RequestResume :: Request ()
- RequestRoots :: Request [ClosurePtr]
- RequestClosure :: ClosurePtr -> Request RawClosure
- RequestInfoTable :: InfoTablePtr -> Request (StgInfoTableWithPtr, RawInfoTable)
- RequestPoll :: Request ()
- RequestSavedObjects :: Request [ClosurePtr]
- RequestStackBitmap :: StackPtr -> Word32 -> Request PtrBitmap
- RequestFunBitmap :: Word16 -> ClosurePtr -> Request PtrBitmap
- RequestConstrDesc :: InfoTablePtr -> Request ConstrDesc
- RequestSourceInfo :: InfoTablePtr -> Request (Maybe SourceInformation)
- RequestAllBlocks :: Request [RawBlock]
- RequestBlock :: ClosurePtr -> Request RawBlock
- data ForkOrPause
- requestCommandId :: Request a -> CommandId
- doRequest :: MVar Handle -> Request a -> IO a
- isWriteRequest :: Request a -> Bool
- withWriteRequest :: Request a -> r a -> (a ~ () => Request a -> r a) -> r a
- isImmutableRequest :: Request a -> Bool
- data AnyReq = forall req. AnyReq !(Request req)
- data AnyResp = forall a. AnyResp !a !(a -> Put)
- newtype CommandId = CommandId Word32
- data SourceInformation = SourceInformation {
- infoName :: !String
- infoClosureType :: !ClosureType
- infoType :: !String
- infoLabel :: !String
- infoModule :: !String
- infoPosition :: !String
- data ClosureType
- = INVALID_OBJECT
- | CONSTR
- | CONSTR_1_0
- | CONSTR_0_1
- | CONSTR_2_0
- | CONSTR_1_1
- | CONSTR_0_2
- | CONSTR_NOCAF
- | FUN
- | FUN_1_0
- | FUN_0_1
- | FUN_2_0
- | FUN_1_1
- | FUN_0_2
- | FUN_STATIC
- | THUNK
- | THUNK_1_0
- | THUNK_0_1
- | THUNK_2_0
- | THUNK_1_1
- | THUNK_0_2
- | THUNK_STATIC
- | THUNK_SELECTOR
- | BCO
- | AP
- | PAP
- | AP_STACK
- | IND
- | IND_STATIC
- | RET_BCO
- | RET_SMALL
- | RET_BIG
- | RET_FUN
- | UPDATE_FRAME
- | CATCH_FRAME
- | UNDERFLOW_FRAME
- | STOP_FRAME
- | BLOCKING_QUEUE
- | BLACKHOLE
- | MVAR_CLEAN
- | MVAR_DIRTY
- | TVAR
- | ARR_WORDS
- | MUT_ARR_PTRS_CLEAN
- | MUT_ARR_PTRS_DIRTY
- | MUT_ARR_PTRS_FROZEN_DIRTY
- | MUT_ARR_PTRS_FROZEN_CLEAN
- | MUT_VAR_CLEAN
- | MUT_VAR_DIRTY
- | WEAK
- | PRIM
- | MUT_PRIM
- | TSO
- | STACK
- | TREC_CHUNK
- | ATOMICALLY_FRAME
- | CATCH_RETRY_FRAME
- | CATCH_STM_FRAME
- | WHITEHOLE
- | SMALL_MUT_ARR_PTRS_CLEAN
- | SMALL_MUT_ARR_PTRS_DIRTY
- | SMALL_MUT_ARR_PTRS_FROZEN_DIRTY
- | SMALL_MUT_ARR_PTRS_FROZEN_CLEAN
- | COMPACT_NFDATA
- | N_CLOSURE_TYPES
- getIPE :: Get (Maybe SourceInformation)
- putIPE :: Maybe SourceInformation -> Put
- getInfoTable :: Get (StgInfoTable, RawInfoTable)
- putInfoTable :: RawInfoTable -> Put
- putRequest :: Request a -> Put
- getRequest :: Get AnyReq
Documentation
module GHC.Debug.Types.Ptr
module GHC.Debug.Types.Closures
A request sent from the debugger to the debuggee parametrized on the result type.
RequestVersion :: Request Word32 | Request protocol version |
RequestPause :: ForkOrPause -> Request () | Pause the debuggee. |
RequestResume :: Request () | Resume the debuggee. |
RequestRoots :: Request [ClosurePtr] | Request the debuggee's root pointers. |
RequestClosure :: ClosurePtr -> Request RawClosure | Request a closure |
RequestInfoTable :: InfoTablePtr -> Request (StgInfoTableWithPtr, RawInfoTable) | Request an info table |
RequestPoll :: Request () | Wait for the debuggee to pause itself and then execute an action. It currently impossible to resume after a pause caused by a poll. |
RequestSavedObjects :: Request [ClosurePtr] | A client can save objects by calling a special RTS method This function returns the closures it saved. |
RequestStackBitmap :: StackPtr -> Word32 -> Request PtrBitmap | Request the pointer bitmap for a stack frame at a given offset from a StackPtr. |
RequestFunBitmap :: Word16 -> ClosurePtr -> Request PtrBitmap | Decode the bitmap contained in a StgFunInfoTable Used by PAP and AP closure types. |
RequestConstrDesc :: InfoTablePtr -> Request ConstrDesc | Request the constructor description for an info table.
The info table must be from a |
RequestSourceInfo :: InfoTablePtr -> Request (Maybe SourceInformation) | Lookup source information of an info table |
RequestAllBlocks :: Request [RawBlock] | Copy all blocks from the process at once |
RequestBlock :: ClosurePtr -> Request RawBlock | Request the block which contains a specific pointer |
data ForkOrPause Source #
The decision about whether to fork the running process or pause it running whilst we are debugging it.
Instances
requestCommandId :: Request a -> CommandId Source #
isWriteRequest :: Request a -> Bool Source #
Whether a request mutates the debuggee state, don't cache these ones
withWriteRequest :: Request a -> r a -> (a ~ () => Request a -> r a) -> r a Source #
isImmutableRequest :: Request a -> Bool Source #
Requests which will always answer the same. For example, info tables are immutable and so requesting an info table will always result in the same value and is safe to cache across pause lines.
data SourceInformation Source #
SourceInformation | |
|
Instances
Show SourceInformation Source # | |
Defined in GHC.Debug.Types showsPrec :: Int -> SourceInformation -> ShowS # show :: SourceInformation -> String # showList :: [SourceInformation] -> ShowS # | |
Eq SourceInformation Source # | |
Defined in GHC.Debug.Types (==) :: SourceInformation -> SourceInformation -> Bool # (/=) :: SourceInformation -> SourceInformation -> Bool # | |
Ord SourceInformation Source # | |
Defined in GHC.Debug.Types compare :: SourceInformation -> SourceInformation -> Ordering # (<) :: SourceInformation -> SourceInformation -> Bool # (<=) :: SourceInformation -> SourceInformation -> Bool # (>) :: SourceInformation -> SourceInformation -> Bool # (>=) :: SourceInformation -> SourceInformation -> Bool # max :: SourceInformation -> SourceInformation -> SourceInformation # min :: SourceInformation -> SourceInformation -> SourceInformation # |
data ClosureType #
Instances
Serialisation functions
putInfoTable :: RawInfoTable -> Put Source #
putRequest :: Request a -> Put Source #
getRequest :: Get AnyReq Source #