vacuum-0.0.9: Extract graph representations of ghc heap values.Source codeContentsIndex
GHC.Vacuum
Description
 ghci> toAdjList $ vacuum (fix (0:))
 [(0,[1,0]),(1,[])]

 ghci> ppHs $ vacuum (fix (0:))
 fromList
   [(0,
     HNode{nodePtrs = [1, 0], nodeLits = [40425920],
           nodeInfo =
             ConInfo{itabPkg = "ghc-prim", itabMod = "GHC.Types", itabCon = ":",
                     itabPtrs = 2, itabLits = 0, itabType = CONSTR_2_0, itabSrtLen = 1,
                     itabCode =
                       [72, 131, 195, 2, 255, 101, 0, 144, 224, 30, 0, 0, 0, 0, 0, 0]}}),
    (1,
     HNode{nodePtrs = [], nodeLits = [0, 40425920],
           nodeInfo =
             ConInfo{itabPkg = "integer", itabMod = "GHC.Integer.Internals",
                     itabCon = "S#", itabPtrs = 0, itabLits = 1, itabType = CONSTR_0_1,
                     itabSrtLen = 0,
                     itabCode =
                       [72, 255, 195, 255, 101, 0, 102, 144, 152, 0, 0, 0, 0, 0, 0, 0]}})]

 ghci> ppDot . nameGraph $ vacuum (fix (0:))
 digraph g {
 graph [rankdir=LR, splines=true];
 node [label="\N", shape=none, fontcolor=blue, fontname=courier];
 edge [color=black, style=dotted, fontname=courier, arrowname=onormal];

     ":|0" -> {"S#|1",":|0"}
     "S#|1" -> {}
 }
Synopsis
type HNodeId = Int
data HNode = HNode {
nodePtrs :: [HNodeId]
nodeLits :: [Word]
nodeInfo :: InfoTab
}
emptyHNode :: ClosureType -> HNode
vacuum :: a -> IntMap HNode
dump :: a -> IO (IntMap HNode)
vacuumTo :: Int -> a -> IntMap HNode
dumpTo :: Int -> a -> IO (IntMap HNode)
toAdjList :: IntMap HNode -> [(Int, [Int])]
nameGraph :: IntMap HNode -> [(String, [String])]
data ShowHNode = ShowHNode {
showHNode :: Int -> HNode -> String
externHNode :: Int -> String
}
showHNodes :: ShowHNode -> IntMap HNode -> [(String, [String])]
ppHs :: Show a => a -> Doc
ppDot :: [(String, [String])] -> Doc
data Draw e v m a = Draw {
mkV :: Int -> a -> m v
mkE :: v -> v -> m e
succs :: a -> [Int]
}
newtype G e v = G {
unG :: IntMap (v, IntMap e)
}
draw :: Monad m => Draw e v m a -> IntMap a -> m (G e v)
printDraw :: Draw (Int, Int) Int IO HNode
split :: (a -> [Int]) -> IntMap a -> IntMap ([Int], [Int])
data Closure = Closure {
closPtrs :: [HValue]
closLits :: [Word]
closITab :: InfoTab
}
data InfoTab
= ConInfo {
itabPkg :: String
itabMod :: String
itabCon :: String
itabPtrs :: Word
itabLits :: Word
itabType :: ClosureType
itabSrtLen :: Word
itabCode :: [Word]
}
| OtherInfo {
itabPtrs :: Word
itabLits :: Word
itabType :: ClosureType
itabSrtLen :: Word
itabCode :: [Word]
}
getClosure :: a -> IO Closure
nodePkg :: HNode -> String
nodeMod :: HNode -> String
nodeName :: HNode -> String
itabName :: InfoTab -> (String, String, String)
getInfoPtr :: a -> Ptr StgInfoTable
Documentation
type HNodeId = IntSource
data HNode Source
Constructors
HNode
nodePtrs :: [HNodeId]
nodeLits :: [Word]
nodeInfo :: InfoTab
show/hide Instances
emptyHNode :: ClosureType -> HNodeSource
vacuum :: a -> IntMap HNodeSource
.
dump :: a -> IO (IntMap HNode)Source
vacuumTo :: Int -> a -> IntMap HNodeSource
Stop after a given depth.
dumpTo :: Int -> a -> IO (IntMap HNode)Source
toAdjList :: IntMap HNode -> [(Int, [Int])]Source
nameGraph :: IntMap HNode -> [(String, [String])]Source
data ShowHNode Source
Constructors
ShowHNode
showHNode :: Int -> HNode -> String
externHNode :: Int -> String
showHNodes :: ShowHNode -> IntMap HNode -> [(String, [String])]Source
ppHs :: Show a => a -> DocSource
ppDot :: [(String, [String])] -> DocSource
data Draw e v m a Source
To assist in "rendering" the graph to some source.
Constructors
Draw
mkV :: Int -> a -> m v
mkE :: v -> v -> m e
succs :: a -> [Int]
newtype G e v Source
Constructors
G
unG :: IntMap (v, IntMap e)
show/hide Instances
(Eq e, Eq v) => Eq (G e v)
(Ord e, Ord v) => Ord (G e v)
(Read e, Read v) => Read (G e v)
(Show e, Show v) => Show (G e v)
draw :: Monad m => Draw e v m a -> IntMap a -> m (G e v)Source
printDraw :: Draw (Int, Int) Int IO HNodeSource
An example Draw
split :: (a -> [Int]) -> IntMap a -> IntMap ([Int], [Int])Source
Build a map to (preds,succs)
data Closure Source
Constructors
Closure
closPtrs :: [HValue]
closLits :: [Word]
closITab :: InfoTab
show/hide Instances
data InfoTab Source
Constructors
ConInfo
itabPkg :: String
itabMod :: String
itabCon :: String
itabPtrs :: Word
itabLits :: Word
itabType :: ClosureType
itabSrtLen :: Word
itabCode :: [Word]
OtherInfo
itabPtrs :: Word
itabLits :: Word
itabType :: ClosureType
itabSrtLen :: Word
itabCode :: [Word]
show/hide Instances
getClosure :: a -> IO ClosureSource
This is in part borrowed from RtClosureInspect.getClosureData.
nodePkg :: HNode -> StringSource
nodeMod :: HNode -> StringSource
nodeName :: HNode -> StringSource
itabName :: InfoTab -> (String, String, String)Source
getInfoPtr :: a -> Ptr StgInfoTableSource
Produced by Haddock version 2.4.2