
Is there any way that you can turn an arbitrary Haskell value into a string? I rephrase: There *is* a way to turn arbitrary values into strings. I know there is, because the GHCi debugger *does* it. The question is, does anybody know of an /easy/ way to do this? Basically, I'm writing a mutable container implementation. It can hold any type of data, but it would massively aid debugging if I could actually print out what's in it. On the other hand, I don't want to alter the entire program to have Show constraints everywhere just so I can print out some debug traces (and then alter everything back again afterwards once I'm done debugging). Anybody know of a way to do this? (As it happens, the values I'm testing with are all Showable anyway, but the type checker doesn't know that...)

On Fri, Oct 16, 2009 at 8:19 PM, Andrew Coppin
Is there any way that you can turn an arbitrary Haskell value into a string?
I rephrase: There *is* a way to turn arbitrary values into strings. I know there is, because the GHCi debugger *does* it. The question is, does anybody know of an /easy/ way to do this?
Ghci only displays values with a Show instance.

David Virebayre wrote:
On Fri, Oct 16, 2009 at 8:19 PM, Andrew Coppin
wrote: Is there any way that you can turn an arbitrary Haskell value into a string?
I rephrase: There *is* a way to turn arbitrary values into strings. I know there is, because the GHCi debugger *does* it. The question is, does anybody know of an /easy/ way to do this?
Ghci only displays values with a Show instance.
Well, I can live with getting an empty string if no Show instance is available. But I can't figure out how to even do that...

