announce: StableTable Printer for GHC

Bernard James POPE bjpop@cs.mu.OZ.AU
Wed, 1 May 2002 18:20:09 +1000 (EST)


Hi all,

Ever had that deep desire to see what was in that pesky
Stable Pointer/Name table?

Probably not, but I did, and I wrote some code to
print it out in all its glory from the safe confines
of a Haskell program. I thought I'd share it with you
just in case one day you too want to see what is lurking in
there.

You can find the code here:

   http://www.cs.mu.oz.au/~bjpop/code.html 

Here's an example of what it can do:

-----------------------------------------------------

>  module Main where
>
>  import Stable
>  foreign import ccall "printStableTable" printStableTable :: IO ()
>
>  main = do let list = [1,2,3,4] ++ list
>            print $ take 5 list
>            trueSName <- makeStableName True
>            listSPtr1   <- newStablePtr list
>            listSPtr2   <- newStablePtr list
>            printStableTable

If you run this program, you get as output:

   [1,2,3,4,1]
   --- Begin Stable Table ---
   
   stable_ptr_free = 3
   
   0.val    = NULL
   0.ref    = 0
   0.sn_obj = NULL
   
   1.val    = (addr = 0x80963e0) True
   1.ref    = 0
   1.sn_obj = <STABLE_NAME>
   
   2.val    = (addr = 0x500c11c4) (: 1 (: 2 (: 3 (: 4 cycle))))
   2.ref    = 2
   2.sn_obj = NULL
   
   3.val    = free at pos 4
   3.ref    = 0
   3.sn_obj = NULL
   
   4.val    = free at pos 5
   4.ref    = 0
   4.sn_obj = NULL
   
   ... blah blah blah, until the end of the table ...

-----------------------------------------------------

Some features:

   It shows each entry in the table, and implicitly the
   free list, starting at stable_ptr_free.

   Data structures are printed in all their glory, 
   including the current address of the value and
   the representation of the value. 

   Cycles are detected! (See 2.val), but other types
   of sharing are not yet shown, however it is possible
   with tweaks.

Why might you want this?

1. Debugging the stable pointer table implementation.

2. Debugging your own code.
   Stable pointers introduce the potential for nasty
   space leaks in Haskell programs. Much like malloc/free
   in C. If you forget to free your pointers then the 
   space is retained. If you suspect that your program
   is leaking space in this way, then just whip out the
   table printer and see what is looks like.

3. Checking how much sharing you have in your data (with
   tweaks, as I said ealier you can show sharing).

What do you need to use it?

   Just a current version of GHC. It should compile out of
   the box without any modification to GHC.

   Oh, and you have to compile your program with -prof to
   see all the data constructors.

How does it print the data structures with cycles?

   The library also comes with yet another library for
   prinitng arbitrary Haskell Data structures, done
   via the FFI interface.

   NOTE: this is different from the GHCinternals library.

   We can detect cycles more easily if we are just 
   printing things and not building new values on the heap
   at the same time. Probably this extra library should live
   somewhere by itself, but I have just bundled them together
   at the moment.

Cheers,
Bernie.