| Copyright | (c) 2012 Joachim Breitner | 
|---|---|
| License | BSD3 | 
| Maintainer | Joachim Breitner <mail@joachim-breitner.de> | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
GHC.Exts.Heap
Description
With this module, you can investigate the heap representation of Haskell values, i.e. to investigate sharing and lazy evaluation.
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 ClosureType- = INVALID_OBJECT
- | CONSTR
- | CONSTR_1_0
- | CONSTR_0_1
- | CONSTR_2_0
- | CONSTR_1_1
- | CONSTR_0_2
- | CONSTR_NOCAF
- | FUN
- | FUN_1_0
- | FUN_0_1
- | FUN_2_0
- | FUN_1_1
- | FUN_0_2
- | FUN_STATIC
- | THUNK
- | THUNK_1_0
- | THUNK_0_1
- | THUNK_2_0
- | THUNK_1_1
- | THUNK_0_2
- | THUNK_STATIC
- | THUNK_SELECTOR
- | BCO
- | AP
- | PAP
- | AP_STACK
- | IND
- | IND_STATIC
- | RET_BCO
- | RET_SMALL
- | RET_BIG
- | RET_FUN
- | UPDATE_FRAME
- | CATCH_FRAME
- | UNDERFLOW_FRAME
- | STOP_FRAME
- | BLOCKING_QUEUE
- | BLACKHOLE
- | MVAR_CLEAN
- | MVAR_DIRTY
- | TVAR
- | ARR_WORDS
- | MUT_ARR_PTRS_CLEAN
- | MUT_ARR_PTRS_DIRTY
- | MUT_ARR_PTRS_FROZEN_DIRTY
- | MUT_ARR_PTRS_FROZEN_CLEAN
- | MUT_VAR_CLEAN
- | MUT_VAR_DIRTY
- | WEAK
- | PRIM
- | MUT_PRIM
- | TSO
- | STACK
- | TREC_CHUNK
- | ATOMICALLY_FRAME
- | CATCH_RETRY_FRAME
- | CATCH_STM_FRAME
- | WHITEHOLE
- | SMALL_MUT_ARR_PTRS_CLEAN
- | SMALL_MUT_ARR_PTRS_DIRTY
- | SMALL_MUT_ARR_PTRS_FROZEN_DIRTY
- | SMALL_MUT_ARR_PTRS_FROZEN_CLEAN
- | COMPACT_NFDATA
- | N_CLOSURE_TYPES
 
- data PrimType
- class HasHeapRep (a :: TYPE rep) where- getClosureData :: a -> IO Closure
 
- data StgInfoTable = StgInfoTable {}
- type EntryFunPtr = FunPtr (Ptr () -> IO (Ptr ()))
- type HalfWord = Word32
- type ItblCodes = Either [Word8] [Word32]
- itblSize :: Int
- peekItbl :: Ptr StgInfoTable -> IO StgInfoTable
- pokeItbl :: Ptr StgInfoTable -> StgInfoTable -> IO ()
- getBoxedClosureData :: Box -> IO Closure
- allClosures :: GenClosure b -> [b]
- data Box = Box Any
- asBox :: a -> Box
- areBoxesEqual :: Box -> Box -> IO Bool
Closure types
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.
Constructors
| ConstrClosure | A data constructor | 
| 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  | 
| MutArrClosure | A  | 
| Fields 
 | |
| SmallMutArrClosure | A  Since: 8.10.1 | 
| Fields 
 | |
| MVarClosure | An  | 
| Fields 
 | |
| MutVarClosure | A  | 
| Fields 
 | |
| BlockingQueueClosure | An STM blocking queue. | 
| WeakClosure | |
| Fields 
 | |
| 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 | 
| Fields 
 | |
| UnsupportedClosure | |
| Fields 
 | |
Instances
data ClosureType Source #
Constructors
Instances
Instances
| Eq PrimType Source # | |
| Show PrimType Source # | |
| Generic PrimType Source # | |
| Binary PrimType Source # | |
| type Rep PrimType Source # | |
| Defined in GHC.Exts.Heap.Closures type Rep PrimType = D1 (MetaData "PrimType" "GHC.Exts.Heap.Closures" "ghc-lib-parser-0.20190806-7XKS8xDb4onMFDG7Z5wgP" 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)))) | |
class HasHeapRep (a :: TYPE rep) where Source #
Methods
getClosureData :: a -> IO Closure Source #
Instances
Info Table types
data StgInfoTable Source #
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.
Constructors
| StgInfoTable | |
Instances
peekItbl :: Ptr StgInfoTable -> IO StgInfoTable Source #
Read an InfoTable from the heap into a haskell type. WARNING: This code assumes it is passed a pointer to a "standard" info table. If tables_next_to_code is enabled, it will look 1 byte before the start for the entry field.
pokeItbl :: Ptr StgInfoTable -> StgInfoTable -> IO () Source #
Closure inspection
getBoxedClosureData :: Box -> IO Closure Source #
Like getClosureData, but taking a Box, so it is easier to work with.
allClosures :: GenClosure b -> [b] Source #
For generic code, this function returns all referenced closures.
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.
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