Safe Haskell | None |
---|---|
Language | Haskell2010 |
GHC.Debug.Client
Description
The main API for creating debuggers. For example, this API can be used to connect to an instrumented process, query the GC roots and then decode the first root up to depth 10 and displayed to the user.
main = withDebuggeeConnect "/tmp/ghc-debug" p1 p1 :: Debuggee -> IO () p1 e = do pause e g <- run e $ do precacheBlocks (r:_) <- gcRoots buildHeapGraph (Just 10) r putStrLn (ppHeapGraph (const "") g)
Synopsis
- data Debuggee
- type DebugM = DebugM
- debuggeeRun :: FilePath -> FilePath -> IO Debuggee
- debuggeeConnect :: FilePath -> IO Debuggee
- debuggeeClose :: Debuggee -> IO ()
- withDebuggeeRun :: FilePath -> FilePath -> (Debuggee -> IO a) -> IO a
- withDebuggeeConnect :: FilePath -> (Debuggee -> IO a) -> IO a
- socketDirectory :: IO FilePath
- snapshotRun :: FilePath -> (Debuggee -> IO a) -> IO a
- run :: Debuggee -> DebugM a -> IO a
- runTrace :: Debuggee -> DebugM a -> IO a
- runAnalysis :: DebugM a -> (a -> IO r) -> Debuggee -> IO r
- pause :: Debuggee -> IO ()
- fork :: Debuggee -> IO ()
- pauseThen :: Debuggee -> DebugM b -> IO b
- resume :: Debuggee -> IO ()
- pausePoll :: Debuggee -> IO ()
- withPause :: Debuggee -> IO a -> IO a
- version :: DebugM Version
- gcRoots :: DebugM [ClosurePtr]
- allBlocks :: DebugM [RawBlock]
- getSourceInfo :: InfoTablePtr -> DebugM (Maybe SourceInformation)
- savedObjects :: DebugM [ClosurePtr]
- precacheBlocks :: DebugM [RawBlock]
- dereferenceClosure :: ClosurePtr -> DebugM SizedClosure
- dereferenceToClosurePtr :: SizedClosure -> DebugM SizedClosureP
- addConstrDesc :: SizedClosure -> DebugM SizedClosureC
- requestCCSMain :: DebugM CCSPtr
- dereferenceClosures :: [ClosurePtr] -> DebugM [SizedClosure]
- dereferenceStack :: StackCont -> DebugM StackFrames
- dereferencePapPayload :: PayloadCont -> DebugM PapPayload
- dereferenceConDesc :: ConstrDescCont -> DebugM ConstrDesc
- dereferenceInfoTable :: InfoTablePtr -> DebugM StgInfoTable
- dereferenceIndexTable :: IndexTablePtr -> DebugM IndexTable
- dereferenceSRT :: InfoTablePtr -> DebugM SrtPayload
- dereferenceCCS :: CCSPtr -> DebugM CCSPayload
- dereferenceCC :: CCPtr -> DebugM CCPayload
- class Hextraversable (m :: Type -> Type -> Type -> Type -> Type -> Type -> Type) where
- hextraverse :: Applicative f => (a -> f b) -> (c -> f d) -> (e -> f g) -> (h -> f i) -> (j -> f k) -> (l -> f n) -> m a c e h j l -> f (m b d g i k n)
- buildHeapGraph :: Maybe Int -> ClosurePtr -> DebugM (HeapGraph Size)
- multiBuildHeapGraph :: Maybe Int -> NonEmpty ClosurePtr -> DebugM (HeapGraph Size)
- data HeapGraph a = HeapGraph {
- roots :: !(NonEmpty ClosurePtr)
- graph :: !(IntMap (HeapGraphEntry a))
- data HeapGraphEntry a = HeapGraphEntry {
- hgeClosurePtr :: ClosurePtr
- hgeClosure :: DebugClosure CCSPtr SrtHI PapHI ConstrDesc StackHI (Maybe HeapGraphIndex)
- hgeData :: a
- ppHeapGraph :: (a -> String) -> HeapGraph a -> String
- traceWrite :: (DebugMonad m, Show a) => a -> m ()
- traceMsg :: DebugMonad m => String -> m ()
- saveCache :: DebugMonad m => FilePath -> m ()
- loadCache :: DebugMonad m => FilePath -> m ()
- allClosures :: DebugClosure ccs (GenSrtPayload c) (GenPapPayload c) a (GenStackFrames (GenSrtPayload c) c) c -> [c]
- dcSize :: DebugClosureWithSize ccs srt pap string s b -> Size
- hexmap :: forall a b c d e f g h i j k l t. Hextraversable t => (a -> b) -> (c -> d) -> (e -> f) -> (g -> h) -> (i -> j) -> (k -> l) -> t a c e g i k -> t b d f h j l
- noSize :: DebugClosureWithSize ccs srt pap string s b -> DebugClosure ccs srt pap string s b
- parseConstrDesc :: String -> ConstrDesc
- data CCPayload = CCPayload {}
- type CCSPayload = GenCCSPayload CCSPtr CCPtr
- type Closure = DebugClosure CCSPtr SrtCont PayloadCont ConstrDescCont StackCont ClosurePtr
- 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
- | CONTINUATION
- | N_CLOSURE_TYPES
- data ConstrDesc = ConstrDesc {}
- type ConstrDescCont = InfoTablePtr
- data DebugClosure ccs srt pap string s b
- = ConstrClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- ptrArgs :: ![b]
- dataArgs :: ![Word]
- constrDesc :: !string
- | FunClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- srt :: !srt
- ptrArgs :: ![b]
- dataArgs :: ![Word]
- | ThunkClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- srt :: !srt
- ptrArgs :: ![b]
- dataArgs :: ![Word]
- | SelectorClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- selectee :: !b
- | PAPClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- arity :: !HalfWord
- n_args :: !HalfWord
- fun :: !b
- pap_payload :: !pap
- | APClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- arity :: !HalfWord
- n_args :: !HalfWord
- fun :: !b
- ap_payload :: !pap
- | APStackClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- ap_st_size :: !Word
- fun :: !b
- payload :: !s
- | IndClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- indirectee :: !b
- | BCOClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- instrs :: !b
- literals :: !b
- bcoptrs :: !b
- arity :: !HalfWord
- size :: !HalfWord
- bitmap :: !PtrBitmap
- | BlackholeClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- indirectee :: !b
- | ArrWordsClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- bytes :: !Word
- arrWords :: ![Word]
- | MutArrClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- mccPtrs :: !Word
- mccSize :: !Word
- mccPayload :: ![b]
- | SmallMutArrClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- mccPtrs :: !Word
- mccPayload :: ![b]
- | MVarClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- queueHead :: !b
- queueTail :: !b
- value :: !b
- | MutVarClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- var :: !b
- | BlockingQueueClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- link :: !b
- blackHole :: !b
- owner :: !b
- queue :: !b
- | TSOClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- _link :: !b
- global_link :: !b
- tsoStack :: !b
- trec :: !b
- blocked_exceptions :: !b
- bq :: !b
- threadLabel :: !(Maybe b)
- what_next :: WhatNext
- why_blocked :: WhyBlocked
- flags :: [TsoFlags]
- threadId :: Word64
- saved_errno :: Word32
- dirty :: Word32
- alloc_limit :: Int64
- tot_stack_size :: Word32
- prof :: Maybe StgTSOProfInfo
- | StackClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- stack_size :: !Word32
- stack_dirty :: !Word8
- stack_marking :: !Word8
- frames :: s
- | WeakClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- cfinalizers :: !b
- key :: !b
- value :: !b
- finalizer :: !b
- mlink :: !(Maybe b)
- | TVarClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- current_value :: !b
- tvar_watch_queue :: !b
- num_updates :: !Int
- | TRecChunkClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- prev_chunk :: !b
- next_idx :: !Word
- entries :: ![TRecEntry b]
- | MutPrimClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- ptrArgs :: ![b]
- dataArgs :: ![Word]
- | PrimClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- ptrArgs :: ![b]
- dataArgs :: ![Word]
- | OtherClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- hvalues :: ![b]
- rawWords :: ![Word]
- | UnsupportedClosure {
- info :: !StgInfoTableWithPtr
- profHeader :: Maybe (ProfHeader ccs)
- = ConstrClosure {
- data DebugClosureWithExtra x ccs srt pap string s b = DCS {
- extraDCS :: x
- unDCS :: DebugClosure ccs srt pap string s b
- type DebugClosureWithSize = DebugClosureWithExtra Size
- data DebugStackFrame srt b = DebugStackFrame {
- frame_info :: !StgInfoTableWithPtr
- frame_srt :: srt
- values :: [FieldValue b]
- data FieldValue b
- data GenCCSPayload ccsPtr ccPtr = CCSPayload {
- ccsID :: !Int64
- ccsCc :: ccPtr
- ccsPrevStack :: Maybe ccsPtr
- ccsIndexTable :: Maybe IndexTablePtr
- ccsRoot :: Maybe CCSPtr
- ccsDepth :: Word
- ccsSccCount :: Word64
- ccsSelected :: Word
- ccsTimeTicks :: Word
- ccsMemAlloc :: Word64
- ccsInheritedAlloc :: Word64
- ccsInheritedTicks :: Word
- newtype GenPapPayload b = GenPapPayload {
- getValues :: [FieldValue b]
- newtype GenSrtPayload b = GenSrtPayload {}
- newtype GenStackFrames srt b = GenStackFrames {
- getFrames :: [DebugStackFrame srt b]
- class Hextraversable (m :: Type -> Type -> Type -> Type -> Type -> Type -> Type) where
- hextraverse :: Applicative f => (a -> f b) -> (c -> f d) -> (e -> f g) -> (h -> f i) -> (j -> f k) -> (l -> f n) -> m a c e h j l -> f (m b d g i k n)
- newtype InclusiveSize = InclusiveSize {}
- data IndexTable = IndexTable {}
- type PapPayload = GenPapPayload ClosurePtr
- data PayloadCont = PayloadCont ClosurePtr [Word64]
- data ProfHeader a = ProfHeader {
- ccs :: a
- hp :: ProfHeaderWord
- type ProfHeaderWithPtr = ProfHeader CCSPtr
- data ProfHeaderWord
- = RetainerHeader {
- trav :: !Bool
- retainerSet :: !RetainerSetPtr
- | LDVWord {
- state :: !Bool
- creationTime :: !Word32
- lastUseTime :: !Word32
- | EraWord Word64
- | OtherHeader Word64
- = RetainerHeader {
- newtype RetainerSize = RetainerSize {}
- newtype Size = Size {}
- type SizedClosure = DebugClosureWithSize CCSPtr SrtCont PayloadCont ConstrDescCont StackCont ClosurePtr
- type SizedClosureC = DebugClosureWithSize CCSPtr SrtCont PayloadCont ConstrDesc StackCont ClosurePtr
- type SizedClosureP = DebugClosureWithSize CCSPtr SrtPayload PapPayload ConstrDesc StackCont ClosurePtr
- type SrtCont = InfoTablePtr
- type SrtPayload = GenSrtPayload ClosurePtr
- data StackCont = StackCont StackPtr RawStack
- type StackFrames = GenStackFrames SrtCont ClosurePtr
- data StgInfoTable = StgInfoTable {
- ptrs :: HalfWord
- nptrs :: HalfWord
- tipe :: ClosureType
- srtlen :: HalfWord
- data StgInfoTableWithPtr = StgInfoTableWithPtr {}
- data TRecEntry b = TRecEntry {
- tvar :: !b
- expected_value :: !b
- new_value :: !b
- trec_num_updates :: Int
- data TsoFlags
- data WhatNext
- data WhyBlocked
- data SourceInformation = SourceInformation {
- infoName :: !String
- infoClosureType :: !ClosureType
- infoType :: !String
- infoLabel :: !String
- infoModule :: !String
- infoPosition :: !String
- data RawBlock = RawBlock BlockPtr Word16 ByteString
- data BlockPtr
- data StackPtr
- data ClosurePtr
- data InfoTablePtr
- data CCPtr
- data CCSPtr
- data IndexTablePtr
- type StackHI = GenStackFrames (GenSrtPayload (Maybe HeapGraphIndex)) (Maybe HeapGraphIndex)
- type PapHI = GenPapPayload (Maybe HeapGraphIndex)
- type HeapGraphIndex = ClosurePtr
Running/Connecting to a debuggee
Arguments
:: FilePath | path to executable to run as the debuggee |
-> FilePath | filename of socket (e.g. |
-> IO Debuggee |
Run a debuggee and connect to it. Use debuggeeClose
when you're done.
debuggeeClose :: Debuggee -> IO () Source #
Close the connection to the debuggee.
Arguments
:: FilePath | path to executable to run as the debuggee |
-> FilePath | filename of socket (e.g. |
-> (Debuggee -> IO a) | |
-> IO a |
Bracketed version of debuggeeRun
. Runs a debuggee, connects to it, runs
the action, kills the process, then closes the debuggee.
Bracketed version of debuggeeConnect
. Connects to a debuggee, runs the
action, then closes the debuggee.
snapshotRun :: FilePath -> (Debuggee -> IO a) -> IO a Source #
Start an analysis session using a snapshot. This will not connect to a
debuggee. The snapshot is created by snapshot
.
Running DebugM
runAnalysis :: DebugM a -> (a -> IO r) -> Debuggee -> IO r Source #
Perform the given analysis whilst the debuggee is paused, then resume and apply the continuation to the result.
Pause/Resume
pausePoll :: Debuggee -> IO () Source #
Like pause, but wait for the debuggee to pause itself. It currently impossible to resume after a pause caused by a poll.?????????? Is that true???? can we not just call resume????
Basic Requests
gcRoots :: DebugM [ClosurePtr] Source #
Query the debuggee for the list of GC Roots
getSourceInfo :: InfoTablePtr -> DebugM (Maybe SourceInformation) Source #
Query the debuggee for source information about a specific info table.
This requires your executable to be built with -finfo-table-map
.
savedObjects :: DebugM [ClosurePtr] Source #
Query the debuggee for the list of saved objects.
precacheBlocks :: DebugM [RawBlock] Source #
Fetch all the blocks from the debuggee and add them to the block cache
dereferenceClosure :: ClosurePtr -> DebugM SizedClosure Source #
Consult the BlockCache
for the block which contains a specific
closure, if it's not there then try to fetch the right block, if that
fails, call dereferenceClosureDirect
dereferenceClosures :: [ClosurePtr] -> DebugM [SizedClosure] Source #
dereferenceStack :: StackCont -> DebugM StackFrames Source #
Deference some StackFrames from a given StackCont
dereferencePapPayload :: PayloadCont -> DebugM PapPayload Source #
Derference the PapPayload from the PayloadCont
dereferenceCCS :: CCSPtr -> DebugM CCSPayload Source #
class Hextraversable (m :: Type -> Type -> Type -> Type -> Type -> Type -> Type) where #
Methods
hextraverse :: Applicative f => (a -> f b) -> (c -> f d) -> (e -> f g) -> (h -> f i) -> (j -> f k) -> (l -> f n) -> m a c e h j l -> f (m b d g i k n) #
Instances
Hextraversable DebugClosure # | |
Defined in GHC.Debug.Types.Closures Methods hextraverse :: Applicative f => (a -> f b) -> (c -> f d) -> (e -> f g) -> (h -> f i) -> (j -> f k) -> (l -> f n) -> DebugClosure a c e h j l -> f (DebugClosure b d g i k n) # | |
Hextraversable (DebugClosureWithExtra x) # | |
Defined in GHC.Debug.Types.Closures Methods hextraverse :: Applicative f => (a -> f b) -> (c -> f d) -> (e -> f g) -> (h -> f i) -> (j -> f k) -> (l -> f n) -> DebugClosureWithExtra x a c e h j l -> f (DebugClosureWithExtra x b d g i k n) # |
Building a Heap Graph
buildHeapGraph :: Maybe Int -> ClosurePtr -> DebugM (HeapGraph Size) Source #
Build a heap graph starting from the given root. The first argument controls how many levels to recurse. You nearly always want to set this to a small number ~ 10, as otherwise you can easily run out of memory.
multiBuildHeapGraph :: Maybe Int -> NonEmpty ClosurePtr -> DebugM (HeapGraph Size) Source #
Build a heap graph starting from multiple roots. The first argument controls how many levels to recurse. You nearly always want to set this value to a small number ~ 10 as otherwise you can easily run out of memory.
Constructors
HeapGraph | |
Fields
|
Instances
Functor HeapGraph # | |
Foldable HeapGraph # | |
Defined in GHC.Debug.Types.Graph Methods fold :: Monoid m => HeapGraph m -> m # foldMap :: Monoid m => (a -> m) -> HeapGraph a -> m # foldMap' :: Monoid m => (a -> m) -> HeapGraph a -> m # foldr :: (a -> b -> b) -> b -> HeapGraph a -> b # foldr' :: (a -> b -> b) -> b -> HeapGraph a -> b # foldl :: (b -> a -> b) -> b -> HeapGraph a -> b # foldl' :: (b -> a -> b) -> b -> HeapGraph a -> b # foldr1 :: (a -> a -> a) -> HeapGraph a -> a # foldl1 :: (a -> a -> a) -> HeapGraph a -> a # toList :: HeapGraph a -> [a] # length :: HeapGraph a -> Int # elem :: Eq a => a -> HeapGraph a -> Bool # maximum :: Ord a => HeapGraph a -> a # minimum :: Ord a => HeapGraph a -> a # | |
Traversable HeapGraph # | |
Defined in GHC.Debug.Types.Graph | |
Show a => Show (HeapGraph a) # | |
data HeapGraphEntry a #
Constructors
HeapGraphEntry | |
Fields
|
Instances
Printing a heap graph
ppHeapGraph :: (a -> String) -> HeapGraph a -> String #
Tracing
traceWrite :: (DebugMonad m, Show a) => a -> m () Source #
traceMsg :: DebugMonad m => String -> m () Source #
Caching
saveCache :: DebugMonad m => FilePath -> m () Source #
loadCache :: DebugMonad m => FilePath -> m () Source #
Types
allClosures :: DebugClosure ccs (GenSrtPayload c) (GenPapPayload c) a (GenStackFrames (GenSrtPayload c) c) c -> [c] #
dcSize :: DebugClosureWithSize ccs srt pap string s b -> Size #
hexmap :: forall a b c d e f g h i j k l t. Hextraversable t => (a -> b) -> (c -> d) -> (e -> f) -> (g -> h) -> (i -> j) -> (k -> l) -> t a c e g i k -> t b d f h j l #
noSize :: DebugClosureWithSize ccs srt pap string s b -> DebugClosure ccs srt pap string s b #
parseConstrDesc :: String -> ConstrDesc #
Constructors
CCPayload | |
Instances
Show CCPayload # | |
Eq CCPayload # | |
Ord CCPayload # | |
type CCSPayload = GenCCSPayload CCSPtr CCPtr #
data ClosureType #
Constructors
Instances
data ConstrDesc #
Instances
Show ConstrDesc # | |
Defined in GHC.Debug.Types.Closures Methods showsPrec :: Int -> ConstrDesc -> ShowS # show :: ConstrDesc -> String # showList :: [ConstrDesc] -> ShowS # | |
Eq ConstrDesc # | |
Defined in GHC.Debug.Types.Closures | |
Ord ConstrDesc # | |
Defined in GHC.Debug.Types.Closures Methods compare :: ConstrDesc -> ConstrDesc -> Ordering # (<) :: ConstrDesc -> ConstrDesc -> Bool # (<=) :: ConstrDesc -> ConstrDesc -> Bool # (>) :: ConstrDesc -> ConstrDesc -> Bool # (>=) :: ConstrDesc -> ConstrDesc -> Bool # max :: ConstrDesc -> ConstrDesc -> ConstrDesc # min :: ConstrDesc -> ConstrDesc -> ConstrDesc # |
type ConstrDescCont = InfoTablePtr #
data DebugClosure ccs srt pap string s b #
Constructors
ConstrClosure | |
Fields
| |
FunClosure | |
Fields
| |
ThunkClosure | |
Fields
| |
SelectorClosure | |
Fields
| |
PAPClosure | |
Fields
| |
APClosure | |
Fields
| |
APStackClosure | |
Fields
| |
IndClosure | |
Fields
| |
BCOClosure | |
Fields
| |
BlackholeClosure | |
Fields
| |
ArrWordsClosure | |
Fields
| |
MutArrClosure | |
Fields
| |
SmallMutArrClosure | |
Fields
| |
MVarClosure | |
Fields
| |
MutVarClosure | |
Fields
| |
BlockingQueueClosure | |
Fields
| |
TSOClosure | |
Fields
| |
StackClosure | |
Fields
| |
WeakClosure | |
Fields
| |
TVarClosure | |
Fields
| |
TRecChunkClosure | |
Fields
| |
MutPrimClosure | |
Fields
| |
PrimClosure | |
Fields
| |
OtherClosure | |
Fields
| |
UnsupportedClosure | |
Fields
|
Instances
Hextraversable DebugClosure # | |||||
Defined in GHC.Debug.Types.Closures Methods hextraverse :: Applicative f => (a -> f b) -> (c -> f d) -> (e -> f g) -> (h -> f i) -> (j -> f k) -> (l -> f n) -> DebugClosure a c e h j l -> f (DebugClosure b d g i k n) # | |||||
Functor (DebugClosure ccs srt pap string s) # | |||||
Defined in GHC.Debug.Types.Closures Methods fmap :: (a -> b) -> DebugClosure ccs srt pap string s a -> DebugClosure ccs srt pap string s b # (<$) :: a -> DebugClosure ccs srt pap string s b -> DebugClosure ccs srt pap string s a # | |||||
Foldable (DebugClosure ccs srt pap string s) # | |||||
Defined in GHC.Debug.Types.Closures Methods fold :: Monoid m => DebugClosure ccs srt pap string s m -> m # foldMap :: Monoid m => (a -> m) -> DebugClosure ccs srt pap string s a -> m # foldMap' :: Monoid m => (a -> m) -> DebugClosure ccs srt pap string s a -> m # foldr :: (a -> b -> b) -> b -> DebugClosure ccs srt pap string s a -> b # foldr' :: (a -> b -> b) -> b -> DebugClosure ccs srt pap string s a -> b # foldl :: (b -> a -> b) -> b -> DebugClosure ccs srt pap string s a -> b # foldl' :: (b -> a -> b) -> b -> DebugClosure ccs srt pap string s a -> b # foldr1 :: (a -> a -> a) -> DebugClosure ccs srt pap string s a -> a # foldl1 :: (a -> a -> a) -> DebugClosure ccs srt pap string s a -> a # toList :: DebugClosure ccs srt pap string s a -> [a] # null :: DebugClosure ccs srt pap string s a -> Bool # length :: DebugClosure ccs srt pap string s a -> Int # elem :: Eq a => a -> DebugClosure ccs srt pap string s a -> Bool # maximum :: Ord a => DebugClosure ccs srt pap string s a -> a # minimum :: Ord a => DebugClosure ccs srt pap string s a -> a # sum :: Num a => DebugClosure ccs srt pap string s a -> a # product :: Num a => DebugClosure ccs srt pap string s a -> a # | |||||
Traversable (DebugClosure ccs srt pap string s) # | |||||
Defined in GHC.Debug.Types.Closures Methods traverse :: Applicative f => (a -> f b) -> DebugClosure ccs srt pap string s a -> f (DebugClosure ccs srt pap string s b) # sequenceA :: Applicative f => DebugClosure ccs srt pap string s (f a) -> f (DebugClosure ccs srt pap string s a) # mapM :: Monad m => (a -> m b) -> DebugClosure ccs srt pap string s a -> m (DebugClosure ccs srt pap string s b) # sequence :: Monad m => DebugClosure ccs srt pap string s (m a) -> m (DebugClosure ccs srt pap string s a) # | |||||
Generic (DebugClosure ccs srt pap string s b) # | |||||
Defined in GHC.Debug.Types.Closures Associated Types
Methods from :: DebugClosure ccs srt pap string s b -> Rep (DebugClosure ccs srt pap string s b) x # to :: Rep (DebugClosure ccs srt pap string s b) x -> DebugClosure ccs srt pap string s b # | |||||
(Show ccs, Show string, Show srt, Show pap, Show s, Show b) => Show (DebugClosure ccs srt pap string s b) # | |||||
Defined in GHC.Debug.Types.Closures Methods showsPrec :: Int -> DebugClosure ccs srt pap string s b -> ShowS # show :: DebugClosure ccs srt pap string s b -> String # showList :: [DebugClosure ccs srt pap string s b] -> ShowS # | |||||
(Eq ccs, Eq string, Eq srt, Eq pap, Eq s, Eq b) => Eq (DebugClosure ccs srt pap string s b) # | |||||
Defined in GHC.Debug.Types.Closures Methods (==) :: DebugClosure ccs srt pap string s b -> DebugClosure ccs srt pap string s b -> Bool # (/=) :: DebugClosure ccs srt pap string s b -> DebugClosure ccs srt pap string s b -> Bool # | |||||
(Ord ccs, Ord string, Ord srt, Ord pap, Ord s, Ord b) => Ord (DebugClosure ccs srt pap string s b) # | |||||
Defined in GHC.Debug.Types.Closures Methods compare :: DebugClosure ccs srt pap string s b -> DebugClosure ccs srt pap string s b -> Ordering # (<) :: DebugClosure ccs srt pap string s b -> DebugClosure ccs srt pap string s b -> Bool # (<=) :: DebugClosure ccs srt pap string s b -> DebugClosure ccs srt pap string s b -> Bool # (>) :: DebugClosure ccs srt pap string s b -> DebugClosure ccs srt pap string s b -> Bool # (>=) :: DebugClosure ccs srt pap string s b -> DebugClosure ccs srt pap string s b -> Bool # max :: DebugClosure ccs srt pap string s b -> DebugClosure ccs srt pap string s b -> DebugClosure ccs srt pap string s b # min :: DebugClosure ccs srt pap string s b -> DebugClosure ccs srt pap string s b -> DebugClosure ccs srt pap string s b # | |||||
type Rep (DebugClosure ccs srt pap string s b) # | |||||
Defined in GHC.Debug.Types.Closures type Rep (DebugClosure ccs srt pap string s b) = D1 ('MetaData "DebugClosure" "GHC.Debug.Types.Closures" "ghc-debug-common-0.7.0.0-inplace" 'False) ((((C1 ('MetaCons "ConstrClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs)))) :*: (S1 ('MetaSel ('Just "ptrArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]) :*: (S1 ('MetaSel ('Just "dataArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word]) :*: S1 ('MetaSel ('Just "constrDesc") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 string)))) :+: (C1 ('MetaCons "FunClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs)))) :*: (S1 ('MetaSel ('Just "srt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 srt) :*: (S1 ('MetaSel ('Just "ptrArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]) :*: S1 ('MetaSel ('Just "dataArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word])))) :+: C1 ('MetaCons "ThunkClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs)))) :*: (S1 ('MetaSel ('Just "srt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 srt) :*: (S1 ('MetaSel ('Just "ptrArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]) :*: S1 ('MetaSel ('Just "dataArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word])))))) :+: (C1 ('MetaCons "SelectorClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: (S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs))) :*: S1 ('MetaSel ('Just "selectee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b))) :+: (C1 ('MetaCons "PAPClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: (S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs))) :*: S1 ('MetaSel ('Just "arity") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 HalfWord))) :*: (S1 ('MetaSel ('Just "n_args") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 HalfWord) :*: (S1 ('MetaSel ('Just "fun") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "pap_payload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 pap)))) :+: C1 ('MetaCons "APClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: (S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs))) :*: S1 ('MetaSel ('Just "arity") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 HalfWord))) :*: (S1 ('MetaSel ('Just "n_args") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 HalfWord) :*: (S1 ('MetaSel ('Just "fun") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "ap_payload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 pap))))))) :+: ((C1 ('MetaCons "APStackClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs)))) :*: (S1 ('MetaSel ('Just "ap_st_size") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word) :*: (S1 ('MetaSel ('Just "fun") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "payload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 s)))) :+: (C1 ('MetaCons "IndClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: (S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs))) :*: S1 ('MetaSel ('Just "indirectee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b))) :+: C1 ('MetaCons "BCOClosure" 'PrefixI 'True) (((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs)))) :*: (S1 ('MetaSel ('Just "instrs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "literals") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b))) :*: ((S1 ('MetaSel ('Just "bcoptrs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "arity") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 HalfWord)) :*: (S1 ('MetaSel ('Just "size") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 HalfWord) :*: S1 ('MetaSel ('Just "bitmap") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PtrBitmap)))))) :+: (C1 ('MetaCons "BlackholeClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: (S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs))) :*: S1 ('MetaSel ('Just "indirectee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b))) :+: (C1 ('MetaCons "ArrWordsClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs)))) :*: (S1 ('MetaSel ('Just "bytes") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word) :*: S1 ('MetaSel ('Just "arrWords") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word]))) :+: C1 ('MetaCons "MutArrClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs)))) :*: (S1 ('MetaSel ('Just "mccPtrs") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word) :*: (S1 ('MetaSel ('Just "mccSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word) :*: S1 ('MetaSel ('Just "mccPayload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b])))))))) :+: (((C1 ('MetaCons "SmallMutArrClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs)))) :*: (S1 ('MetaSel ('Just "mccPtrs") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word) :*: S1 ('MetaSel ('Just "mccPayload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]))) :+: (C1 ('MetaCons "MVarClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs)))) :*: (S1 ('MetaSel ('Just "queueHead") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: (S1 ('MetaSel ('Just "queueTail") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)))) :+: C1 ('MetaCons "MutVarClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: (S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs))) :*: S1 ('MetaSel ('Just "var") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b))))) :+: (C1 ('MetaCons "BlockingQueueClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: (S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs))) :*: S1 ('MetaSel ('Just "link") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b))) :*: (S1 ('MetaSel ('Just "blackHole") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: (S1 ('MetaSel ('Just "owner") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "queue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)))) :+: (C1 ('MetaCons "TSOClosure" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs)))) :*: (S1 ('MetaSel ('Just "_link") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "global_link") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b))) :*: ((S1 ('MetaSel ('Just "tsoStack") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "trec") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :*: (S1 ('MetaSel ('Just "blocked_exceptions") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: (S1 ('MetaSel ('Just "bq") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "threadLabel") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe b)))))) :*: (((S1 ('MetaSel ('Just "what_next") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WhatNext) :*: S1 ('MetaSel ('Just "why_blocked") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WhyBlocked)) :*: (S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TsoFlags]) :*: S1 ('MetaSel ('Just "threadId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64))) :*: ((S1 ('MetaSel ('Just "saved_errno") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: S1 ('MetaSel ('Just "dirty") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)) :*: (S1 ('MetaSel ('Just "alloc_limit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64) :*: (S1 ('MetaSel ('Just "tot_stack_size") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: S1 ('MetaSel ('Just "prof") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe StgTSOProfInfo))))))) :+: C1 ('MetaCons "StackClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: (S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs))) :*: S1 ('MetaSel ('Just "stack_size") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word32))) :*: (S1 ('MetaSel ('Just "stack_dirty") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word8) :*: (S1 ('MetaSel ('Just "stack_marking") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word8) :*: S1 ('MetaSel ('Just "frames") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 s))))))) :+: ((C1 ('MetaCons "WeakClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: (S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs))) :*: S1 ('MetaSel ('Just "cfinalizers") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b))) :*: ((S1 ('MetaSel ('Just "key") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :*: (S1 ('MetaSel ('Just "finalizer") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "mlink") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe b))))) :+: (C1 ('MetaCons "TVarClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs)))) :*: (S1 ('MetaSel ('Just "current_value") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: (S1 ('MetaSel ('Just "tvar_watch_queue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "num_updates") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int)))) :+: C1 ('MetaCons "TRecChunkClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs)))) :*: (S1 ('MetaSel ('Just "prev_chunk") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: (S1 ('MetaSel ('Just "next_idx") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word) :*: S1 ('MetaSel ('Just "entries") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [TRecEntry b])))))) :+: ((C1 ('MetaCons "MutPrimClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs)))) :*: (S1 ('MetaSel ('Just "ptrArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]) :*: S1 ('MetaSel ('Just "dataArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word]))) :+: C1 ('MetaCons "PrimClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs)))) :*: (S1 ('MetaSel ('Just "ptrArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]) :*: S1 ('MetaSel ('Just "dataArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word])))) :+: (C1 ('MetaCons "OtherClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs)))) :*: (S1 ('MetaSel ('Just "hvalues") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]) :*: S1 ('MetaSel ('Just "rawWords") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word]))) :+: C1 ('MetaCons "UnsupportedClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: S1 ('MetaSel ('Just "profHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProfHeader ccs))))))))) |
data DebugClosureWithExtra x ccs srt pap string s b #
Constructors
DCS | |
Fields
|
Instances
Hextraversable (DebugClosureWithExtra x) # | |
Defined in GHC.Debug.Types.Closures Methods hextraverse :: Applicative f => (a -> f b) -> (c -> f d) -> (e -> f g) -> (h -> f i) -> (j -> f k) -> (l -> f n) -> DebugClosureWithExtra x a c e h j l -> f (DebugClosureWithExtra x b d g i k n) # | |
(Show x, Show ccs, Show string, Show srt, Show pap, Show s, Show b) => Show (DebugClosureWithExtra x ccs srt pap string s b) # | |
Defined in GHC.Debug.Types.Closures Methods showsPrec :: Int -> DebugClosureWithExtra x ccs srt pap string s b -> ShowS # show :: DebugClosureWithExtra x ccs srt pap string s b -> String # showList :: [DebugClosureWithExtra x ccs srt pap string s b] -> ShowS # | |
(Eq x, Eq ccs, Eq string, Eq srt, Eq pap, Eq s, Eq b) => Eq (DebugClosureWithExtra x ccs srt pap string s b) # | |
Defined in GHC.Debug.Types.Closures Methods (==) :: DebugClosureWithExtra x ccs srt pap string s b -> DebugClosureWithExtra x ccs srt pap string s b -> Bool # (/=) :: DebugClosureWithExtra x ccs srt pap string s b -> DebugClosureWithExtra x ccs srt pap string s b -> Bool # | |
(Ord x, Ord ccs, Ord string, Ord srt, Ord pap, Ord s, Ord b) => Ord (DebugClosureWithExtra x ccs srt pap string s b) # | |
Defined in GHC.Debug.Types.Closures Methods compare :: DebugClosureWithExtra x ccs srt pap string s b -> DebugClosureWithExtra x ccs srt pap string s b -> Ordering # (<) :: DebugClosureWithExtra x ccs srt pap string s b -> DebugClosureWithExtra x ccs srt pap string s b -> Bool # (<=) :: DebugClosureWithExtra x ccs srt pap string s b -> DebugClosureWithExtra x ccs srt pap string s b -> Bool # (>) :: DebugClosureWithExtra x ccs srt pap string s b -> DebugClosureWithExtra x ccs srt pap string s b -> Bool # (>=) :: DebugClosureWithExtra x ccs srt pap string s b -> DebugClosureWithExtra x ccs srt pap string s b -> Bool # max :: DebugClosureWithExtra x ccs srt pap string s b -> DebugClosureWithExtra x ccs srt pap string s b -> DebugClosureWithExtra x ccs srt pap string s b # min :: DebugClosureWithExtra x ccs srt pap string s b -> DebugClosureWithExtra x ccs srt pap string s b -> DebugClosureWithExtra x ccs srt pap string s b # |
data DebugStackFrame srt b #
Constructors
DebugStackFrame | |
Fields
|
Instances
Bifoldable DebugStackFrame # | |
Defined in GHC.Debug.Types.Closures Methods bifold :: Monoid m => DebugStackFrame m m -> m # bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> DebugStackFrame a b -> m # bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> DebugStackFrame a b -> c # bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> DebugStackFrame a b -> c # | |
Bifunctor DebugStackFrame # | |
Defined in GHC.Debug.Types.Closures Methods bimap :: (a -> b) -> (c -> d) -> DebugStackFrame a c -> DebugStackFrame b d # first :: (a -> b) -> DebugStackFrame a c -> DebugStackFrame b c # second :: (b -> c) -> DebugStackFrame a b -> DebugStackFrame a c # | |
Bitraversable DebugStackFrame # | |
Defined in GHC.Debug.Types.Closures Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> DebugStackFrame a b -> f (DebugStackFrame c d) # | |
Functor (DebugStackFrame srt) # | |
Defined in GHC.Debug.Types.Closures Methods fmap :: (a -> b) -> DebugStackFrame srt a -> DebugStackFrame srt b # (<$) :: a -> DebugStackFrame srt b -> DebugStackFrame srt a # | |
Foldable (DebugStackFrame srt) # | |
Defined in GHC.Debug.Types.Closures Methods fold :: Monoid m => DebugStackFrame srt m -> m # foldMap :: Monoid m => (a -> m) -> DebugStackFrame srt a -> m # foldMap' :: Monoid m => (a -> m) -> DebugStackFrame srt a -> m # foldr :: (a -> b -> b) -> b -> DebugStackFrame srt a -> b # foldr' :: (a -> b -> b) -> b -> DebugStackFrame srt a -> b # foldl :: (b -> a -> b) -> b -> DebugStackFrame srt a -> b # foldl' :: (b -> a -> b) -> b -> DebugStackFrame srt a -> b # foldr1 :: (a -> a -> a) -> DebugStackFrame srt a -> a # foldl1 :: (a -> a -> a) -> DebugStackFrame srt a -> a # toList :: DebugStackFrame srt a -> [a] # null :: DebugStackFrame srt a -> Bool # length :: DebugStackFrame srt a -> Int # elem :: Eq a => a -> DebugStackFrame srt a -> Bool # maximum :: Ord a => DebugStackFrame srt a -> a # minimum :: Ord a => DebugStackFrame srt a -> a # sum :: Num a => DebugStackFrame srt a -> a # product :: Num a => DebugStackFrame srt a -> a # | |
Traversable (DebugStackFrame srt) # | |
Defined in GHC.Debug.Types.Closures Methods traverse :: Applicative f => (a -> f b) -> DebugStackFrame srt a -> f (DebugStackFrame srt b) # sequenceA :: Applicative f => DebugStackFrame srt (f a) -> f (DebugStackFrame srt a) # mapM :: Monad m => (a -> m b) -> DebugStackFrame srt a -> m (DebugStackFrame srt b) # sequence :: Monad m => DebugStackFrame srt (m a) -> m (DebugStackFrame srt a) # | |
(Show srt, Show b) => Show (DebugStackFrame srt b) # | |
Defined in GHC.Debug.Types.Closures Methods showsPrec :: Int -> DebugStackFrame srt b -> ShowS # show :: DebugStackFrame srt b -> String # showList :: [DebugStackFrame srt b] -> ShowS # | |
(Eq srt, Eq b) => Eq (DebugStackFrame srt b) # | |
Defined in GHC.Debug.Types.Closures Methods (==) :: DebugStackFrame srt b -> DebugStackFrame srt b -> Bool # (/=) :: DebugStackFrame srt b -> DebugStackFrame srt b -> Bool # | |
(Ord srt, Ord b) => Ord (DebugStackFrame srt b) # | |
Defined in GHC.Debug.Types.Closures Methods compare :: DebugStackFrame srt b -> DebugStackFrame srt b -> Ordering # (<) :: DebugStackFrame srt b -> DebugStackFrame srt b -> Bool # (<=) :: DebugStackFrame srt b -> DebugStackFrame srt b -> Bool # (>) :: DebugStackFrame srt b -> DebugStackFrame srt b -> Bool # (>=) :: DebugStackFrame srt b -> DebugStackFrame srt b -> Bool # max :: DebugStackFrame srt b -> DebugStackFrame srt b -> DebugStackFrame srt b # min :: DebugStackFrame srt b -> DebugStackFrame srt b -> DebugStackFrame srt b # |
data FieldValue b #
Instances
Functor FieldValue # | |
Defined in GHC.Debug.Types.Closures Methods fmap :: (a -> b) -> FieldValue a -> FieldValue b # (<$) :: a -> FieldValue b -> FieldValue a # | |
Foldable FieldValue # | |
Defined in GHC.Debug.Types.Closures Methods fold :: Monoid m => FieldValue m -> m # foldMap :: Monoid m => (a -> m) -> FieldValue a -> m # foldMap' :: Monoid m => (a -> m) -> FieldValue a -> m # foldr :: (a -> b -> b) -> b -> FieldValue a -> b # foldr' :: (a -> b -> b) -> b -> FieldValue a -> b # foldl :: (b -> a -> b) -> b -> FieldValue a -> b # foldl' :: (b -> a -> b) -> b -> FieldValue a -> b # foldr1 :: (a -> a -> a) -> FieldValue a -> a # foldl1 :: (a -> a -> a) -> FieldValue a -> a # toList :: FieldValue a -> [a] # null :: FieldValue a -> Bool # length :: FieldValue a -> Int # elem :: Eq a => a -> FieldValue a -> Bool # maximum :: Ord a => FieldValue a -> a # minimum :: Ord a => FieldValue a -> a # sum :: Num a => FieldValue a -> a # product :: Num a => FieldValue a -> a # | |
Traversable FieldValue # | |
Defined in GHC.Debug.Types.Closures Methods traverse :: Applicative f => (a -> f b) -> FieldValue a -> f (FieldValue b) # sequenceA :: Applicative f => FieldValue (f a) -> f (FieldValue a) # mapM :: Monad m => (a -> m b) -> FieldValue a -> m (FieldValue b) # sequence :: Monad m => FieldValue (m a) -> m (FieldValue a) # | |
Show b => Show (FieldValue b) # | |
Defined in GHC.Debug.Types.Closures Methods showsPrec :: Int -> FieldValue b -> ShowS # show :: FieldValue b -> String # showList :: [FieldValue b] -> ShowS # | |
Eq b => Eq (FieldValue b) # | |
Defined in GHC.Debug.Types.Closures | |
Ord b => Ord (FieldValue b) # | |
Defined in GHC.Debug.Types.Closures Methods compare :: FieldValue b -> FieldValue b -> Ordering # (<) :: FieldValue b -> FieldValue b -> Bool # (<=) :: FieldValue b -> FieldValue b -> Bool # (>) :: FieldValue b -> FieldValue b -> Bool # (>=) :: FieldValue b -> FieldValue b -> Bool # max :: FieldValue b -> FieldValue b -> FieldValue b # min :: FieldValue b -> FieldValue b -> FieldValue b # |
data GenCCSPayload ccsPtr ccPtr #
Constructors
CCSPayload | |
Fields
|
Instances
Bifoldable GenCCSPayload # | |
Defined in GHC.Debug.Types.Closures Methods bifold :: Monoid m => GenCCSPayload m m -> m # bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> GenCCSPayload a b -> m # bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> GenCCSPayload a b -> c # bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> GenCCSPayload a b -> c # | |
Bifunctor GenCCSPayload # | |
Defined in GHC.Debug.Types.Closures Methods bimap :: (a -> b) -> (c -> d) -> GenCCSPayload a c -> GenCCSPayload b d # first :: (a -> b) -> GenCCSPayload a c -> GenCCSPayload b c # second :: (b -> c) -> GenCCSPayload a b -> GenCCSPayload a c # | |
Bitraversable GenCCSPayload # | |
Defined in GHC.Debug.Types.Closures Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> GenCCSPayload a b -> f (GenCCSPayload c d) # | |
Functor (GenCCSPayload ccsPtr) # | |
Defined in GHC.Debug.Types.Closures Methods fmap :: (a -> b) -> GenCCSPayload ccsPtr a -> GenCCSPayload ccsPtr b # (<$) :: a -> GenCCSPayload ccsPtr b -> GenCCSPayload ccsPtr a # | |
(Show ccPtr, Show ccsPtr) => Show (GenCCSPayload ccsPtr ccPtr) # | |
Defined in GHC.Debug.Types.Closures Methods showsPrec :: Int -> GenCCSPayload ccsPtr ccPtr -> ShowS # show :: GenCCSPayload ccsPtr ccPtr -> String # showList :: [GenCCSPayload ccsPtr ccPtr] -> ShowS # | |
(Eq ccPtr, Eq ccsPtr) => Eq (GenCCSPayload ccsPtr ccPtr) # | |
Defined in GHC.Debug.Types.Closures Methods (==) :: GenCCSPayload ccsPtr ccPtr -> GenCCSPayload ccsPtr ccPtr -> Bool # (/=) :: GenCCSPayload ccsPtr ccPtr -> GenCCSPayload ccsPtr ccPtr -> Bool # | |
(Ord ccPtr, Ord ccsPtr) => Ord (GenCCSPayload ccsPtr ccPtr) # | |
Defined in GHC.Debug.Types.Closures Methods compare :: GenCCSPayload ccsPtr ccPtr -> GenCCSPayload ccsPtr ccPtr -> Ordering # (<) :: GenCCSPayload ccsPtr ccPtr -> GenCCSPayload ccsPtr ccPtr -> Bool # (<=) :: GenCCSPayload ccsPtr ccPtr -> GenCCSPayload ccsPtr ccPtr -> Bool # (>) :: GenCCSPayload ccsPtr ccPtr -> GenCCSPayload ccsPtr ccPtr -> Bool # (>=) :: GenCCSPayload ccsPtr ccPtr -> GenCCSPayload ccsPtr ccPtr -> Bool # max :: GenCCSPayload ccsPtr ccPtr -> GenCCSPayload ccsPtr ccPtr -> GenCCSPayload ccsPtr ccPtr # min :: GenCCSPayload ccsPtr ccPtr -> GenCCSPayload ccsPtr ccPtr -> GenCCSPayload ccsPtr ccPtr # |
newtype GenPapPayload b #
Constructors
GenPapPayload | |
Fields
|
Instances
Functor GenPapPayload # | |
Defined in GHC.Debug.Types.Closures Methods fmap :: (a -> b) -> GenPapPayload a -> GenPapPayload b # (<$) :: a -> GenPapPayload b -> GenPapPayload a # | |
Foldable GenPapPayload # | |
Defined in GHC.Debug.Types.Closures Methods fold :: Monoid m => GenPapPayload m -> m # foldMap :: Monoid m => (a -> m) -> GenPapPayload a -> m # foldMap' :: Monoid m => (a -> m) -> GenPapPayload a -> m # foldr :: (a -> b -> b) -> b -> GenPapPayload a -> b # foldr' :: (a -> b -> b) -> b -> GenPapPayload a -> b # foldl :: (b -> a -> b) -> b -> GenPapPayload a -> b # foldl' :: (b -> a -> b) -> b -> GenPapPayload a -> b # foldr1 :: (a -> a -> a) -> GenPapPayload a -> a # foldl1 :: (a -> a -> a) -> GenPapPayload a -> a # toList :: GenPapPayload a -> [a] # null :: GenPapPayload a -> Bool # length :: GenPapPayload a -> Int # elem :: Eq a => a -> GenPapPayload a -> Bool # maximum :: Ord a => GenPapPayload a -> a # minimum :: Ord a => GenPapPayload a -> a # sum :: Num a => GenPapPayload a -> a # product :: Num a => GenPapPayload a -> a # | |
Traversable GenPapPayload # | |
Defined in GHC.Debug.Types.Closures Methods traverse :: Applicative f => (a -> f b) -> GenPapPayload a -> f (GenPapPayload b) # sequenceA :: Applicative f => GenPapPayload (f a) -> f (GenPapPayload a) # mapM :: Monad m => (a -> m b) -> GenPapPayload a -> m (GenPapPayload b) # sequence :: Monad m => GenPapPayload (m a) -> m (GenPapPayload a) # | |
Show b => Show (GenPapPayload b) # | |
Defined in GHC.Debug.Types.Closures Methods showsPrec :: Int -> GenPapPayload b -> ShowS # show :: GenPapPayload b -> String # showList :: [GenPapPayload b] -> ShowS # | |
Eq b => Eq (GenPapPayload b) # | |
Defined in GHC.Debug.Types.Closures Methods (==) :: GenPapPayload b -> GenPapPayload b -> Bool # (/=) :: GenPapPayload b -> GenPapPayload b -> Bool # | |
Ord b => Ord (GenPapPayload b) # | |
Defined in GHC.Debug.Types.Closures Methods compare :: GenPapPayload b -> GenPapPayload b -> Ordering # (<) :: GenPapPayload b -> GenPapPayload b -> Bool # (<=) :: GenPapPayload b -> GenPapPayload b -> Bool # (>) :: GenPapPayload b -> GenPapPayload b -> Bool # (>=) :: GenPapPayload b -> GenPapPayload b -> Bool # max :: GenPapPayload b -> GenPapPayload b -> GenPapPayload b # min :: GenPapPayload b -> GenPapPayload b -> GenPapPayload b # |
newtype GenSrtPayload b #
Constructors
GenSrtPayload | |
Instances
Functor GenSrtPayload # | |
Defined in GHC.Debug.Types.Closures Methods fmap :: (a -> b) -> GenSrtPayload a -> GenSrtPayload b # (<$) :: a -> GenSrtPayload b -> GenSrtPayload a # | |
Foldable GenSrtPayload # | |
Defined in GHC.Debug.Types.Closures Methods fold :: Monoid m => GenSrtPayload m -> m # foldMap :: Monoid m => (a -> m) -> GenSrtPayload a -> m # foldMap' :: Monoid m => (a -> m) -> GenSrtPayload a -> m # foldr :: (a -> b -> b) -> b -> GenSrtPayload a -> b # foldr' :: (a -> b -> b) -> b -> GenSrtPayload a -> b # foldl :: (b -> a -> b) -> b -> GenSrtPayload a -> b # foldl' :: (b -> a -> b) -> b -> GenSrtPayload a -> b # foldr1 :: (a -> a -> a) -> GenSrtPayload a -> a # foldl1 :: (a -> a -> a) -> GenSrtPayload a -> a # toList :: GenSrtPayload a -> [a] # null :: GenSrtPayload a -> Bool # length :: GenSrtPayload a -> Int # elem :: Eq a => a -> GenSrtPayload a -> Bool # maximum :: Ord a => GenSrtPayload a -> a # minimum :: Ord a => GenSrtPayload a -> a # sum :: Num a => GenSrtPayload a -> a # product :: Num a => GenSrtPayload a -> a # | |
Traversable GenSrtPayload # | |
Defined in GHC.Debug.Types.Closures Methods traverse :: Applicative f => (a -> f b) -> GenSrtPayload a -> f (GenSrtPayload b) # sequenceA :: Applicative f => GenSrtPayload (f a) -> f (GenSrtPayload a) # mapM :: Monad m => (a -> m b) -> GenSrtPayload a -> m (GenSrtPayload b) # sequence :: Monad m => GenSrtPayload (m a) -> m (GenSrtPayload a) # | |
Show b => Show (GenSrtPayload b) # | |
Defined in GHC.Debug.Types.Closures Methods showsPrec :: Int -> GenSrtPayload b -> ShowS # show :: GenSrtPayload b -> String # showList :: [GenSrtPayload b] -> ShowS # | |
Eq b => Eq (GenSrtPayload b) # | |
Defined in GHC.Debug.Types.Closures Methods (==) :: GenSrtPayload b -> GenSrtPayload b -> Bool # (/=) :: GenSrtPayload b -> GenSrtPayload b -> Bool # | |
Ord b => Ord (GenSrtPayload b) # | |
Defined in GHC.Debug.Types.Closures Methods compare :: GenSrtPayload b -> GenSrtPayload b -> Ordering # (<) :: GenSrtPayload b -> GenSrtPayload b -> Bool # (<=) :: GenSrtPayload b -> GenSrtPayload b -> Bool # (>) :: GenSrtPayload b -> GenSrtPayload b -> Bool # (>=) :: GenSrtPayload b -> GenSrtPayload b -> Bool # max :: GenSrtPayload b -> GenSrtPayload b -> GenSrtPayload b # min :: GenSrtPayload b -> GenSrtPayload b -> GenSrtPayload b # |
newtype GenStackFrames srt b #
Constructors
GenStackFrames | |
Fields
|
Instances
Bifoldable GenStackFrames # | |
Defined in GHC.Debug.Types.Closures Methods bifold :: Monoid m => GenStackFrames m m -> m # bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> GenStackFrames a b -> m # bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> GenStackFrames a b -> c # bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> GenStackFrames a b -> c # | |
Bifunctor GenStackFrames # | |
Defined in GHC.Debug.Types.Closures Methods bimap :: (a -> b) -> (c -> d) -> GenStackFrames a c -> GenStackFrames b d # first :: (a -> b) -> GenStackFrames a c -> GenStackFrames b c # second :: (b -> c) -> GenStackFrames a b -> GenStackFrames a c # | |
Bitraversable GenStackFrames # | |
Defined in GHC.Debug.Types.Closures Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> GenStackFrames a b -> f (GenStackFrames c d) # | |
Functor (GenStackFrames srt) # | |
Defined in GHC.Debug.Types.Closures Methods fmap :: (a -> b) -> GenStackFrames srt a -> GenStackFrames srt b # (<$) :: a -> GenStackFrames srt b -> GenStackFrames srt a # | |
Foldable (GenStackFrames srt) # | |
Defined in GHC.Debug.Types.Closures Methods fold :: Monoid m => GenStackFrames srt m -> m # foldMap :: Monoid m => (a -> m) -> GenStackFrames srt a -> m # foldMap' :: Monoid m => (a -> m) -> GenStackFrames srt a -> m # foldr :: (a -> b -> b) -> b -> GenStackFrames srt a -> b # foldr' :: (a -> b -> b) -> b -> GenStackFrames srt a -> b # foldl :: (b -> a -> b) -> b -> GenStackFrames srt a -> b # foldl' :: (b -> a -> b) -> b -> GenStackFrames srt a -> b # foldr1 :: (a -> a -> a) -> GenStackFrames srt a -> a # foldl1 :: (a -> a -> a) -> GenStackFrames srt a -> a # toList :: GenStackFrames srt a -> [a] # null :: GenStackFrames srt a -> Bool # length :: GenStackFrames srt a -> Int # elem :: Eq a => a -> GenStackFrames srt a -> Bool # maximum :: Ord a => GenStackFrames srt a -> a # minimum :: Ord a => GenStackFrames srt a -> a # sum :: Num a => GenStackFrames srt a -> a # product :: Num a => GenStackFrames srt a -> a # | |
Traversable (GenStackFrames srt) # | |
Defined in GHC.Debug.Types.Closures Methods traverse :: Applicative f => (a -> f b) -> GenStackFrames srt a -> f (GenStackFrames srt b) # sequenceA :: Applicative f => GenStackFrames srt (f a) -> f (GenStackFrames srt a) # mapM :: Monad m => (a -> m b) -> GenStackFrames srt a -> m (GenStackFrames srt b) # sequence :: Monad m => GenStackFrames srt (m a) -> m (GenStackFrames srt a) # | |
(Show srt, Show b) => Show (GenStackFrames srt b) # | |
Defined in GHC.Debug.Types.Closures Methods showsPrec :: Int -> GenStackFrames srt b -> ShowS # show :: GenStackFrames srt b -> String # showList :: [GenStackFrames srt b] -> ShowS # | |
(Eq srt, Eq b) => Eq (GenStackFrames srt b) # | |
Defined in GHC.Debug.Types.Closures Methods (==) :: GenStackFrames srt b -> GenStackFrames srt b -> Bool # (/=) :: GenStackFrames srt b -> GenStackFrames srt b -> Bool # | |
(Ord srt, Ord b) => Ord (GenStackFrames srt b) # | |
Defined in GHC.Debug.Types.Closures Methods compare :: GenStackFrames srt b -> GenStackFrames srt b -> Ordering # (<) :: GenStackFrames srt b -> GenStackFrames srt b -> Bool # (<=) :: GenStackFrames srt b -> GenStackFrames srt b -> Bool # (>) :: GenStackFrames srt b -> GenStackFrames srt b -> Bool # (>=) :: GenStackFrames srt b -> GenStackFrames srt b -> Bool # max :: GenStackFrames srt b -> GenStackFrames srt b -> GenStackFrames srt b # min :: GenStackFrames srt b -> GenStackFrames srt b -> GenStackFrames srt b # |
class Hextraversable (m :: Type -> Type -> Type -> Type -> Type -> Type -> Type) where #
Methods
hextraverse :: Applicative f => (a -> f b) -> (c -> f d) -> (e -> f g) -> (h -> f i) -> (j -> f k) -> (l -> f n) -> m a c e h j l -> f (m b d g i k n) #
Instances
Hextraversable DebugClosure # | |
Defined in GHC.Debug.Types.Closures Methods hextraverse :: Applicative f => (a -> f b) -> (c -> f d) -> (e -> f g) -> (h -> f i) -> (j -> f k) -> (l -> f n) -> DebugClosure a c e h j l -> f (DebugClosure b d g i k n) # | |
Hextraversable (DebugClosureWithExtra x) # | |
Defined in GHC.Debug.Types.Closures Methods hextraverse :: Applicative f => (a -> f b) -> (c -> f d) -> (e -> f g) -> (h -> f i) -> (j -> f k) -> (l -> f n) -> DebugClosureWithExtra x a c e h j l -> f (DebugClosureWithExtra x b d g i k n) # |
newtype InclusiveSize #
Constructors
InclusiveSize | |
Fields |
Instances
Monoid InclusiveSize # | |||||
Defined in GHC.Debug.Types.Closures Methods mempty :: InclusiveSize # mappend :: InclusiveSize -> InclusiveSize -> InclusiveSize # mconcat :: [InclusiveSize] -> InclusiveSize # | |||||
Semigroup InclusiveSize # | |||||
Defined in GHC.Debug.Types.Closures Methods (<>) :: InclusiveSize -> InclusiveSize -> InclusiveSize # sconcat :: NonEmpty InclusiveSize -> InclusiveSize # stimes :: Integral b => b -> InclusiveSize -> InclusiveSize # | |||||
Generic InclusiveSize # | |||||
Defined in GHC.Debug.Types.Closures Associated Types
| |||||
Show InclusiveSize # | |||||
Defined in GHC.Debug.Types.Closures Methods showsPrec :: Int -> InclusiveSize -> ShowS # show :: InclusiveSize -> String # showList :: [InclusiveSize] -> ShowS # | |||||
type Rep InclusiveSize # | |||||
Defined in GHC.Debug.Types.Closures type Rep InclusiveSize = D1 ('MetaData "InclusiveSize" "GHC.Debug.Types.Closures" "ghc-debug-common-0.7.0.0-inplace" 'True) (C1 ('MetaCons "InclusiveSize" 'PrefixI 'True) (S1 ('MetaSel ('Just "getInclusiveSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) |
data IndexTable #
Constructors
IndexTable | |
Fields
|
Instances
Show IndexTable # | |
Defined in GHC.Debug.Types.Closures Methods showsPrec :: Int -> IndexTable -> ShowS # show :: IndexTable -> String # showList :: [IndexTable] -> ShowS # | |
Eq IndexTable # | |
Defined in GHC.Debug.Types.Closures | |
Ord IndexTable # | |
Defined in GHC.Debug.Types.Closures Methods compare :: IndexTable -> IndexTable -> Ordering # (<) :: IndexTable -> IndexTable -> Bool # (<=) :: IndexTable -> IndexTable -> Bool # (>) :: IndexTable -> IndexTable -> Bool # (>=) :: IndexTable -> IndexTable -> Bool # max :: IndexTable -> IndexTable -> IndexTable # min :: IndexTable -> IndexTable -> IndexTable # |
type PapPayload = GenPapPayload ClosurePtr #
data PayloadCont #
Constructors
PayloadCont ClosurePtr [Word64] |
Instances
Show PayloadCont # | |
Defined in GHC.Debug.Types.Closures Methods showsPrec :: Int -> PayloadCont -> ShowS # show :: PayloadCont -> String # showList :: [PayloadCont] -> ShowS # | |
Eq PayloadCont # | |
Defined in GHC.Debug.Types.Closures |
data ProfHeader a #
Constructors
ProfHeader | |
Fields
|
Instances
Functor ProfHeader # | |
Defined in GHC.Debug.Types.Closures Methods fmap :: (a -> b) -> ProfHeader a -> ProfHeader b # (<$) :: a -> ProfHeader b -> ProfHeader a # | |
Foldable ProfHeader # | |
Defined in GHC.Debug.Types.Closures Methods fold :: Monoid m => ProfHeader m -> m # foldMap :: Monoid m => (a -> m) -> ProfHeader a -> m # foldMap' :: Monoid m => (a -> m) -> ProfHeader a -> m # foldr :: (a -> b -> b) -> b -> ProfHeader a -> b # foldr' :: (a -> b -> b) -> b -> ProfHeader a -> b # foldl :: (b -> a -> b) -> b -> ProfHeader a -> b # foldl' :: (b -> a -> b) -> b -> ProfHeader a -> b # foldr1 :: (a -> a -> a) -> ProfHeader a -> a # foldl1 :: (a -> a -> a) -> ProfHeader a -> a # toList :: ProfHeader a -> [a] # null :: ProfHeader a -> Bool # length :: ProfHeader a -> Int # elem :: Eq a => a -> ProfHeader a -> Bool # maximum :: Ord a => ProfHeader a -> a # minimum :: Ord a => ProfHeader a -> a # sum :: Num a => ProfHeader a -> a # product :: Num a => ProfHeader a -> a # | |
Traversable ProfHeader # | |
Defined in GHC.Debug.Types.Closures Methods traverse :: Applicative f => (a -> f b) -> ProfHeader a -> f (ProfHeader b) # sequenceA :: Applicative f => ProfHeader (f a) -> f (ProfHeader a) # mapM :: Monad m => (a -> m b) -> ProfHeader a -> m (ProfHeader b) # sequence :: Monad m => ProfHeader (m a) -> m (ProfHeader a) # | |
Show a => Show (ProfHeader a) # | |
Defined in GHC.Debug.Types.Closures Methods showsPrec :: Int -> ProfHeader a -> ShowS # show :: ProfHeader a -> String # showList :: [ProfHeader a] -> ShowS # | |
Eq a => Eq (ProfHeader a) # | |
Defined in GHC.Debug.Types.Closures | |
Ord a => Ord (ProfHeader a) # | |
Defined in GHC.Debug.Types.Closures Methods compare :: ProfHeader a -> ProfHeader a -> Ordering # (<) :: ProfHeader a -> ProfHeader a -> Bool # (<=) :: ProfHeader a -> ProfHeader a -> Bool # (>) :: ProfHeader a -> ProfHeader a -> Bool # (>=) :: ProfHeader a -> ProfHeader a -> Bool # max :: ProfHeader a -> ProfHeader a -> ProfHeader a # min :: ProfHeader a -> ProfHeader a -> ProfHeader a # |
type ProfHeaderWithPtr = ProfHeader CCSPtr #
data ProfHeaderWord #
Constructors
RetainerHeader | |
Fields
| |
LDVWord | |
Fields
| |
EraWord Word64 | |
OtherHeader Word64 |
Instances
Show ProfHeaderWord # | |
Defined in GHC.Debug.Types.Closures Methods showsPrec :: Int -> ProfHeaderWord -> ShowS # show :: ProfHeaderWord -> String # showList :: [ProfHeaderWord] -> ShowS # | |
Eq ProfHeaderWord # | |
Defined in GHC.Debug.Types.Closures Methods (==) :: ProfHeaderWord -> ProfHeaderWord -> Bool # (/=) :: ProfHeaderWord -> ProfHeaderWord -> Bool # | |
Ord ProfHeaderWord # | |
Defined in GHC.Debug.Types.Closures Methods compare :: ProfHeaderWord -> ProfHeaderWord -> Ordering # (<) :: ProfHeaderWord -> ProfHeaderWord -> Bool # (<=) :: ProfHeaderWord -> ProfHeaderWord -> Bool # (>) :: ProfHeaderWord -> ProfHeaderWord -> Bool # (>=) :: ProfHeaderWord -> ProfHeaderWord -> Bool # max :: ProfHeaderWord -> ProfHeaderWord -> ProfHeaderWord # min :: ProfHeaderWord -> ProfHeaderWord -> ProfHeaderWord # |
newtype RetainerSize #
Constructors
RetainerSize | |
Fields |
Instances
Monoid RetainerSize # | |||||
Defined in GHC.Debug.Types.Closures Methods mempty :: RetainerSize # mappend :: RetainerSize -> RetainerSize -> RetainerSize # mconcat :: [RetainerSize] -> RetainerSize # | |||||
Semigroup RetainerSize # | |||||
Defined in GHC.Debug.Types.Closures Methods (<>) :: RetainerSize -> RetainerSize -> RetainerSize # sconcat :: NonEmpty RetainerSize -> RetainerSize # stimes :: Integral b => b -> RetainerSize -> RetainerSize # | |||||
Generic RetainerSize # | |||||
Defined in GHC.Debug.Types.Closures Associated Types
| |||||
Show RetainerSize # | |||||
Defined in GHC.Debug.Types.Closures Methods showsPrec :: Int -> RetainerSize -> ShowS # show :: RetainerSize -> String # showList :: [RetainerSize] -> ShowS # | |||||
Eq RetainerSize # | |||||
Defined in GHC.Debug.Types.Closures | |||||
Ord RetainerSize # | |||||
Defined in GHC.Debug.Types.Closures Methods compare :: RetainerSize -> RetainerSize -> Ordering # (<) :: RetainerSize -> RetainerSize -> Bool # (<=) :: RetainerSize -> RetainerSize -> Bool # (>) :: RetainerSize -> RetainerSize -> Bool # (>=) :: RetainerSize -> RetainerSize -> Bool # max :: RetainerSize -> RetainerSize -> RetainerSize # min :: RetainerSize -> RetainerSize -> RetainerSize # | |||||
type Rep RetainerSize # | |||||
Defined in GHC.Debug.Types.Closures type Rep RetainerSize = D1 ('MetaData "RetainerSize" "GHC.Debug.Types.Closures" "ghc-debug-common-0.7.0.0-inplace" 'True) (C1 ('MetaCons "RetainerSize" 'PrefixI 'True) (S1 ('MetaSel ('Just "getRetainerSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) |
type SizedClosure = DebugClosureWithSize CCSPtr SrtCont PayloadCont ConstrDescCont StackCont ClosurePtr #
type SizedClosureC = DebugClosureWithSize CCSPtr SrtCont PayloadCont ConstrDesc StackCont ClosurePtr #
type SizedClosureP = DebugClosureWithSize CCSPtr SrtPayload PapPayload ConstrDesc StackCont ClosurePtr #
type SrtCont = InfoTablePtr #
type SrtPayload = GenSrtPayload ClosurePtr #
Instances
Show StackCont # | |
Eq StackCont # | |
Ord StackCont # | |
type StackFrames = GenStackFrames SrtCont ClosurePtr #
data StgInfoTable #
Constructors
StgInfoTable | |
Fields
|
Instances
Generic StgInfoTable # | |||||
Defined in GHC.Debug.Types.Closures Associated Types
| |||||
Show StgInfoTable # | |||||
Defined in GHC.Debug.Types.Closures Methods showsPrec :: Int -> StgInfoTable -> ShowS # show :: StgInfoTable -> String # showList :: [StgInfoTable] -> ShowS # | |||||
Eq StgInfoTable # | |||||
Defined in GHC.Debug.Types.Closures | |||||
type Rep StgInfoTable # | |||||
Defined in GHC.Debug.Types.Closures type Rep StgInfoTable = D1 ('MetaData "StgInfoTable" "GHC.Debug.Types.Closures" "ghc-debug-common-0.7.0.0-inplace" 'False) (C1 ('MetaCons "StgInfoTable" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ptrs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HalfWord) :*: S1 ('MetaSel ('Just "nptrs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HalfWord)) :*: (S1 ('MetaSel ('Just "tipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ClosureType) :*: S1 ('MetaSel ('Just "srtlen") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HalfWord)))) |
data StgInfoTableWithPtr #
Constructors
StgInfoTableWithPtr | |
Fields |
Instances
Show StgInfoTableWithPtr # | |
Defined in GHC.Debug.Types.Closures Methods showsPrec :: Int -> StgInfoTableWithPtr -> ShowS # show :: StgInfoTableWithPtr -> String # showList :: [StgInfoTableWithPtr] -> ShowS # | |
Eq StgInfoTableWithPtr # | |
Defined in GHC.Debug.Types.Closures Methods (==) :: StgInfoTableWithPtr -> StgInfoTableWithPtr -> Bool # (/=) :: StgInfoTableWithPtr -> StgInfoTableWithPtr -> Bool # | |
Ord StgInfoTableWithPtr # | |
Defined in GHC.Debug.Types.Closures Methods compare :: StgInfoTableWithPtr -> StgInfoTableWithPtr -> Ordering # (<) :: StgInfoTableWithPtr -> StgInfoTableWithPtr -> Bool # (<=) :: StgInfoTableWithPtr -> StgInfoTableWithPtr -> Bool # (>) :: StgInfoTableWithPtr -> StgInfoTableWithPtr -> Bool # (>=) :: StgInfoTableWithPtr -> StgInfoTableWithPtr -> Bool # max :: StgInfoTableWithPtr -> StgInfoTableWithPtr -> StgInfoTableWithPtr # min :: StgInfoTableWithPtr -> StgInfoTableWithPtr -> StgInfoTableWithPtr # |
Constructors
TRecEntry | |
Fields
|
Instances
Functor TRecEntry # | |||||
Foldable TRecEntry # | |||||
Defined in GHC.Debug.Types.Closures Methods fold :: Monoid m => TRecEntry m -> m # foldMap :: Monoid m => (a -> m) -> TRecEntry a -> m # foldMap' :: Monoid m => (a -> m) -> TRecEntry a -> m # foldr :: (a -> b -> b) -> b -> TRecEntry a -> b # foldr' :: (a -> b -> b) -> b -> TRecEntry a -> b # foldl :: (b -> a -> b) -> b -> TRecEntry a -> b # foldl' :: (b -> a -> b) -> b -> TRecEntry a -> b # foldr1 :: (a -> a -> a) -> TRecEntry a -> a # foldl1 :: (a -> a -> a) -> TRecEntry a -> a # toList :: TRecEntry a -> [a] # length :: TRecEntry a -> Int # elem :: Eq a => a -> TRecEntry a -> Bool # maximum :: Ord a => TRecEntry a -> a # minimum :: Ord a => TRecEntry a -> a # | |||||
Traversable TRecEntry # | |||||
Defined in GHC.Debug.Types.Closures | |||||
Generic (TRecEntry b) # | |||||
Defined in GHC.Debug.Types.Closures Associated Types
| |||||
Show b => Show (TRecEntry b) # | |||||
Eq b => Eq (TRecEntry b) # | |||||
Ord b => Ord (TRecEntry b) # | |||||
Defined in GHC.Debug.Types.Closures | |||||
type Rep (TRecEntry b) # | |||||
Defined in GHC.Debug.Types.Closures type Rep (TRecEntry b) = D1 ('MetaData "TRecEntry" "GHC.Debug.Types.Closures" "ghc-debug-common-0.7.0.0-inplace" 'False) (C1 ('MetaCons "TRecEntry" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tvar") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "expected_value") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :*: (S1 ('MetaSel ('Just "new_value") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "trec_num_updates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))) |
Constructors
TsoLocked | |
TsoBlockx | |
TsoInterruptible | |
TsoStoppedOnBreakpoint | |
TsoMarked | |
TsoSqueezed | |
TsoAllocLimit | |
TsoFlagsUnknownValue Word32 |
Instances
Generic TsoFlags # | |||||
Defined in GHC.Debug.Types.Closures Associated Types
| |||||
Show TsoFlags # | |||||
Eq TsoFlags # | |||||
Ord TsoFlags # | |||||
Defined in GHC.Debug.Types.Closures | |||||
type Rep TsoFlags # | |||||
Defined in GHC.Debug.Types.Closures type Rep TsoFlags = D1 ('MetaData "TsoFlags" "GHC.Debug.Types.Closures" "ghc-debug-common-0.7.0.0-inplace" 'False) (((C1 ('MetaCons "TsoLocked" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TsoBlockx" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TsoInterruptible" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TsoStoppedOnBreakpoint" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TsoMarked" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TsoSqueezed" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TsoAllocLimit" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TsoFlagsUnknownValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32))))) |
Instances
Generic WhatNext # | |||||
Defined in GHC.Debug.Types.Closures Associated Types
| |||||
Show WhatNext # | |||||
Eq WhatNext # | |||||
Ord WhatNext # | |||||
Defined in GHC.Debug.Types.Closures | |||||
type Rep WhatNext # | |||||
Defined in GHC.Debug.Types.Closures type Rep WhatNext = D1 ('MetaData "WhatNext" "GHC.Debug.Types.Closures" "ghc-debug-common-0.7.0.0-inplace" 'False) ((C1 ('MetaCons "ThreadRunGHC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ThreadInterpret" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ThreadKilled" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ThreadComplete" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WhatNextUnknownValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16))))) |
data WhyBlocked #
Constructors
NotBlocked | |
BlockedOnMVar | |
BlockedOnMVarRead | |
BlockedOnBlackHole | |
BlockedOnRead | |
BlockedOnWrite | |
BlockedOnDelay | |
BlockedOnSTM | |
BlockedOnDoProc | |
BlockedOnCCall | |
BlockedOnCCall_Interruptible | |
BlockedOnMsgThrowTo | |
ThreadMigrating | |
WhyBlockedUnknownValue Word32 |
Instances
Generic WhyBlocked # | |||||
Defined in GHC.Debug.Types.Closures Associated Types
| |||||
Show WhyBlocked # | |||||
Defined in GHC.Debug.Types.Closures Methods showsPrec :: Int -> WhyBlocked -> ShowS # show :: WhyBlocked -> String # showList :: [WhyBlocked] -> ShowS # | |||||
Eq WhyBlocked # | |||||
Defined in GHC.Debug.Types.Closures | |||||
Ord WhyBlocked # | |||||
Defined in GHC.Debug.Types.Closures Methods compare :: WhyBlocked -> WhyBlocked -> Ordering # (<) :: WhyBlocked -> WhyBlocked -> Bool # (<=) :: WhyBlocked -> WhyBlocked -> Bool # (>) :: WhyBlocked -> WhyBlocked -> Bool # (>=) :: WhyBlocked -> WhyBlocked -> Bool # max :: WhyBlocked -> WhyBlocked -> WhyBlocked # min :: WhyBlocked -> WhyBlocked -> WhyBlocked # | |||||
type Rep WhyBlocked # | |||||
Defined in GHC.Debug.Types.Closures type Rep WhyBlocked = D1 ('MetaData "WhyBlocked" "GHC.Debug.Types.Closures" "ghc-debug-common-0.7.0.0-inplace" 'False) (((C1 ('MetaCons "NotBlocked" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BlockedOnMVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockedOnMVarRead" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "BlockedOnBlackHole" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockedOnRead" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BlockedOnWrite" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockedOnDelay" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "BlockedOnSTM" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BlockedOnDoProc" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockedOnCCall" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "BlockedOnCCall_Interruptible" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockedOnMsgThrowTo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ThreadMigrating" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WhyBlockedUnknownValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))))) |
data SourceInformation #
Constructors
SourceInformation | |
Fields
|
Instances
Show SourceInformation # | |
Defined in GHC.Debug.Types Methods showsPrec :: Int -> SourceInformation -> ShowS # show :: SourceInformation -> String # showList :: [SourceInformation] -> ShowS # | |
Eq SourceInformation # | |
Defined in GHC.Debug.Types Methods (==) :: SourceInformation -> SourceInformation -> Bool # (/=) :: SourceInformation -> SourceInformation -> Bool # | |
Ord SourceInformation # | |
Defined in GHC.Debug.Types Methods compare :: SourceInformation -> SourceInformation -> Ordering # (<) :: SourceInformation -> SourceInformation -> Bool # (<=) :: SourceInformation -> SourceInformation -> Bool # (>) :: SourceInformation -> SourceInformation -> Bool # (>=) :: SourceInformation -> SourceInformation -> Bool # max :: SourceInformation -> SourceInformation -> SourceInformation # min :: SourceInformation -> SourceInformation -> SourceInformation # |
Constructors
RawBlock BlockPtr Word16 ByteString |
data ClosurePtr #
Instances
Binary ClosurePtr # | |
Defined in GHC.Debug.Types.Ptr | |
Show ClosurePtr # | |
Defined in GHC.Debug.Types.Ptr Methods showsPrec :: Int -> ClosurePtr -> ShowS # show :: ClosurePtr -> String # showList :: [ClosurePtr] -> ShowS # | |
Eq ClosurePtr # | |
Defined in GHC.Debug.Types.Ptr | |
Ord ClosurePtr # | |
Defined in GHC.Debug.Types.Ptr Methods compare :: ClosurePtr -> ClosurePtr -> Ordering # (<) :: ClosurePtr -> ClosurePtr -> Bool # (<=) :: ClosurePtr -> ClosurePtr -> Bool # (>) :: ClosurePtr -> ClosurePtr -> Bool # (>=) :: ClosurePtr -> ClosurePtr -> Bool # max :: ClosurePtr -> ClosurePtr -> ClosurePtr # min :: ClosurePtr -> ClosurePtr -> ClosurePtr # | |
Hashable ClosurePtr # | |
Defined in GHC.Debug.Types.Ptr |
data InfoTablePtr #
Instances
Binary InfoTablePtr # | |
Defined in GHC.Debug.Types.Ptr | |
Show InfoTablePtr # | |
Defined in GHC.Debug.Types.Ptr Methods showsPrec :: Int -> InfoTablePtr -> ShowS # show :: InfoTablePtr -> String # showList :: [InfoTablePtr] -> ShowS # | |
Eq InfoTablePtr # | |
Defined in GHC.Debug.Types.Ptr | |
Ord InfoTablePtr # | |
Defined in GHC.Debug.Types.Ptr Methods compare :: InfoTablePtr -> InfoTablePtr -> Ordering # (<) :: InfoTablePtr -> InfoTablePtr -> Bool # (<=) :: InfoTablePtr -> InfoTablePtr -> Bool # (>) :: InfoTablePtr -> InfoTablePtr -> Bool # (>=) :: InfoTablePtr -> InfoTablePtr -> Bool # max :: InfoTablePtr -> InfoTablePtr -> InfoTablePtr # min :: InfoTablePtr -> InfoTablePtr -> InfoTablePtr # | |
Hashable InfoTablePtr # | |
Defined in GHC.Debug.Types.Ptr |
data IndexTablePtr #
Instances
Binary IndexTablePtr # | |
Defined in GHC.Debug.Types.Ptr | |
Show IndexTablePtr # | |
Defined in GHC.Debug.Types.Ptr Methods showsPrec :: Int -> IndexTablePtr -> ShowS # show :: IndexTablePtr -> String # showList :: [IndexTablePtr] -> ShowS # | |
Eq IndexTablePtr # | |
Defined in GHC.Debug.Types.Ptr Methods (==) :: IndexTablePtr -> IndexTablePtr -> Bool # (/=) :: IndexTablePtr -> IndexTablePtr -> Bool # | |
Ord IndexTablePtr # | |
Defined in GHC.Debug.Types.Ptr Methods compare :: IndexTablePtr -> IndexTablePtr -> Ordering # (<) :: IndexTablePtr -> IndexTablePtr -> Bool # (<=) :: IndexTablePtr -> IndexTablePtr -> Bool # (>) :: IndexTablePtr -> IndexTablePtr -> Bool # (>=) :: IndexTablePtr -> IndexTablePtr -> Bool # max :: IndexTablePtr -> IndexTablePtr -> IndexTablePtr # min :: IndexTablePtr -> IndexTablePtr -> IndexTablePtr # | |
Hashable IndexTablePtr # | |
Defined in GHC.Debug.Types.Ptr |
type StackHI = GenStackFrames (GenSrtPayload (Maybe HeapGraphIndex)) (Maybe HeapGraphIndex) #
type PapHI = GenPapPayload (Maybe HeapGraphIndex) #
type HeapGraphIndex = ClosurePtr #