ghc-debug-common-0.6.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 ccs srt 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 

Fields

StackClosure 

Fields

WeakClosure 

Fields

TVarClosure 
TRecChunkClosure 
MutPrimClosure 

Fields

PrimClosure 

Fields

OtherClosure

Another kind of closure

Fields

UnsupportedClosure 

Instances

Instances details
Hextraversable DebugClosure Source # 
Instance details

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

Foldable (DebugClosure ccs srt pap string s) Source # 
Instance details

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

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

Functor (DebugClosure ccs srt pap string s) Source # 
Instance details

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 #

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

Defined in GHC.Debug.Types.Closures

Associated Types

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

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

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

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

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

Defined in GHC.Debug.Types.Closures

type Rep (DebugClosure ccs srt pap string s b)

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.6.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 ccs srt pap string s b Source #

Constructors

DCS 

Fields

Instances

Instances details
Hextraversable (DebugClosureWithExtra x) Source # 
Instance details

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

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

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

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

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 #

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 #

Read Size Source # 
Instance details

Defined in GHC.Debug.Types.Closures

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.6.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.6.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.6.0.0-inplace" 'True) (C1 ('MetaCons "RetainerSize" 'PrefixI 'True) (S1 ('MetaSel ('Just "getRetainerSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

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

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

Info Table Representation

data StgInfoTable Source #

Constructors

StgInfoTable 

Fields

Instances

Instances details
Generic StgInfoTable Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Associated Types

type Rep StgInfoTable :: Type -> Type #

Show StgInfoTable Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Eq StgInfoTable Source # 
Instance details

Defined in GHC.Debug.Types.Closures

type Rep StgInfoTable Source # 
Instance details

Defined in GHC.Debug.Types.Closures

data ClosureType Source #

Instances

Instances details
Enum ClosureType Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Generic ClosureType Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Associated Types

type Rep ClosureType :: Type -> Type #

Read ClosureType Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Show ClosureType Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Eq ClosureType Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Ord ClosureType Source # 
Instance details

Defined in GHC.Debug.Types.Closures

type Rep ClosureType Source # 
Instance details

Defined in GHC.Debug.Types.Closures

type Rep ClosureType = D1 ('MetaData "ClosureType" "GHC.Debug.Types.Closures" "ghc-debug-common-0.6.0.0-inplace" '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 "CONTINUATION" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "N_CLOSURE_TYPES" 'PrefixI 'False) (U1 :: Type -> Type))))))))

data WhatNext Source #

Instances

Instances details
Generic WhatNext Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Associated Types

type Rep WhatNext :: Type -> Type #

Methods

from :: WhatNext -> Rep WhatNext x #

to :: Rep WhatNext x -> WhatNext #

Show WhatNext Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Eq WhatNext Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Ord WhatNext Source # 
Instance details

Defined in GHC.Debug.Types.Closures

type Rep WhatNext Source # 
Instance details

Defined in GHC.Debug.Types.Closures

type Rep WhatNext = D1 ('MetaData "WhatNext" "GHC.Debug.Types.Closures" "ghc-debug-common-0.6.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 Source #

Instances

Instances details
Generic WhyBlocked Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Associated Types

type Rep WhyBlocked :: Type -> Type #

Show WhyBlocked Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Eq WhyBlocked Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Ord WhyBlocked Source # 
Instance details

Defined in GHC.Debug.Types.Closures

type Rep WhyBlocked Source # 
Instance details

Defined in GHC.Debug.Types.Closures

type Rep WhyBlocked = D1 ('MetaData "WhyBlocked" "GHC.Debug.Types.Closures" "ghc-debug-common-0.6.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 TsoFlags Source #

Instances

Instances details
Generic TsoFlags Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Associated Types

type Rep TsoFlags :: Type -> Type #

Methods

from :: TsoFlags -> Rep TsoFlags x #

to :: Rep TsoFlags x -> TsoFlags #

Show TsoFlags Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Eq TsoFlags Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Ord TsoFlags Source # 
Instance details

Defined in GHC.Debug.Types.Closures

type Rep TsoFlags Source # 
Instance details

Defined in GHC.Debug.Types.Closures

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

Stack Frame Representation

data DebugStackFrame srt b Source #

Constructors

DebugStackFrame 

Instances

Instances details
Bifoldable DebugStackFrame Source # 
Instance details

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

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

Defined in GHC.Debug.Types.Closures

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> DebugStackFrame a b -> f (DebugStackFrame c d) #

Foldable (DebugStackFrame srt) Source # 
Instance details

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

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

Functor (DebugStackFrame srt) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

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

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

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

Defined in GHC.Debug.Types.Closures

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

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) 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 srt b Source #

Constructors

GenStackFrames 

Fields

Instances

Instances details
Bifoldable GenStackFrames Source # 
Instance details

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

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

Defined in GHC.Debug.Types.Closures

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> GenStackFrames a b -> f (GenStackFrames c d) #

Foldable (GenStackFrames srt) Source # 
Instance details

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

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

Functor (GenStackFrames srt) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

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

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

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

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

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

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 #

data StackCont Source #

Information needed to decode a set of stack frames

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

Eq 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

SRT field representation

newtype GenSrtPayload b Source #

Constructors

GenSrtPayload 

Fields

Instances

Instances details
Foldable GenSrtPayload Source # 
Instance details

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

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

Functor GenSrtPayload Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

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

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

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

Defined in GHC.Debug.Types.Closures

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

Defined in GHC.Debug.Types.Closures

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

Defined in GHC.Debug.Types.Closures

data ProfHeader a Source #

Constructors

ProfHeader 

Fields

Instances

Instances details
Foldable ProfHeader Source # 
Instance details

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

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

Functor ProfHeader Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

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

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

Show a => Show (ProfHeader a) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Eq a => Eq (ProfHeader a) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

Methods

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

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

Ord a => Ord (ProfHeader a) Source # 
Instance details

Defined in GHC.Debug.Types.Closures

data GenCCSPayload ccsPtr ccPtr Source #

Instances

Instances details
Bifoldable GenCCSPayload Source # 
Instance details

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

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

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

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

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

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

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 #

Traversing functions

class Hextraversable m where Source #

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

Instances

Instances details
Hextraversable DebugClosure Source # 
Instance details

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

Hextraversable (DebugClosureWithExtra x) Source # 
Instance details

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

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