GHCi can't show you functions can it? Unless you have a Show instance
for functions loaded. I think the basic answer is no, not even with
crazy unsafe stuff, because without the typeclass constraint GHC
doesn't know to pass around the secret dictionary containing the
methods that tell it how to show your data.
On Fri, Oct 16, 2009 at 2:19 PM, Andrew Coppin
Is there any way that you can turn an arbitrary Haskell value into a string?
I rephrase: There *is* a way to turn arbitrary values into strings. I know there is, because the GHCi debugger *does* it. The question is, does anybody know of an /easy/ way to do this?
Basically, I'm writing a mutable container implementation. It can hold any type of data, but it would massively aid debugging if I could actually print out what's in it. On the other hand, I don't want to alter the entire program to have Show constraints everywhere just so I can print out some debug traces (and then alter everything back again afterwards once I'm done debugging).
Anybody know of a way to do this? (As it happens, the values I'm testing with are all Showable anyway, but the type checker doesn't know that...)
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Andrew Coppin wrote:
Is there any way that you can turn an arbitrary Haskell value into a string?
No, the only values of type a -> String are the constant functions and _|_.
I rephrase: There *is* a way to turn arbitrary values into strings. I know there is, because the GHCi debugger *does* it. The question is, does anybody know of an /easy/ way to do this?
No. GHCi does not always do this: Prelude Data.Ratio> let plus1 = (+1) Prelude Data.Ratio> plus1 <interactive>:1:0: No instance for (Show (a -> a)) arising from a use of `print' at <interactive>:1:0-4 Possible fix: add an instance declaration for (Show (a -> a)) In a stmt of a 'do' expression: print it Prelude Data.Ratio>
Basically, I'm writing a mutable container implementation. It can hold any type of data, but it would massively aid debugging if I could actually print out what's in it. On the other hand, I don't want to alter the entire program to have Show constraints everywhere just so I can print out some debug traces (and then alter everything back again afterwards once I'm done debugging).
This is not advisable, as you see.
Anybody know of a way to do this? (As it happens, the values I'm testing with are all Showable anyway, but the type checker doesn't know that...)
What is the problem with adding a function showMyContainer :: (Show a) => Container a -> String ? In this case you can show your container (for debugging purposes), but only if you have Showable elements in your container. Cheers, Jochem -- Jochem Berndsen | jochem@functor.nl | jochem@牛在田里.com

Jochem Berndsen wrote:
I rephrase: There *is* a way to turn arbitrary values into strings. I know there is, because the GHCi debugger *does* it. The question is, does anybody know of an /easy/ way to do this?
No. GHCi does not always do this:
Prelude Data.Ratio> let plus1 = (+1) Prelude Data.Ratio> plus1
<interactive>:1:0: No instance for (Show (a -> a)) arising from a use of `print' at <interactive>:1:0-4 Possible fix: add an instance declaration for (Show (a -> a)) In a stmt of a 'do' expression: print it Prelude Data.Ratio>
The GHCi *debugger* can print out even values for which no Show instance exists. (But yes, it fails to print anything interesting for function types... It works for ADTs that don't have Show though.)
Anybody know of a way to do this? (As it happens, the values I'm testing with are all Showable anyway, but the type checker doesn't know that...)
What is the problem with adding a function showMyContainer :: (Show a) => Container a -> String ? In this case you can show your container (for debugging purposes), but only if you have Showable elements in your container.
This could plausibly work...

My GHCi can't do that :o
I just wrote data A = B | C and loaded the file into GHCi. Typing B gives me:
<interactive>:1:0:
No instance for (Show A)
arising from a use of `print' at <interactive>:1:0
Possible fix: add an instance declaration for (Show A)
In a stmt of a 'do' expression: print it
The error also gives an idea of what GHCi is doing behind the scenes:
it's just calling print, which has a Show constraint.
On Fri, Oct 16, 2009 at 2:40 PM, Andrew Coppin
Jochem Berndsen wrote:
I rephrase: There *is* a way to turn arbitrary values into strings. I know there is, because the GHCi debugger *does* it. The question is, does anybody know of an /easy/ way to do this?
No. GHCi does not always do this:
Prelude Data.Ratio> let plus1 = (+1) Prelude Data.Ratio> plus1
<interactive>:1:0: No instance for (Show (a -> a)) arising from a use of `print' at <interactive>:1:0-4 Possible fix: add an instance declaration for (Show (a -> a)) In a stmt of a 'do' expression: print it Prelude Data.Ratio>
The GHCi *debugger* can print out even values for which no Show instance exists. (But yes, it fails to print anything interesting for function types... It works for ADTs that don't have Show though.)
Anybody know of a way to do this? (As it happens, the values I'm testing with are all Showable anyway, but the type checker doesn't know that...)
What is the problem with adding a function showMyContainer :: (Show a) => Container a -> String ? In this case you can show your container (for debugging purposes), but only if you have Showable elements in your container.
This could plausibly work...
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Andrew has mentioned the debugger several times, NOT the interactive REPL. That is, using :-commands to inspect values. -Ross On Oct 16, 2009, at 2:46 PM, Daniel Peebles wrote:
My GHCi can't do that :o
I just wrote data A = B | C and loaded the file into GHCi. Typing B gives me:
<interactive>:1:0: No instance for (Show A) arising from a use of `print' at <interactive>:1:0 Possible fix: add an instance declaration for (Show A) In a stmt of a 'do' expression: print it
The error also gives an idea of what GHCi is doing behind the scenes: it's just calling print, which has a Show constraint.
On Fri, Oct 16, 2009 at 2:40 PM, Andrew Coppin
wrote: Jochem Berndsen wrote:
I rephrase: There *is* a way to turn arbitrary values into strings. I know there is, because the GHCi debugger *does* it. The question is, does anybody know of an /easy/ way to do this?
No. GHCi does not always do this:
Prelude Data.Ratio> let plus1 = (+1) Prelude Data.Ratio> plus1
<interactive>:1:0: No instance for (Show (a -> a)) arising from a use of `print' at <interactive>:1:0-4 Possible fix: add an instance declaration for (Show (a -> a)) In a stmt of a 'do' expression: print it Prelude Data.Ratio>
The GHCi *debugger* can print out even values for which no Show instance exists. (But yes, it fails to print anything interesting for function types... It works for ADTs that don't have Show though.)
Anybody know of a way to do this? (As it happens, the values I'm testing with are all Showable anyway, but the type checker doesn't know that...)
What is the problem with adding a function showMyContainer :: (Show a) => Container a -> String ? In this case you can show your container (for debugging purposes), but only if you have Showable elements in your container.
This could plausibly work...
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Whoops, sorry about that then!
On Fri, Oct 16, 2009 at 2:59 PM, Ross Mellgren
Andrew has mentioned the debugger several times, NOT the interactive REPL. That is, using :-commands to inspect values.
-Ross
On Oct 16, 2009, at 2:46 PM, Daniel Peebles wrote:
My GHCi can't do that :o
I just wrote data A = B | C and loaded the file into GHCi. Typing B gives me:
<interactive>:1:0: No instance for (Show A) arising from a use of `print' at <interactive>:1:0 Possible fix: add an instance declaration for (Show A) In a stmt of a 'do' expression: print it
The error also gives an idea of what GHCi is doing behind the scenes: it's just calling print, which has a Show constraint.
On Fri, Oct 16, 2009 at 2:40 PM, Andrew Coppin
wrote: Jochem Berndsen wrote:
I rephrase: There *is* a way to turn arbitrary values into strings. I know there is, because the GHCi debugger *does* it. The question is, does anybody know of an /easy/ way to do this?
No. GHCi does not always do this:
Prelude Data.Ratio> let plus1 = (+1) Prelude Data.Ratio> plus1
<interactive>:1:0: No instance for (Show (a -> a)) arising from a use of `print' at <interactive>:1:0-4 Possible fix: add an instance declaration for (Show (a -> a)) In a stmt of a 'do' expression: print it Prelude Data.Ratio>
The GHCi *debugger* can print out even values for which no Show instance exists. (But yes, it fails to print anything interesting for function types... It works for ADTs that don't have Show though.)
Anybody know of a way to do this? (As it happens, the values I'm testing with are all Showable anyway, but the type checker doesn't know that...)
What is the problem with adding a function showMyContainer :: (Show a) => Container a -> String ? In this case you can show your container (for debugging purposes), but only if you have Showable elements in your container.
This could plausibly work...
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

No problem, just trying to make sure the conversation stays on track :-) -Ross On Oct 16, 2009, at 3:26 PM, Daniel Peebles wrote:
Whoops, sorry about that then!
On Fri, Oct 16, 2009 at 2:59 PM, Ross Mellgren
wrote: Andrew has mentioned the debugger several times, NOT the interactive REPL. That is, using :-commands to inspect values.
-Ross
On Oct 16, 2009, at 2:46 PM, Daniel Peebles wrote:
My GHCi can't do that :o
I just wrote data A = B | C and loaded the file into GHCi. Typing B gives me:
<interactive>:1:0: No instance for (Show A) arising from a use of `print' at <interactive>:1:0 Possible fix: add an instance declaration for (Show A) In a stmt of a 'do' expression: print it
The error also gives an idea of what GHCi is doing behind the scenes: it's just calling print, which has a Show constraint.
On Fri, Oct 16, 2009 at 2:40 PM, Andrew Coppin
wrote: Jochem Berndsen wrote:
I rephrase: There *is* a way to turn arbitrary values into strings. I know there is, because the GHCi debugger *does* it. The question is, does anybody know of an /easy/ way to do this?
No. GHCi does not always do this:
Prelude Data.Ratio> let plus1 = (+1) Prelude Data.Ratio> plus1
<interactive>:1:0: No instance for (Show (a -> a)) arising from a use of `print' at <interactive>:1:0-4 Possible fix: add an instance declaration for (Show (a -> a)) In a stmt of a 'do' expression: print it Prelude Data.Ratio>
The GHCi *debugger* can print out even values for which no Show instance exists. (But yes, it fails to print anything interesting for function types... It works for ADTs that don't have Show though.)
Anybody know of a way to do this? (As it happens, the values I'm testing with are all Showable anyway, but the type checker doesn't know that...)
What is the problem with adding a function showMyContainer :: (Show a) => Container a -> String ? In this case you can show your container (for debugging purposes), but only if you have Showable elements in your container.
This could plausibly work...
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Derek Elkins wrote:
See vacuum: http://hackage.haskell.org/package/vacuum
Could be useful... Thanks!

On 10/17/09, Andrew Coppin
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

Hello Andrew, Friday, October 16, 2009, 10:19:46 PM, you wrote:
actually print out what's in it. On the other hand, I don't want to alter the entire program to have Show constraints everywhere just so I can print out some debug traces (and then alter everything back again afterwards once I'm done debugging).
i personally just never use explicit function type declarations. this way constraints are added and removed automatically depending on functions you are using inside -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (8)
-
Andrew Coppin
-
Bulat Ziganshin
-
Daniel Peebles
-
David Virebayre
-
Derek Elkins
-
Jochem Berndsen
-
Matt Morrow
-
Ross Mellgren