Copyright | (c) 2012-2019 Joachim Breitner |
---|---|
License | BSD3 |
Maintainer | Joachim Breitner <mail@joachim-breitner.de> |
Safe Haskell | None |
Language | Haskell2010 |
With this module, you can investigate the heap representation of Haskell values, i.e. to investigate sharing and lazy evaluation.
Synopsis
- 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]
- | MVarClosure {
- info :: !StgInfoTable
- queueHead :: !b
- queueTail :: !b
- value :: !b
- | MutVarClosure {
- info :: !StgInfoTable
- var :: !b
- | BlockingQueueClosure { }
- | IntClosure { }
- | WordClosure { }
- | Int64Closure { }
- | Word64Closure { }
- | AddrClosure { }
- | FloatClosure { }
- | DoubleClosure { }
- | OtherClosure {
- info :: !StgInfoTable
- hvalues :: ![b]
- rawWords :: ![Word]
- | UnsupportedClosure {
- info :: !StgInfoTable
- type Closure = GenClosure Box
- allClosures :: GenClosure b -> [b]
- 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 StgInfoTable = StgInfoTable {}
- type HalfWord = Word32
- getClosureData :: HasHeapRep a => a -> IO Closure
- getBoxedClosureData :: Box -> IO Closure
- getClosureRaw :: a -> IO (Ptr StgInfoTable, [Word], [Box])
- ppClosure :: (Int -> b -> String) -> Int -> GenClosure b -> String
- data HeapTree
- buildHeapTree :: Int -> Box -> IO HeapTree
- ppHeapTree :: HeapTree -> String
- data HeapGraphEntry a = HeapGraphEntry {
- hgeBox :: Box
- hgeClosure :: GenClosure (Maybe HeapGraphIndex)
- hgeLive :: Bool
- hgeData :: a
- type HeapGraphIndex = Int
- newtype HeapGraph a = HeapGraph (IntMap (HeapGraphEntry a))
- lookupHeapGraph :: HeapGraphIndex -> HeapGraph a -> Maybe (HeapGraphEntry a)
- heapGraphRoot :: HeapGraphIndex
- buildHeapGraph :: Monoid a => Int -> a -> Box -> IO (HeapGraph a)
- multiBuildHeapGraph :: Monoid a => Int -> [(a, Box)] -> IO (HeapGraph a, [(a, HeapGraphIndex)])
- addHeapGraph :: Monoid a => Int -> a -> Box -> HeapGraph a -> IO (HeapGraphIndex, HeapGraph a)
- annotateHeapGraph :: Monoid a => a -> HeapGraphIndex -> HeapGraph a -> HeapGraph a
- updateHeapGraph :: Monoid a => Int -> HeapGraph a -> IO (HeapGraph a, HeapGraphIndex -> HeapGraphIndex)
- ppHeapGraph :: HeapGraph a -> String
- data Box = Box (Any :: Type)
- asBox :: a -> Box
- areBoxesEqual :: Box -> Box -> IO Bool
- disassembleBCO :: (a -> Maybe (GenClosure b)) -> GenClosure a -> Maybe [BCI b]
Heap data types
data GenClosure b #
This is the representation of a Haskell value on the heap. It reflects http://hackage.haskell.org/trac/ghc/browser/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://ghc.haskell.org/trac/ghc/wiki/Commentary/Rts/Storage/HeapObjects 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 |
| |
MVarClosure | An |
| |
MutVarClosure | A |
| |
BlockingQueueClosure | An STM blocking queue. |
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
type Closure = GenClosure Box #
allClosures :: GenClosure b -> [b] #
For generic code, this function returns all referenced closures.
data ClosureType #
Instances
data StgInfoTable #
This is a somewhat faithful representation of an info table. See http://hackage.haskell.org/trac/ghc/browser/includes/rts/storage/InfoTables.h for more details on this data structure.
Instances
Show StgInfoTable | |
Defined in GHC.Exts.Heap.InfoTable.Types showsPrec :: Int -> StgInfoTable -> ShowS # show :: StgInfoTable -> String # showList :: [StgInfoTable] -> ShowS # | |
Storable StgInfoTable Source # | |
Defined in GHC.HeapView sizeOf :: StgInfoTable -> Int # alignment :: StgInfoTable -> Int # peekElemOff :: Ptr StgInfoTable -> Int -> IO StgInfoTable # pokeElemOff :: Ptr StgInfoTable -> Int -> StgInfoTable -> IO () # peekByteOff :: Ptr b -> Int -> IO StgInfoTable # pokeByteOff :: Ptr b -> Int -> StgInfoTable -> IO () # peek :: Ptr StgInfoTable -> IO StgInfoTable # poke :: Ptr StgInfoTable -> StgInfoTable -> IO () # |
Reading from the heap
getClosureData :: HasHeapRep a => a -> IO Closure #
getBoxedClosureData :: Box -> IO Closure #
Like getClosureData
, but taking a Box
, so it is easier to work with.
getClosureRaw :: a -> IO (Ptr StgInfoTable, [Word], [Box]) Source #
This returns the raw representation of the given argument. The second
component of the triple are the words on the heap, and the third component
are those words that are actually pointers. Once back in Haskell word, the
Word
may be outdated after a garbage collector run, but the corresponding
Box
will still point to the correct value.
Pretty printing
Heap maps
For more global views of the heap, you can use heap maps. These come in variations, either a trees or as graphs, depending on whether you want to detect cycles and sharing or not.
The entries of a HeapGraph
can be annotated with arbitrary values. Most
operations expect this to be in the Monoid
class: They use mempty
to
annotate closures added because the passed values reference them, and they
use mappend
to combine the annotations when two values conincide, e.g.
during updateHeapGraph
.
Heap maps as tree, i.e. no sharing, no cycles.
buildHeapTree :: Int -> Box -> IO HeapTree Source #
Constructing an HeapTree
from a boxed value. It takes a depth parameter
that prevents it from running ad infinitum for cyclic or infinite
structures.
ppHeapTree :: HeapTree -> String Source #
Pretty-Printing a heap Tree
Example output for [Just 4, Nothing, *something*]
, where *something* is an
unevaluated expression depending on the command line argument.
[Just (I# 4),Nothing,Just (_thunk ["arg1","arg2"])]
data HeapGraphEntry a Source #
For heap graphs, i.e. data structures that also represent sharing and
cyclic structures, these are the entries. If the referenced value is
Nothing
, then we do not have that value in the map, most likely due to
exceeding the recursion bound passed to buildHeapGraph
.
Besides a pointer to the stored value and the closure representation we also keep track of whether the value was still alive at the last update of the heap graph. In addition we have a slot for arbitrary data, for the user's convenience.
HeapGraphEntry | |
|
Instances
Functor HeapGraphEntry Source # | |
Defined in GHC.HeapView fmap :: (a -> b) -> HeapGraphEntry a -> HeapGraphEntry b # (<$) :: a -> HeapGraphEntry b -> HeapGraphEntry a # | |
Show a => Show (HeapGraphEntry a) Source # | |
Defined in GHC.HeapView showsPrec :: Int -> HeapGraphEntry a -> ShowS # show :: HeapGraphEntry a -> String # showList :: [HeapGraphEntry a] -> ShowS # |
type HeapGraphIndex = Int Source #
The whole graph. The suggested interface is to only use lookupHeapGraph
,
as the internal representation may change. Nevertheless, we export it here:
Sometimes the user knows better what he needs than we do.
HeapGraph (IntMap (HeapGraphEntry a)) |
lookupHeapGraph :: HeapGraphIndex -> HeapGraph a -> Maybe (HeapGraphEntry a) Source #
:: Monoid a | |
=> Int | Search limit |
-> a | Data value for the root |
-> Box | The value to start with |
-> IO (HeapGraph a) |
Creates a HeapGraph
for the value in the box, but not recursing further
than the given limit. The initial value has index heapGraphRoot
.
annotateHeapGraph :: Monoid a => a -> HeapGraphIndex -> HeapGraph a -> HeapGraph a Source #
updateHeapGraph :: Monoid a => Int -> HeapGraph a -> IO (HeapGraph a, HeapGraphIndex -> HeapGraphIndex) Source #
This function updates a heap graph to reflect the current state of closures on the heap, conforming to the following specification.
- Every entry whose value has been garbage collected by now is marked as
dead by setting
hgeLive
toFalse
- Every entry whose value is still live gets the
hgeClosure
field updated and newly referenced closures are, up to the given depth, added to the graph. - A map mapping previous indicies to the corresponding new indicies is returned as well.
- The closure at
heapGraphRoot
stays atheapGraphRoot
ppHeapGraph :: HeapGraph a -> String Source #
Pretty-prints a HeapGraph. The resulting string contains newlines. Example
for let s = "Ki" in (s, s, cycle "Ho")
:
let x1 = "Ki" x6 = C# 'H' : C# 'o' : x6 in (x1,x1,x6)
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
areBoxesEqual :: Box -> Box -> IO Bool #
Boxes can be compared, but this is not pure, as different heap objects can, after garbage collection, become the same object.
Disassembler
disassembleBCO :: (a -> Maybe (GenClosure b)) -> GenClosure a -> Maybe [BCI b] Source #
This function integrates the disassembler in GHC.Disassembler. The first argument should a function that dereferences the pointer in the closure to a closure.
If any of these return Nothing
, then disassembleBCO
returns Nothing