[Haskell-cafe] x -> String
Matt Morrow
moonpatio at gmail.com
Sun Oct 18 12:06:45 EDT 2009
On 10/17/09, Andrew Coppin <andrewcoppin at btinternet.com> wrote:
> Derek Elkins wrote:
>> See vacuum: http://hackage.haskell.org/package/vacuum
>>
> Could be useful... Thanks!
>
As Derek mentioned, vacuum would be perfect for this:
-----------------------------------------------------------------------------
import Data.Word
import GHC.Vacuum
import GHC.Vacuum.ClosureType
import qualified Data.IntMap as IM
type Info = (ClosureType -- what kind of heap node is this?
,[String] -- [pkg,mod,con] for constructors
,[Int] -- "pointers" refering to other nodes in IntMap
,[Word]) -- literal data in constructors
overview :: HNode -> Info
overview o =
let ptrs = nodePtrs o
lits = nodeLits o
itab = nodeInfo o
ctyp = itabType itab
-- only available
-- for constructors
(pkg,mod,con) = itabName itab
names = filter (not . null)
[pkg,mod,con]
in (ctyp
,names -- [] for non-data
,ptrs
,lits)
-- returns an adjacency-list graph
info :: a -> [(Int,Info)]
info = fmap (\(a,b)->(a,overview b))
. IM.toList . vacuum
-- returns an adjacency-list graph
infoLazy :: a -> [(Int,Info)]
infoLazy = fmap (\(a,b)->(a,overview b))
. IM.toList . vacuumLazy
-----------------------------------------------------------------------------
-- example usage
data A a = A Int | B a | forall b. C b [A a]
val0 = [A 42, B (Left Nothing), C (pi,()) val0]
val1 = fmap (\n -> C n []) [0..]
{-
ghci> mapM_ print (info val0)
Loading package vacuum-1.0.0 ... linking ... done.
(0,(CONSTR_2_0,["ghc-prim","GHC.Types",":"],[1,2],[]))
(1,(CONSTR,["main","Main","A"],[3],[]))
(2,(CONSTR_2_0,["ghc-prim","GHC.Types",":"],[4,5],[]))
(3,(CONSTR_0_1,["ghc-prim","GHC.Types","I#"],[],[42]))
(4,(CONSTR,["main","Main","B"],[6],[]))
(5,(CONSTR_2_0,["ghc-prim","GHC.Types",":"],[8,9],[]))
(6,(CONSTR_1_0,["base","Data.Either","Left"],[7],[]))
(7,(CONSTR_NOCAF_STATIC,["base","Data.Maybe","Nothing"],[],[]))
(8,(CONSTR,["main","Main","C"],[10,0],[]))
(9,(CONSTR_NOCAF_STATIC,["ghc-prim","GHC.Types","[]"],[],[]))
(10,(CONSTR_2_0,["ghc-prim","GHC.Tuple","(,)"],[11,12],[]))
(11,(CONSTR_NOCAF_STATIC,["ghc-prim","GHC.Types","D#"],[],[4614256656552045848]))
(12,(CONSTR_NOCAF_STATIC,["ghc-prim","GHC.Unit","()"],[],[]))
ghci> mapM_ print (infoLazy val1)
(0,(AP,[],[],[]))
ghci> val1 `seq` ()
()
ghci> mapM_ print (infoLazy val1)
(0,(CONSTR_2_0,["ghc-prim","GHC.Types",":"],[1,2],[]))
(1,(THUNK_2_0,[],[],[]))
(2,(THUNK_2_0,[],[],[]))
ghci> length . take 2 $ val1
2
ghci> mapM_ print (infoLazy val1)
(0,(CONSTR_2_0,["ghc-prim","GHC.Types",":"],[1,2],[]))
(1,(THUNK_2_0,[],[],[]))
(2,(CONSTR_2_0,["ghc-prim","GHC.Types",":"],[3,4],[]))
(3,(THUNK_2_0,[],[],[]))
(4,(THUNK_2_0,[],[],[]))
ghci> case val1 of a:b:_ -> a `seq` b `seq` ()
()
ghci> mapM_ print (infoLazy val1)
(0,(CONSTR_2_0,["ghc-prim","GHC.Types",":"],[1,2],[]))
(1,(CONSTR,["main","Main","C"],[3,4],[]))
(2,(CONSTR_2_0,["ghc-prim","GHC.Types",":"],[5,6],[]))
(3,(CONSTR_0_1,["integer","GHC.Integer.Internals","S#"],[],[0]))
(4,(CONSTR_NOCAF_STATIC,["ghc-prim","GHC.Types","[]"],[],[]))
(5,(CONSTR,["main","Main","C"],[7,4],[]))
(6,(THUNK_2_0,[],[],[]))
(7,(CONSTR_0_1,["integer","GHC.Integer.Internals","S#"],[],[1]))
-}
-----------------------------------------------------------------------------
Matt
More information about the Haskell-Cafe
mailing list