Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Closure = GenClosure Box
- data GenClosure b
- = ConstrClosure { }
- | FunClosure {
- info :: !StgInfoTable
- ptrArgs :: ![b]
- dataArgs :: ![Word]
- | ThunkClosure {
- info :: !StgInfoTable
- ptrArgs :: ![b]
- dataArgs :: ![Word]
- | SelectorClosure {
- info :: !StgInfoTable
- selectee :: !b
- | PAPClosure { }
- | APClosure { }
- | APStackClosure {
- info :: !StgInfoTable
- fun :: !b
- payload :: ![b]
- | IndClosure {
- info :: !StgInfoTable
- indirectee :: !b
- | BCOClosure { }
- | BlackholeClosure {
- info :: !StgInfoTable
- indirectee :: !b
- | ArrWordsClosure { }
- | MutArrClosure {
- info :: !StgInfoTable
- mccPtrs :: !Word
- mccSize :: !Word
- mccPayload :: ![b]
- | SmallMutArrClosure {
- info :: !StgInfoTable
- mccPtrs :: !Word
- mccPayload :: ![b]
- | MVarClosure {
- info :: !StgInfoTable
- queueHead :: !b
- queueTail :: !b
- value :: !b
- | MutVarClosure {
- info :: !StgInfoTable
- var :: !b
- | BlockingQueueClosure { }
- | WeakClosure {
- info :: !StgInfoTable
- cfinalizers :: !b
- key :: !b
- value :: !b
- finalizer :: !b
- link :: !b
- | IntClosure { }
- | WordClosure { }
- | Int64Closure { }
- | Word64Closure { }
- | AddrClosure { }
- | FloatClosure { }
- | DoubleClosure { }
- | OtherClosure {
- info :: !StgInfoTable
- hvalues :: ![b]
- rawWords :: ![Word]
- | UnsupportedClosure {
- info :: !StgInfoTable
- data PrimType
- allClosures :: GenClosure b -> [b]
- closureSize :: Box -> Int
- data Box = Box Any
- areBoxesEqual :: Box -> Box -> IO Bool
- asBox :: a -> Box
Closures
type Closure = GenClosure Box Source #
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.
ConstrClosure | A data constructor |
FunClosure | A function |
| |
ThunkClosure | A thunk, an expression not obviously in head normal form |
| |
SelectorClosure | A thunk which performs a simple selection operation |
| |
PAPClosure | An unsaturated function application |
| |
APClosure | A function application |
| |
APStackClosure | A suspended thunk evaluation |
| |
IndClosure | A pointer to another closure, introduced when a thunk is updated to point at its value |
| |
BCOClosure | A byte-code object (BCO) which can be interpreted by GHC's byte-code interpreter (e.g. as used by GHCi) |
| |
BlackholeClosure | A thunk under evaluation by another thread |
| |
ArrWordsClosure | A |
MutArrClosure | A |
| |
SmallMutArrClosure | A Since: ghc-heap-8.10.1 |
| |
MVarClosure | An |
| |
MutVarClosure | A |
| |
BlockingQueueClosure | An STM blocking queue. |
WeakClosure | |
| |
IntClosure | Primitive Int |
WordClosure | Primitive Word |
Int64Closure | Primitive Int64 |
Word64Closure | Primitive Word64 |
AddrClosure | Primitive Addr |
FloatClosure | Primitive Float |
DoubleClosure | Primitive Double |
OtherClosure | Another kind of closure |
| |
UnsupportedClosure | |
|
Instances
Instances
Eq PrimType # | |
Show PrimType # | |
Generic PrimType # | |
type Rep PrimType # | |
Defined in GHC.Exts.Heap.Closures type Rep PrimType = D1 ('MetaData "PrimType" "GHC.Exts.Heap.Closures" "ghc-heap-8.10.1" '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 a closure in words.
Since: ghc-heap-8.10.1
Boxes
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.