
Hi all, During my work on buddha (haskell debugger) I've had the need to print arbitrary values from a running program. Along the way I've written some code that works with GHC to do this. Just in case there are others who might benefit from this, I've ripped some code out of buddha and made it into somewhat of a library. You can download it from here: http://www.cs.mu.oz.au/~bjpop/code.html The main parts are: reify :: a -> IO Graph data Graph = ... prettyGraph :: Graph -> String The graph type is an ordinary data type: type Unique = Int -- a unique label for each node type Tag = Int -- what kind of node it is type NumKids = Int -- how many children it has data Graph = AppNode Unique String Tag NumKids [Graph] | CharNode Char | IntNode Int | IntegerNode Integer | FloatNode Float | DoubleNode Double | NullNode deriving Show The main features are: - it is conservative wrt to evaluation (lazy). It does not make its argument evaluate any further, - it detects cycles in the heap representation and makes them visible in the Graph representation (though the current pretty printer does not take advantage of this), - it knows about some "special" things like exceptions and some other oddities, - it ought to work on GHC 5 and 6, though I haven't tested it extensively on the latter Functions are a sore point (they all get mapped to the one thing, sigh). It makes use of the FFI and the nice API that GHC provides for the RTS (is that enough TLAs in one sentence?) Unfortunately to use the library you must compile with -prof. The reason is to trick GHC into keeping names of data constructors on the heap. I'd rather avoid this, and perhaps with the new HsDebug stuff in GHC there is a better way to get such names, but I haven't looked too hard. (Any ideas?) An example is below. Ooroo, Bernie. -------------------------------------------------------------------------------- Here's an example: {- demonstrating the use of ReifyHs.reify -} module Main where import ReifyHs (reify) import PrettyGraph (prettyGraph) import Data.Char (toUpper) main :: IO () main = do putStrLn $ "GHC version: " ++ show __GLASGOW_HASKELL__ let listTups = zip "abcdefghij" [1..] putStr "\n\nForce the list to be evaluated a bit:\n\n" print $ take 3 listTups graph <- reify listTups putStr "\n\nhere's the graph representation: \n\n" print graph putStr "\n\nhere's a pretty print of the above: \n\n" putStrLn $ prettyGraph graph putStr "\n\nForce the list to be evaluated a bit more:\n\n" print $ take 5 listTups graph <- reify listTups putStr "\n\nthe graph pretty printed again: \n\n" putStrLn $ prettyGraph graph -------------------------------------------------------------------------------- Running the example after "make" bjpop@bjpop2:/tmp/reify$ ./test GHC version: 504 Force the list to be evaluated a bit: [('a',1),('b',2),('c',3)] here's the graph representation: AppNode 1076636796 ":" 1 2 [AppNode 1076636776 "(,)" 1 2 [CharNode 'a', IntNode 1],AppNode 1076637368 ":" 1 2 [AppNode 1076637348 "(,)" 1 2 [CharNode 'b',IntNode 2],AppNode 1076637932 ":" 1 2 [AppNode 1076637912 "(,)" 1 2 [CharNode 'c',IntNode 3],AppNode (-1) "" 3 0 []]]] here's a pretty print of the above: [('a',1),('b',2),('c',3) .. ? Force the list to be evaluated a bit more: [('a',1),('b',2),('c',3),('d',4),('e',5)] the graph pretty printed again: [('a',1),('b',2),('c',3),('d',4),('e',5) .. ?
participants (1)
-
Bernard James POPE