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
- | IOPortClosure {
- 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
- | TSOClosure {
- info :: !StgInfoTable
- link :: !b
- global_link :: !b
- tsoStack :: !b
- trec :: !b
- blocked_exceptions :: !b
- bq :: !b
- what_next :: !WhatNext
- why_blocked :: !WhyBlocked
- flags :: ![TsoFlags]
- threadId :: !Word64
- saved_errno :: !Word32
- tso_dirty :: !Word32
- alloc_limit :: !Int64
- tot_stack_size :: !Word32
- prof :: !(Maybe StgTSOProfInfo)
- | StackClosure {
- info :: !StgInfoTable
- stack_size :: !Word32
- stack_dirty :: !Word8
- stack_marking :: !Word8
- | IntClosure { }
- | WordClosure { }
- | Int64Closure { }
- | Word64Closure { }
- | AddrClosure { }
- | FloatClosure { }
- | DoubleClosure { }
- | OtherClosure {
- info :: !StgInfoTable
- hvalues :: ![b]
- rawWords :: ![Word]
- | UnsupportedClosure {
- info :: !StgInfoTable
- data PrimType
- data WhatNext
- data WhyBlocked
- data TsoFlags
- 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 b
: 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 |
| |
IOPortClosure | An |
| |
MutVarClosure | A |
| |
BlockingQueueClosure | An STM blocking queue. |
WeakClosure | |
| |
TSOClosure | Representation of StgTSO: A Thread State Object. The values for
|
| |
StackClosure | Representation of StgStack: The 'tsoStack ' of a |
| |
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
Generic PrimType Source # | |
Show PrimType Source # | |
Eq PrimType Source # | |
Ord PrimType Source # | |
Defined in GHC.Exts.Heap.Closures | |
type Rep PrimType Source # | |
Defined in GHC.Exts.Heap.Closures type Rep PrimType = D1 ('MetaData "PrimType" "GHC.Exts.Heap.Closures" "ghc-heap-9.2.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)))) |
ThreadRunGHC | |
ThreadInterpret | |
ThreadKilled | |
ThreadComplete | |
WhatNextUnknownValue Word16 | Please report this as a bug |
Instances
Generic WhatNext Source # | |
Show WhatNext Source # | |
Eq WhatNext Source # | |
Ord WhatNext Source # | |
Defined in GHC.Exts.Heap.Closures | |
type Rep WhatNext Source # | |
Defined in GHC.Exts.Heap.Closures type Rep WhatNext = D1 ('MetaData "WhatNext" "GHC.Exts.Heap.Closures" "ghc-heap-9.2.1" '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
TsoLocked | |
TsoBlockx | |
TsoInterruptible | |
TsoStoppedOnBreakpoint | |
TsoMarked | |
TsoSqueezed | |
TsoAllocLimit | |
TsoFlagsUnknownValue Word32 | Please report this as a bug |
Instances
Generic TsoFlags Source # | |
Show TsoFlags Source # | |
Eq TsoFlags Source # | |
Ord TsoFlags Source # | |
Defined in GHC.Exts.Heap.Closures | |
type Rep TsoFlags Source # | |
Defined in GHC.Exts.Heap.Closures type Rep TsoFlags = D1 ('MetaData "TsoFlags" "GHC.Exts.Heap.Closures" "ghc-heap-9.2.1" '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))))) |
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: 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.