ghc-debug-common-0.2.0.0: Connect to a socket created by ghc-debug-stub and analyse the heap of the debuggee program.
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Debug.Types

Synopsis

Documentation

data Request a where Source #

A request sent from the debugger to the debuggee parametrized on the result type.

Constructors

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 ConstrClosure

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

Instances

Instances details
Show (Request a) Source # 
Instance details

Defined in GHC.Debug.Types

Methods

showsPrec :: Int -> Request a -> ShowS #

show :: Request a -> String #

showList :: [Request a] -> ShowS #

Eq (Request a) Source # 
Instance details

Defined in GHC.Debug.Types

Methods

(==) :: Request a -> Request a -> Bool #

(/=) :: Request a -> Request a -> Bool #

Hashable (Request a) Source # 
Instance details

Defined in GHC.Debug.Types

Methods

hashWithSalt :: Int -> Request a -> Int #

hash :: Request a -> Int #

data ForkOrPause Source #

The decision about whether to fork the running process or pause it running whilst we are debugging it.

Constructors

Pause 
Fork 

Instances

Instances details
Enum ForkOrPause Source # 
Instance details

Defined in GHC.Debug.Types

Show ForkOrPause Source # 
Instance details

Defined in GHC.Debug.Types

Binary ForkOrPause Source # 
Instance details

Defined in GHC.Debug.Types

Eq ForkOrPause Source # 
Instance details

Defined in GHC.Debug.Types

Ord ForkOrPause Source # 
Instance details

Defined in GHC.Debug.Types

Hashable ForkOrPause Source # 
Instance details

Defined in GHC.Debug.Types

doRequest :: MVar Handle -> Request a -> IO a Source #

Perform a request

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 AnyReq Source #

Constructors

forall req. AnyReq !(Request req) 

Instances

Instances details
Eq AnyReq Source # 
Instance details

Defined in GHC.Debug.Types

Methods

(==) :: AnyReq -> AnyReq -> Bool #

(/=) :: AnyReq -> AnyReq -> Bool #

Hashable AnyReq Source # 
Instance details

Defined in GHC.Debug.Types

Methods

hashWithSalt :: Int -> AnyReq -> Int #

hash :: AnyReq -> Int #

data AnyResp Source #

Constructors

forall a. AnyResp !a !(a -> Put) 

newtype CommandId Source #

Constructors

CommandId Word32 

Instances

Instances details
Show CommandId Source # 
Instance details

Defined in GHC.Debug.Types

Binary CommandId Source # 
Instance details

Defined in GHC.Debug.Types

Eq CommandId Source # 
Instance details

Defined in GHC.Debug.Types

Ord CommandId Source # 
Instance details

Defined in GHC.Debug.Types

Hashable CommandId Source # 
Instance details

Defined in GHC.Debug.Types

data ClosureType #

Instances

Instances details
Enum ClosureType 
Instance details

Defined in GHC.Exts.Heap.ClosureTypes

Generic ClosureType 
Instance details

Defined in GHC.Exts.Heap.ClosureTypes

Associated Types

type Rep ClosureType :: Type -> Type #

Show ClosureType 
Instance details

Defined in GHC.Exts.Heap.ClosureTypes

Eq ClosureType 
Instance details

Defined in GHC.Exts.Heap.ClosureTypes

Ord ClosureType 
Instance details

Defined in GHC.Exts.Heap.ClosureTypes

type Rep ClosureType 
Instance details

Defined in GHC.Exts.Heap.ClosureTypes

type Rep ClosureType = D1 ('MetaData "ClosureType" "GHC.Exts.Heap.ClosureTypes" "ghc-heap-9.2.1" 'False) ((((((C1 ('MetaCons "INVALID_OBJECT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CONSTR" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CONSTR_1_0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CONSTR_0_1" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CONSTR_2_0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CONSTR_1_1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CONSTR_0_2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CONSTR_NOCAF" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "FUN" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FUN_1_0" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FUN_0_1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FUN_2_0" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "FUN_1_1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FUN_0_2" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FUN_STATIC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "THUNK" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "THUNK_1_0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "THUNK_0_1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "THUNK_2_0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "THUNK_1_1" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "THUNK_0_2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "THUNK_STATIC" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "THUNK_SELECTOR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BCO" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "AP" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PAP" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AP_STACK" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IND" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "IND_STATIC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RET_BCO" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RET_SMALL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RET_BIG" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: (((((C1 ('MetaCons "RET_FUN" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UPDATE_FRAME" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CATCH_FRAME" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UNDERFLOW_FRAME" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "STOP_FRAME" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BLOCKING_QUEUE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BLACKHOLE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MVAR_CLEAN" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "MVAR_DIRTY" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TVAR" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ARR_WORDS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MUT_ARR_PTRS_CLEAN" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MUT_ARR_PTRS_DIRTY" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MUT_ARR_PTRS_FROZEN_DIRTY" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MUT_ARR_PTRS_FROZEN_CLEAN" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MUT_VAR_CLEAN" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "MUT_VAR_DIRTY" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WEAK" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PRIM" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MUT_PRIM" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TSO" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "STACK" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TREC_CHUNK" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ATOMICALLY_FRAME" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "CATCH_RETRY_FRAME" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CATCH_STM_FRAME" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WHITEHOLE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SMALL_MUT_ARR_PTRS_CLEAN" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "SMALL_MUT_ARR_PTRS_DIRTY" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SMALL_MUT_ARR_PTRS_FROZEN_DIRTY" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SMALL_MUT_ARR_PTRS_FROZEN_CLEAN" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "COMPACT_NFDATA" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "N_CLOSURE_TYPES" 'PrefixI 'False) (U1 :: Type -> Type))))))))

Serialisation functions