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.Closures

Description

The Haskell representation of a heap closure, the DebugClosure type - is quite similar to the one found in the ghc-heap package but with some - more type parameters and other changes..

Synopsis

Closure Representation

data DebugClosure pap string s b Source #

This is the representation of a Haskell value on the heap. It reflects https://gitlab.haskell.org/ghc/ghc/blob/master/includes/rts/storage/Closures.h

The data type is parametrized by 4 type parameters which correspond to different pointer types.

All Heap objects have the same basic layout. A header containing a pointer to the info table and a payload with various fields. The info field below always refers to the info table pointed to by the header. The remaining fields are the payload.

See https://gitlab.haskell.org/ghc/ghc/wikis/commentary/rts/storage/heap-objects for more information.

Constructors

ConstrClosure

A data constructor

Fields

FunClosure

A function

Fields

ThunkClosure

A thunk, an expression not obviously in head normal form

Fields

SelectorClosure

A thunk which performs a simple selection operation

Fields

PAPClosure

An unsaturated function application

Fields

APClosure

A function application

Fields

APStackClosure

A suspended thunk evaluation

Fields

IndClosure

A pointer to another closure, introduced when a thunk is updated to point at its value

Fields

BCOClosure

A byte-code object (BCO) which can be interpreted by GHC's byte-code interpreter (e.g. as used by GHCi)

Fields

BlackholeClosure

A thunk under evaluation by another thread

Fields

ArrWordsClosure

A ByteArray#

Fields

MutArrClosure

A MutableByteArray#

Fields

SmallMutArrClosure

A SmallMutableArray#

Since: 8.10.1

Fields

MVarClosure

An MVar#, with a queue of thread state objects blocking on them

Fields

MutVarClosure

A MutVar#

Fields

BlockingQueueClosure

An STM blocking queue.

Fields

TSOClosure 
StackClosure 

Fields

WeakClosure 

Fields

TVarClosure 
TRecChunkClosure 
MutPrimClosure 

Fields

OtherClosure

Another kind of closure

Fields

UnsupportedClosure 

Instances

Instances details
Quadtraversable DebugClosure Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

quadtraverse :: Applicative f => (a -> f b) -> (c -> f d) -> (e -> f g) -> (h -> f i) -> DebugClosure a c e h -> f (DebugClosure b d g i) Source #

Foldable (DebugClosure pap string s) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

fold :: Monoid m => DebugClosure pap string s m -> m #

foldMap :: Monoid m => (a -> m) -> DebugClosure pap string s a -> m #

foldMap' :: Monoid m => (a -> m) -> DebugClosure pap string s a -> m #

foldr :: (a -> b -> b) -> b -> DebugClosure pap string s a -> b #

foldr' :: (a -> b -> b) -> b -> DebugClosure pap string s a -> b #

foldl :: (b -> a -> b) -> b -> DebugClosure pap string s a -> b #

foldl' :: (b -> a -> b) -> b -> DebugClosure pap string s a -> b #

foldr1 :: (a -> a -> a) -> DebugClosure pap string s a -> a #

foldl1 :: (a -> a -> a) -> DebugClosure pap string s a -> a #

toList :: DebugClosure pap string s a -> [a] #

null :: DebugClosure pap string s a -> Bool #

length :: DebugClosure pap string s a -> Int #

elem :: Eq a => a -> DebugClosure pap string s a -> Bool #

maximum :: Ord a => DebugClosure pap string s a -> a #

minimum :: Ord a => DebugClosure pap string s a -> a #

sum :: Num a => DebugClosure pap string s a -> a #

product :: Num a => DebugClosure pap string s a -> a #

Traversable (DebugClosure pap string s) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

traverse :: Applicative f => (a -> f b) -> DebugClosure pap string s a -> f (DebugClosure pap string s b) #

sequenceA :: Applicative f => DebugClosure pap string s (f a) -> f (DebugClosure pap string s a) #

mapM :: Monad m => (a -> m b) -> DebugClosure pap string s a -> m (DebugClosure pap string s b) #

sequence :: Monad m => DebugClosure pap string s (m a) -> m (DebugClosure pap string s a) #

Functor (DebugClosure pap string s) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

fmap :: (a -> b) -> DebugClosure pap string s a -> DebugClosure pap string s b #

(<$) :: a -> DebugClosure pap string s b -> DebugClosure pap string s a #

