ghc-heap-9.0.1: Functions for walking GHC's heap
Safe HaskellNone
LanguageHaskell2010

GHC.Exts.Heap.Closures

Synopsis

Closures

data GenClosure 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 the type to store references in. Usually this is a Box with the type synonym Closure.

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

  • info :: !StgInfoTable
     
  • instrs :: !b

    A pointer to an ArrWords of instructions

  • literals :: !b

    A pointer to an ArrWords of literals

  • bcoptrs :: !b

    A pointer to an ArrWords of byte code objects

  • arity :: !HalfWord

    Arity of the partial application

  • size :: !HalfWord

    The size of this BCO in words

  • bitmap :: ![Word]

    An StgLargeBitmap describing the pointerhood of its args/free vars

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

IOPortClosure

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

Fields

MutVarClosure

A MutVar#

Fields

BlockingQueueClosure

An STM blocking queue.

Fields

WeakClosure 

Fields

IntClosure

Primitive Int

Fields

WordClosure

Primitive Word

Fields

Int64Closure

Primitive Int64

Fields

Word64Closure

Primitive Word64

Fields

AddrClosure

Primitive Addr

Fields

FloatClosure

Primitive Float

Fields

DoubleClosure

Primitive Double

Fields

OtherClosure

Another kind of closure

Fields

UnsupportedClosure 

Fields

Instances

Instances details
Functor GenClosure Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Methods

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

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

Foldable GenClosure Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Methods

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

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

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

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

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

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

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

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

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

toList :: GenClosure a -> [a] #

null :: GenClosure a -> Bool #

length :: GenClosure a -> Int #

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

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

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

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

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

Traversable GenClosure Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Methods

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

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

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

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

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

Defined in GHC.Exts.Heap.Closures

Generic (GenClosure b) Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

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

Methods

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

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

type Rep (GenClosure b) Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

type Rep (GenClosure b) = D1 ('MetaData "GenClosure" "GHC.Exts.Heap.Closures" "ghc-heap-9.0.1-COvifXZwcNtEPlzrVE2khv" 'False) ((((C1 ('MetaCons "ConstrClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (S1 ('MetaSel ('Just "ptrArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]) :*: S1 ('MetaSel ('Just "dataArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word]))) :*: (S1 ('MetaSel ('Just "pkg") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String) :*: (S1 ('MetaSel ('Just "modl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String)))) :+: (C1 ('MetaCons "FunClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (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 StgInfoTable) :*: (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 StgInfoTable) :*: S1 ('MetaSel ('Just "selectee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :+: (C1 ('MetaCons "PAPClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: 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 "payload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b])))) :+: C1 ('MetaCons "APClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: 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 "payload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]))))))) :+: ((C1 ('MetaCons "APStackClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (S1 ('MetaSel ('Just "fun") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "payload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]))) :+: (C1 ('MetaCons "IndClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "indirectee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :+: C1 ('MetaCons "BCOClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (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 StgInfoTable) :*: S1 ('MetaSel ('Just "indirectee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :+: C1 ('MetaCons "ArrWordsClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (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 StgInfoTable) :*: 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 StgInfoTable) :*: (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 StgInfoTable) :*: 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 "IOPortClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: 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 StgInfoTable) :*: S1 ('MetaSel ('Just "var") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)))) :+: ((C1 ('MetaCons "BlockingQueueClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: 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 "WeakClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (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 "link") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b))))) :+: (C1 ('MetaCons "IntClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType) :*: S1 ('MetaSel ('Just "intVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "WordClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType) :*: S1 ('MetaSel ('Just "wordVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word))))) :+: ((C1 ('MetaCons "Int64Closure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType) :*: S1 ('MetaSel ('Just "int64Val") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int64)) :+: (C1 ('MetaCons "Word64Closure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType) :*: S1 ('MetaSel ('Just "word64Val") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64)) :+: C1 ('MetaCons "AddrClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType) :*: S1 ('MetaSel ('Just "addrVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)))) :+: ((C1 ('MetaCons "FloatClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType) :*: S1 ('MetaSel ('Just "floatVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Float)) :+: C1 ('MetaCons "DoubleClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType) :*: S1 ('MetaSel ('Just "doubleVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double))) :+: (C1 ('MetaCons "OtherClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (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 StgInfoTable)))))))

data PrimType Source #

Instances

Instances details
Eq PrimType Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Show PrimType Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Generic PrimType Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep PrimType :: Type -> Type #

Methods

from :: PrimType -> Rep PrimType x #

to :: Rep PrimType x -> PrimType #

type Rep PrimType Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

type Rep PrimType = D1 ('MetaData "PrimType" "GHC.Exts.Heap.Closures" "ghc-heap-9.0.1-COvifXZwcNtEPlzrVE2khv" 'False) ((C1 ('MetaCons "PInt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PWord" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PInt64" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PWord64" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PAddr" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PFloat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PDouble" 'PrefixI 'False) (U1 :: Type -> Type))))

allClosures :: GenClosure b -> [b] Source #

For generic code, this function returns all referenced closures.

closureSize :: Box -> Int Source #

Get the size of the top-level closure in words. Includes header and payload. Does not follow pointers.

Since: 8.10.1

Boxes

data Box Source #

An arbitrary Haskell value in a safe Box. The point is that even unevaluated thunks can safely be moved around inside the Box, and when required, e.g. in getBoxedClosureData, the function knows how far it has to evaluate the argument.

Constructors

Box Any 

Instances

Instances details
Show Box Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Methods

showsPrec :: Int -> Box -> ShowS #

show :: Box -> String #

showList :: [Box] -> ShowS #

areBoxesEqual :: Box -> Box -> IO Bool Source #

Boxes can be compared, but this is not pure, as different heap objects can, after garbage collection, become the same object.

asBox :: a -> Box Source #

This takes an arbitrary value and puts it into a box. Note that calls like

asBox (head list)

will put the thunk "head list" into the box, not the element at the head of the list. For that, use careful case expressions:

case list of x:_ -> asBox x