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" -> {}
 }
 ghci> let a = [0..]
 ghci> toAdjList $ vacuumLazy a
 [(0,[])]
 ghci> take 2 a
 [0,1]
 ghci> toAdjList $ vacuumLazy a
 [(0,[1,2]),(1,[]),(2,[3,4]),(3,[]),(4,[])]
 ghci> take 3 a
 [0,1,2]
 ghci> toAdjList $ vacuumLazy a
 [(0,[1,2]),(1,[]),(2,[3,4]),(3,[]),(4,[5,6]),(5,[]),(6,[])]
- type HNodeId = Int
- data HNode = HNode {}
- emptyHNode :: ClosureType -> HNode
- summary :: HNode -> ([String], [HNodeId], [Word])
- vacuum :: a -> IntMap HNode
- vacuumTo :: Int -> a -> IntMap HNode
- vacuumLazy :: a -> IntMap HNode
- vacuumStream :: a -> [(HNodeId, HNode)]
- vacuumDebug :: a -> IntMap [(StableName HValue, HNodeId)]
- dump :: a -> IO (IntMap HNode)
- dumpTo :: Int -> a -> IO (IntMap HNode)
- dumpLazy :: a -> IO (IntMap HNode)
- toAdjList :: IntMap HNode -> [(Int, [Int])]
- toAdjPair :: (HNodeId, HNode) -> (Int, [Int])
- nameGraph :: IntMap HNode -> [(String, [String])]
- data ShowHNode = ShowHNode {}
- showHNodes :: ShowHNode -> IntMap HNode -> [(String, [String])]
- ppDot :: [(String, [String])] -> Doc
- data Draw e v m a = Draw {}
- newtype G e v = G {}
- 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 {}
- data InfoTab
- getClosure :: a -> IO Closure
- closureType :: a -> IO ClosureType
- getInfoTab :: a -> IO InfoTab
- getInfoPtr :: a -> Ptr StgInfoTable
- peekInfoTab :: Ptr StgInfoTable -> IO InfoTab
- nodePkg :: HNode -> String
- nodeMod :: HNode -> String
- nodeName :: HNode -> String
- itabName :: InfoTab -> (String, String, String)
- type HValue = Any
Documentation
emptyHNode :: ClosureType -> HNodeSource
vacuumLazy :: a -> IntMap HNodeSource
Doesn't force anything.
vacuumStream :: a -> [(HNodeId, HNode)]Source
Returns nodes as it encounters them.
vacuumDebug :: a -> IntMap [(StableName HValue, HNodeId)]Source
To assist in "rendering" the graph to some source.
getClosure :: a -> IO ClosureSource
This is in part borrowed from RtClosureInspect.getClosureData.
closureType :: a -> IO ClosureTypeSource
getInfoTab :: a -> IO InfoTabSource
getInfoPtr :: a -> Ptr StgInfoTableSource