Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data HeapGraph a = HeapGraph {
- roots :: !(NonEmpty ClosurePtr)
- graph :: !(IntMap (HeapGraphEntry a))
- data HeapGraphEntry a = HeapGraphEntry {}
- type HeapGraphIndex = ClosurePtr
- type PapHI = GenPapPayload (Maybe HeapGraphIndex)
- type StackHI = GenStackFrames (GenSrtPayload (Maybe HeapGraphIndex)) (Maybe HeapGraphIndex)
- type SrtHI = GenSrtPayload (Maybe HeapGraphIndex)
- type DerefFunction m a = ClosurePtr -> m (DebugClosureWithExtra a SrtPayload PapPayload ConstrDesc (GenStackFrames SrtPayload ClosurePtr) ClosurePtr)
- buildHeapGraph :: MonadFix m => DerefFunction m a -> Maybe Int -> ClosurePtr -> m (HeapGraph a)
- multiBuildHeapGraph :: MonadFix m => DerefFunction m a -> Maybe Int -> NonEmpty ClosurePtr -> m (HeapGraph a)
- generalBuildHeapGraph :: forall m a. MonadFix m => DerefFunction m a -> Maybe Int -> HeapGraph a -> NonEmpty ClosurePtr -> m (HeapGraph a)
- ppHeapGraph :: (a -> String) -> HeapGraph a -> String
- ppClosure :: (Int -> c -> String) -> Int -> DebugClosure (GenSrtPayload c) p ConstrDesc s c -> String
- lookupHeapGraph :: HeapGraphIndex -> HeapGraph a -> Maybe (HeapGraphEntry a)
- traverseHeapGraph :: Applicative m => (HeapGraphEntry a -> m (HeapGraphEntry b)) -> HeapGraph a -> m (HeapGraph b)
- updateHeapGraph :: (HeapGraphEntry a -> Maybe (HeapGraphEntry a)) -> HeapGraphIndex -> HeapGraph a -> HeapGraph a
- heapGraphSize :: HeapGraph a -> Int
- annotateHeapGraph :: (a -> a) -> HeapGraphIndex -> HeapGraph a -> HeapGraph a
- data ReverseGraph
- mkReverseGraph :: HeapGraph a -> ReverseGraph
- reverseEdges :: ClosurePtr -> ReverseGraph -> Maybe [ClosurePtr]
Types
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 | |
|
Instances
Foldable HeapGraph Source # | |
Defined in GHC.Debug.Types.Graph fold :: Monoid m => HeapGraph m -> m # foldMap :: Monoid m => (a -> m) -> HeapGraph a -> m # foldMap' :: Monoid m => (a -> m) -> HeapGraph a -> m # foldr :: (a -> b -> b) -> b -> HeapGraph a -> b # foldr' :: (a -> b -> b) -> b -> HeapGraph a -> b # foldl :: (b -> a -> b) -> b -> HeapGraph a -> b # foldl' :: (b -> a -> b) -> b -> HeapGraph a -> b # foldr1 :: (a -> a -> a) -> HeapGraph a -> a # foldl1 :: (a -> a -> a) -> HeapGraph a -> a # toList :: HeapGraph a -> [a] # length :: HeapGraph a -> Int # elem :: Eq a => a -> HeapGraph a -> Bool # maximum :: Ord a => HeapGraph a -> a # minimum :: Ord a => HeapGraph a -> a # | |
Traversable HeapGraph Source # | |
Functor HeapGraph Source # | |
Show a => Show (HeapGraph a) Source # | |
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 have a slot for arbitrary data, for the user's convenience.
Instances
type HeapGraphIndex = ClosurePtr Source #
type PapHI = GenPapPayload (Maybe HeapGraphIndex) Source #
type StackHI = GenStackFrames (GenSrtPayload (Maybe HeapGraphIndex)) (Maybe HeapGraphIndex) Source #
type SrtHI = GenSrtPayload (Maybe HeapGraphIndex) Source #
Building a heap graph
type DerefFunction m a = ClosurePtr -> m (DebugClosureWithExtra a SrtPayload PapPayload ConstrDesc (GenStackFrames SrtPayload ClosurePtr) ClosurePtr) Source #
:: MonadFix m | |
=> DerefFunction m a | |
-> Maybe Int | |
-> ClosurePtr | The value to start with |
-> m (HeapGraph a) |
Creates a HeapGraph
for the value in the box, but not recursing further
than the given limit.
:: MonadFix m | |
=> DerefFunction m a | |
-> Maybe Int | |
-> NonEmpty ClosurePtr | Starting values with associated data entry |
-> m (HeapGraph a) |
Creates a HeapGraph
for the values in multiple boxes, but not recursing
further than the given limit.
generalBuildHeapGraph :: forall m a. MonadFix m => DerefFunction m a -> Maybe Int -> HeapGraph a -> NonEmpty ClosurePtr -> m (HeapGraph a) Source #
Printing a heap graph
ppHeapGraph :: (a -> String) -> 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)
ppClosure :: (Int -> c -> String) -> Int -> DebugClosure (GenSrtPayload c) p ConstrDesc s c -> String Source #
Utility
lookupHeapGraph :: HeapGraphIndex -> HeapGraph a -> Maybe (HeapGraphEntry a) Source #
traverseHeapGraph :: Applicative m => (HeapGraphEntry a -> m (HeapGraphEntry b)) -> HeapGraph a -> m (HeapGraph b) Source #
updateHeapGraph :: (HeapGraphEntry a -> Maybe (HeapGraphEntry a)) -> HeapGraphIndex -> HeapGraph a -> HeapGraph a Source #
heapGraphSize :: HeapGraph a -> Int Source #
annotateHeapGraph :: (a -> a) -> HeapGraphIndex -> HeapGraph a -> HeapGraph a Source #
Reverse Graph
data ReverseGraph Source #
mkReverseGraph :: HeapGraph a -> ReverseGraph Source #
reverseEdges :: ClosurePtr -> ReverseGraph -> Maybe [ClosurePtr] Source #