Generic (DebugClosure pap string s b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Associated Types

type Rep (DebugClosure pap string s b) :: Type -> Type #

Methods

from :: DebugClosure pap string s b -> Rep (DebugClosure pap string s b) x #

to :: Rep (DebugClosure pap string s b) x -> DebugClosure pap string s b #

(Show b, Show string, Show pap, Show s) => Show (DebugClosure pap string s b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

showsPrec :: Int -> DebugClosure pap string s b -> ShowS #

show :: DebugClosure pap string s b -> String #

showList :: [DebugClosure pap string s b] -> ShowS #

(Eq b, Eq string, Eq pap, Eq s) => Eq (DebugClosure pap string s b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

(==) :: DebugClosure pap string s b -> DebugClosure pap string s b -> Bool #

(/=) :: DebugClosure pap string s b -> DebugClosure pap string s b -> Bool #

(Ord b, Ord string, Ord pap, Ord s) => Ord (DebugClosure pap string s b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

compare :: DebugClosure pap string s b -> DebugClosure pap string s b -> Ordering #

(<) :: DebugClosure pap string s b -> DebugClosure pap string s b -> Bool #

(<=) :: DebugClosure pap string s b -> DebugClosure pap string s b -> Bool #

(>) :: DebugClosure pap string s b -> DebugClosure pap string s b -> Bool #

(>=) :: DebugClosure pap string s b -> DebugClosure pap string s b -> Bool #

max :: DebugClosure pap string s b -> DebugClosure pap string s b -> DebugClosure pap string s b #

min :: DebugClosure pap string s b -> DebugClosure pap string s b -> DebugClosure pap string s b #

type Rep (DebugClosure pap string s b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

type Rep (DebugClosure pap string s b) = D1 ('MetaData "DebugClosure" "GHC.Debug.Types.Closures" "ghc-debug-common-0.2.0.0-inplace" 'False) ((((C1 ('MetaCons "ConstrClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: 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 "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 "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 "selectee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :+: (C1 ('MetaCons "PAPClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: S1 ('MetaSel ('Just "arity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HalfWord)) :*: (S1 ('MetaSel ('Just "n_args") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (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 "arity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HalfWord)) :*: (S1 ('MetaSel ('Just "n_args") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (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 "ap_st_size") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (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 "indirectee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :+: C1 ('MetaCons "BCOClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: (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 'DecidedStrict) (Rec0 HalfWord)) :*: (S1 ('MetaSel ('Just "size") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HalfWord) :*: S1 ('MetaSel ('Just "bitmap") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word])))))) :+: (C1 ('MetaCons "BlackholeClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: 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 "bytes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (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 "mccPtrs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word)) :*: (S1 ('MetaSel ('Just "mccSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (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 "mccPtrs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (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 "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 "var") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)))) :+: (C1 ('MetaCons "BlockingQueueClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: 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 "_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 "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 "stack_size") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32)) :*: (S1 ('MetaSel ('Just "stack_dirty") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word8) :*: (S1 ('MetaSel ('Just "stack_marking") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (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 "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 "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 'DecidedStrict) (Rec0 Int))) :+: C1 ('MetaCons "TRecChunkClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTableWithPtr) :*: S1 ('MetaSel ('Just "prev_chunk") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :*: (S1 ('MetaSel ('Just "next_idx") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (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 "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 "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)))))))

data TRecEntry b Source #

Constructors

TRecEntry 

Fields

Instances

Instances details
Foldable TRecEntry Source # 
Instance details

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] #

null :: TRecEntry a -> Bool #

length :: TRecEntry a -> Int #

elem :: Eq a => a -> TRecEntry a -> Bool #

maximum :: Ord a => TRecEntry a -> a #

minimum :: Ord a => TRecEntry a -> a #

sum :: Num a => TRecEntry a -> a #

product :: Num a => TRecEntry a -> a #

Traversable TRecEntry Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

traverse :: Applicative f => (a -> f b) -> TRecEntry a -> f (TRecEntry b) #

sequenceA :: Applicative f => TRecEntry (f a) -> f (TRecEntry a) #

mapM :: Monad m => (a -> m b) -> TRecEntry a -> m (TRecEntry b) #

sequence :: Monad m => TRecEntry (m a) -> m (TRecEntry a) #

Functor TRecEntry Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

fmap :: (a -> b) -> TRecEntry a -> TRecEntry b #

