| Maintainer | Joachim Breitner <mail@joachim-breitner.de> | 
|---|---|
| Safe Haskell | None | 
GHC.HeapView
Description
With this module, you can investigate the heap representation of Haskell values, i.e. to investigate sharing and lazy evaluation.
- data  GenClosure b- = ConsClosure { }
- | ThunkClosure { - info :: StgInfoTable
- ptrArgs :: [b]
- dataArgs :: [Word]
 
- | SelectorClosure { - info :: StgInfoTable
- selectee :: b
 
- | IndClosure { - info :: StgInfoTable
- indirectee :: b
 
- | BlackholeClosure { - info :: StgInfoTable
- indirectee :: b
 
- | APClosure { }
- | PAPClosure { }
- | APStackClosure { - info :: StgInfoTable
- fun :: b
- payload :: [b]
 
- | BCOClosure { }
- | ArrWordsClosure { }
- | MutArrClosure { - info :: StgInfoTable
- mccPtrs :: Word
- mccSize :: Word
- mccPayload :: [b]
 
- | MutVarClosure { - info :: StgInfoTable
- var :: b
 
- | MVarClosure { - info :: StgInfoTable
- queueHead :: b
- queueTail :: b
- value :: b
 
- | FunClosure { - info :: StgInfoTable
- ptrArgs :: [b]
- dataArgs :: [Word]
 
- | BlockingQueueClosure { }
- | OtherClosure { - info :: StgInfoTable
- hvalues :: [b]
- rawWords :: [Word]
 
- | UnsupportedClosure { - info :: StgInfoTable
 
 
- type Closure = GenClosure Box
- allPtrs :: GenClosure b -> [b]
- data  ClosureType - = INVALID_OBJECT
- | CONSTR
- | CONSTR_1_0
- | CONSTR_0_1
- | CONSTR_2_0
- | CONSTR_1_1
- | CONSTR_0_2
- | CONSTR_STATIC
- | CONSTR_NOCAF_STATIC
- | 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_PERM
- | IND_STATIC
- | RET_BCO
- | RET_SMALL
- | RET_BIG
- | RET_DYN
- | RET_FUN
- | UPDATE_FRAME
- | CATCH_FRAME
- | UNDERFLOW_FRAME
- | STOP_FRAME
- | BLOCKING_QUEUE
- | BLACKHOLE
- | MVAR_CLEAN
- | MVAR_DIRTY
- | ARR_WORDS
- | MUT_ARR_PTRS_CLEAN
- | MUT_ARR_PTRS_DIRTY
- | MUT_ARR_PTRS_FROZEN0
- | MUT_ARR_PTRS_FROZEN
- | MUT_VAR_CLEAN
- | MUT_VAR_DIRTY
- | WEAK
- | PRIM
- | MUT_PRIM
- | TSO
- | STACK
- | TREC_CHUNK
- | ATOMICALLY_FRAME
- | CATCH_RETRY_FRAME
- | CATCH_STM_FRAME
- | WHITEHOLE
 
- data StgInfoTable = StgInfoTable {}
- type HalfWord = Word16
- getClosureData :: 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 = HeapGraphEntry WeakBox (GenClosure (Maybe HeapGraphIndex))
- type HeapGraphIndex = Int
- newtype HeapGraph = HeapGraph (IntMap HeapGraphEntry)
- lookupHeapGraph :: HeapGraphIndex -> HeapGraph -> Maybe HeapGraphEntry
- heapGraphRoot :: HeapGraphIndex
- buildHeapGraph :: Int -> Box -> IO HeapGraph
- ppHeapGraph :: HeapGraph -> String
- data Box = Box Any
- asBox :: a -> Box
- data WeakBox
- weakBox :: Box -> IO WeakBox
- isAlive :: WeakBox -> IO Bool
- derefWeakBox :: WeakBox -> IO (Maybe Box)
- type WeakClosure = GenClosure WeakBox
- weakenClosure :: Closure -> IO WeakClosure
Heap data types
data GenClosure b Source
This is the main data type of this module, representing a Haskell value on the heap. This 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, which
  should be either Box or WeakBox, with appropriate type synonyms Closure
  and WeakClosure.
Constructors
| ConsClosure | |
| ThunkClosure | |
| Fields 
 | |
| SelectorClosure | |
| Fields 
 | |
| IndClosure | |
| Fields 
 | |
| BlackholeClosure | |
| Fields 
 | |
| APClosure | |
| PAPClosure | |
| APStackClosure | |
| Fields 
 | |
| BCOClosure | |
| ArrWordsClosure | |
| MutArrClosure | |
| Fields 
 | |
| MutVarClosure | |
| Fields 
 | |
| MVarClosure | |
| Fields 
 | |
| FunClosure | |
| Fields 
 | |
| BlockingQueueClosure | |
| OtherClosure | |
| Fields 
 | |
| UnsupportedClosure | |
| Fields 
 | |
Instances
type Closure = GenClosure BoxSource
allPtrs :: GenClosure b -> [b]Source
For generic code, this function returns all referenced closures.
data ClosureType Source
A closure type enumeration, in order matching the actual value on the heap. Needs to be synchronized with http://hackage.haskell.org/trac/ghc/browser/includes/rts/storage/ClosureTypes.h
Constructors
Instances
data StgInfoTable Source
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. Note that the Storable instance
   provided here does _not_ support writing.
Constructors
| StgInfoTable | |
Instances
Reading from the heap
getClosureData :: a -> IO ClosureSource
This function returns parsed heap representation of the argument _at this
 moment_, even if it is unevaluated or an indirection or other exotic stuff.
 Beware when passing something to this function, the same caveats as for
 asBox apply.
getBoxedClosureData :: Box -> IO ClosureSource
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.
Heap maps as tree, i.e. no sharing, no cycles.
Constructors
| HeapTree WeakBox (GenClosure HeapTree) | |
| EndOfHeapTree | 
buildHeapTree :: Int -> Box -> IO HeapTreeSource
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 -> StringSource
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 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.
Constructors
| HeapGraphEntry WeakBox (GenClosure (Maybe HeapGraphIndex)) | 
Instances
type HeapGraphIndex = IntSource
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.
Constructors
| HeapGraph (IntMap HeapGraphEntry) | 
buildHeapGraph :: Int -> Box -> IO HeapGraphSource
Creates a HeapGraph for the value in the box, but not recursing further
 than the given limit. The initial value has index heapGraphRoot.
ppHeapGraph :: HeapGraph -> StringSource
Boxes
An arbitrarily 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 evalue 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
Weak boxes
An a variant of Box that does not keep the value alive.
type WeakClosure = GenClosure WeakBoxSource