(<$) :: a -> TRecEntry b -> TRecEntry a #

Generic (TRecEntry b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Associated Types

type Rep (TRecEntry b) :: Type -> Type #

Methods

from :: TRecEntry b -> Rep (TRecEntry b) x #

to :: Rep (TRecEntry b) x -> TRecEntry b #

Show b => Show (TRecEntry b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Eq b => Eq (TRecEntry b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

(==) :: TRecEntry b -> TRecEntry b -> Bool #

(/=) :: TRecEntry b -> TRecEntry b -> Bool #

Ord b => Ord (TRecEntry b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

type Rep (TRecEntry b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

type Rep (TRecEntry b) = D1 ('MetaData "TRecEntry" "GHC.Debug.Types.Closures" "ghc-debug-common-0.2.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))))

Wrappers

data DebugClosureWithExtra x pap string s b Source #

Constructors

DCS 

Fields

Instances

Instances details
Quadtraversable (DebugClosureWithExtra x) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

quadtraverse :: Applicative f => (a -> f b) -> (c -> f d) -> (e -> f g) -> (h -> f i) -> DebugClosureWithExtra x a c e h -> f (DebugClosureWithExtra x b d g i) Source #

(Show x, Show b, Show string, Show pap, Show s) => Show (DebugClosureWithExtra x pap string s b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

showsPrec :: Int -> DebugClosureWithExtra x pap string s b -> ShowS #

show :: DebugClosureWithExtra x pap string s b -> String #

showList :: [DebugClosureWithExtra x pap string s b] -> ShowS #

(Eq x, Eq b, Eq string, Eq pap, Eq s) => Eq (DebugClosureWithExtra x pap string s b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

(==) :: DebugClosureWithExtra x pap string s b -> DebugClosureWithExtra x pap string s b -> Bool #

(/=) :: DebugClosureWithExtra x pap string s b -> DebugClosureWithExtra x pap string s b -> Bool #

(Ord x, Ord b, Ord string, Ord pap, Ord s) => Ord (DebugClosureWithExtra x pap string s b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

compare :: DebugClosureWithExtra x pap string s b -> DebugClosureWithExtra x pap string s b -> Ordering #

(<) :: DebugClosureWithExtra x pap string s b -> DebugClosureWithExtra x pap string s b -> Bool #

(<=) :: DebugClosureWithExtra x pap string s b -> DebugClosureWithExtra x pap string s b -> Bool #

(>) :: DebugClosureWithExtra x pap string s b -> DebugClosureWithExtra x pap string s b -> Bool #

(>=) :: DebugClosureWithExtra x pap string s b -> DebugClosureWithExtra x pap string s b -> Bool #

max :: DebugClosureWithExtra x pap string s b -> DebugClosureWithExtra x pap string s b -> DebugClosureWithExtra x pap string s b #

min :: DebugClosureWithExtra x pap string s b -> DebugClosureWithExtra x pap string s b -> DebugClosureWithExtra x pap string s b #

newtype Size Source #

Exclusive size

Constructors

Size 

Fields

Instances

Instances details
Monoid Size Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

mempty :: Size #

mappend :: Size -> Size -> Size #

mconcat :: [Size] -> Size #

Semigroup Size Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

(<>) :: Size -> Size -> Size #

sconcat :: NonEmpty Size -> Size #

stimes :: Integral b => b -> Size -> Size #

Generic Size Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Associated Types

type Rep Size :: Type -> Type #

Methods

from :: Size -> Rep Size x #

to :: Rep Size x -> Size #

Num Size Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

(+) :: Size -> Size -> Size #

(-) :: Size -> Size -> Size #

(*) :: Size -> Size -> Size #

negate :: Size -> Size #

abs :: Size -> Size #

signum :: Size -> Size #

fromInteger :: Integer -> Size #

Show Size Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

Eq Size Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

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

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

Ord Size Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

compare :: Size -> Size -> Ordering #

(<) :: Size -> Size -> Bool #

(<=) :: Size -> Size -> Bool #

(>) :: Size -> Size -> Bool #

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

max :: Size -> Size -> Size #

min :: Size -> Size -> Size #

type Rep Size Source # 
Instance details

Defined in GHC.Debug.Types.Closures

type Rep Size = D1 ('MetaData "Size" "GHC.Debug.Types.Closures" "ghc-debug-common-0.2.0.0-inplace" 'True) (C1 ('MetaCons "Size" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

newtype InclusiveSize Source #

Constructors

InclusiveSize 

Instances

Instances details
Monoid InclusiveSize Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Semigroup InclusiveSize Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Generic InclusiveSize Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Associated Types

type Rep InclusiveSize :: Type -> Type #

Show InclusiveSize Source # 
Instance details

Defined in GHC.Debug.Types.Closures

type Rep InclusiveSize Source # 
Instance details

Defined in GHC.Debug.Types.Closures

type Rep InclusiveSize = D1 ('MetaData "InclusiveSize" "GHC.Debug.Types.Closures" "ghc-debug-common-0.2.0.0-inplace" 'True) (C1 ('MetaCons "InclusiveSize" 'PrefixI 'True) (S1 ('MetaSel ('Just "getInclusiveSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

newtype RetainerSize Source #

Constructors

RetainerSize 

Fields

Instances

Instances details
Monoid RetainerSize Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Semigroup RetainerSize Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Generic RetainerSize Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Associated Types

type Rep RetainerSize :: Type -> Type #

Show RetainerSize Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Eq RetainerSize Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Ord RetainerSize Source # 
Instance details

Defined in GHC.Debug.Types.Closures

type Rep RetainerSize Source # 
Instance details

Defined in GHC.Debug.Types.Closures

type Rep RetainerSize = D1 ('MetaData "RetainerSize" "GHC.Debug.Types.Closures" "ghc-debug-common-0.2.0.0-inplace" 'True) (C1 ('MetaCons "RetainerSize" 'PrefixI 'True) (S1 ('MetaSel ('Just "getRetainerSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

noSize :: DebugClosureWithSize pap string s b -> DebugClosure pap string s b Source #

dcSize :: DebugClosureWithSize pap string s b -> Size Source #

Info Table Representation

data StgInfoTable #

This is a somewhat faithful representation of an info table. See https://gitlab.haskell.org/ghc/ghc/blob/master/includes/rts/storage/InfoTables.h for more details on this data structure.

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))))))))

Stack Frame Representation

data DebugStackFrame b Source #

Instances

Instances details
Foldable DebugStackFrame Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

fold :: Monoid m => DebugStackFrame m -> m #

foldMap :: Monoid m => (a -> m) -> DebugStackFrame a -> m #

foldMap' :: Monoid m => (a -> m) -> DebugStackFrame a -> m #

foldr :: (a -> b -> b) -> b -> DebugStackFrame a -> b #

foldr' :: (a -> b -> b) -> b -> DebugStackFrame a -> b #

foldl :: (b -> a -> b) -> b -> DebugStackFrame a -> b #

foldl' :: (b -> a -> b) -> b -> DebugStackFrame a -> b #

foldr1 :: (a -> a -> a) -> DebugStackFrame a -> a #

foldl1 :: (a -> a -> a) -> DebugStackFrame a -> a #

toList :: DebugStackFrame a -> [a] #

null :: DebugStackFrame a -> Bool #

length :: DebugStackFrame a -> Int #

elem :: Eq a => a -> DebugStackFrame a -> Bool #

maximum :: Ord a => DebugStackFrame a -> a #

minimum :: Ord a => DebugStackFrame a -> a #

sum :: Num a => DebugStackFrame a -> a #

product :: Num a => DebugStackFrame a -> a #

Traversable DebugStackFrame Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

traverse :: Applicative f => (a -> f b) -> DebugStackFrame a -> f (DebugStackFrame b) #

sequenceA :: Applicative f => DebugStackFrame (f a) -> f (DebugStackFrame a) #

mapM :: Monad m => (a -> m b) -> DebugStackFrame a -> m (DebugStackFrame b) #

sequence :: Monad m => DebugStackFrame (m a) -> m (DebugStackFrame a) #

Functor DebugStackFrame Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

fmap :: (a -> b) -> DebugStackFrame a -> DebugStackFrame b #

(<$) :: a -> DebugStackFrame b -> DebugStackFrame a #

Show b => Show (DebugStackFrame b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Eq b => Eq (DebugStackFrame b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Ord b => Ord (DebugStackFrame b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

data FieldValue b Source #

Constructors

SPtr b 
SNonPtr !Word64 

Instances

Instances details
Foldable FieldValue Source # 
Instance details

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 Source # 
Instance details

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) #

Functor FieldValue Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

fmap :: (a -> b) -> FieldValue a -> FieldValue b #

(<$) :: a -> FieldValue b -> FieldValue a #

Show b => Show (FieldValue b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Eq b => Eq (FieldValue b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

(==) :: FieldValue b -> FieldValue b -> Bool #

(/=) :: FieldValue b -> FieldValue b -> Bool #

Ord b => Ord (FieldValue b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

newtype GenStackFrames b Source #

Constructors

GenStackFrames 

Fields

Instances

Instances details
Foldable GenStackFrames Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

fold :: Monoid m => GenStackFrames m -> m #

foldMap :: Monoid m => (a -> m) -> GenStackFrames a -> m #

foldMap' :: Monoid m => (a -> m) -> GenStackFrames a -> m #

foldr :: (a -> b -> b) -> b -> GenStackFrames a -> b #

foldr' :: (a -> b -> b) -> b -> GenStackFrames a -> b #

foldl :: (b -> a -> b) -> b -> GenStackFrames a -> b #

foldl' :: (b -> a -> b) -> b -> GenStackFrames a -> b #

foldr1 :: (a -> a -> a) -> GenStackFrames a -> a #

foldl1 :: (a -> a -> a) -> GenStackFrames a -> a #

toList :: GenStackFrames a -> [a] #

null :: GenStackFrames a -> Bool #

length :: GenStackFrames a -> Int #

elem :: Eq a => a -> GenStackFrames a -> Bool #

maximum :: Ord a => GenStackFrames a -> a #

minimum :: Ord a => GenStackFrames a -> a #

sum :: Num a => GenStackFrames a -> a #

product :: Num a => GenStackFrames a -> a #

Traversable GenStackFrames Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

traverse :: Applicative f => (a -> f b) -> GenStackFrames a -> f (GenStackFrames b) #

sequenceA :: Applicative f => GenStackFrames (f a) -> f (GenStackFrames a) #

mapM :: Monad m => (a -> m b) -> GenStackFrames a -> m (GenStackFrames b) #

sequence :: Monad m => GenStackFrames (m a) -> m (GenStackFrames a) #

Functor GenStackFrames Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

fmap :: (a -> b) -> GenStackFrames a -> GenStackFrames b #

(<$) :: a -> GenStackFrames b -> GenStackFrames a #

Show b => Show (GenStackFrames b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Eq b => Eq (GenStackFrames b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Ord b => Ord (GenStackFrames b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

data StackCont Source #

Information needed to decode a set of stack frames

Instances

Instances details
Show StackCont Source # 
Instance details

Defined in GHC.Debug.Types.Closures

PAP payload representation

newtype GenPapPayload b Source #

Constructors

GenPapPayload 

Fields

Instances

Instances details
Foldable GenPapPayload Source # 
Instance details

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 Source # 
Instance details

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) #

Functor GenPapPayload Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

fmap :: (a -> b) -> GenPapPayload a -> GenPapPayload b #

(<$) :: a -> GenPapPayload b -> GenPapPayload a #

Show b => Show (GenPapPayload b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Eq b => Eq (GenPapPayload b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Ord b => Ord (GenPapPayload b) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

data PayloadCont Source #

Information needed to decode a PAP payload

Constructors

PayloadCont ClosurePtr [Word64] 

Instances

Instances details
Show PayloadCont Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Constructor Description Representation

data ConstrDesc Source #

Constructors

ConstrDesc 

Fields

type ConstrDescCont = InfoTablePtr Source #

Information needed to decode a ConstrDesc

Traversing functions

class Quadtraversable m where Source #

Methods

quadtraverse :: Applicative f => (a -> f b) -> (c -> f d) -> (e -> f g) -> (h -> f i) -> m a c e h -> f (m b d g i) Source #

Instances

Instances details
Quadtraversable DebugClosure Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

quadtraverse :: Applicative f => (a -> f b) -> (c -> f d) -> (e -> f g) -> (h -> f i) -> DebugClosure a c e h -> f (DebugClosure b d g i) Source #

Quadtraversable (DebugClosureWithExtra x) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

quadtraverse :: Applicative f => (a -> f b) -> (c -> f d) -> (e -> f g) -> (h -> f i) -> DebugClosureWithExtra x a c e h -> f (DebugClosureWithExtra x b d g i) Source #

quadmap :: forall a b c d e f g h t. Quadtraversable t => (a -> b) -> (c -> d) -> (e -> f) -> (g -> h) -> t a c e g -> t b d f h Source #