StrategyLib - need help

Ralf Laemmel Ralf.Laemmel@cwi.nl
Thu, 24 Jul 2003 20:27:21 +0200


Very good point!
adhoc and friends support TYPE case.
What's needed here is a so-far unsupported type-CLASS case
which is actually at least non-trivial.
I can only offer semi-solutions:

a) Add a class constraint for Show to the Term class.
   (Would that work? It's a bit invasive anyway.)

b) Alternatively, imoort TermRep and use explode and then show on TermRep.
   (This show maybe does not look so nice,
    but this should be good enough for debugging.)

c) Be more specific about what terms to print,
   say have type-specific cases for types of terms of interest.
   (This would be reasonable if you only care about a few types,
    or there are even just a few types anyway.)

On the long term:
the "boilerplate" approach as supported in > GHC 6.0 will
help with this. (In fact, the GHC 6.0 release comes with a
simple gshow defined on Data.) StrategyLib will soon be
reconstructed on top of "scrap your boilerplate" (say, Data.Generics).
The issue of type-class case is identified, but I don't know if we will
succeed with this very soon.

Hope this helps.
Ralf



Dmitry Astapov wrote:
> 
> I want to write generic traversal which prints everything on the way:
> 
> uglyPrint :: (Term t, Show t) => t -> [(String)]
> uglyPrint = (map snd) . runIdentity . applyTU (full_tdTU uglyPrintStep)
> uglyPrintStep :: (Show t, Term t) => TU [(t, String)] Identity
> uglyPrintStep = constTU [] `adhocTU` (return . uglyPrintAny)
> uglyPrintAny x = [(x,show x)]
> ugliestPrintEver :: (Term t, Show t) => t -> IO ()
> ugliestPrintEver x = do { putStrLn $ show x }
> 
> Compiler (GHC 6.0) gives me:
>     Ambiguous type variable `t' in these top-level constraints:
>       `Term t'
>         arising from use of `uglyPrintStep' at ...
>       `Show t'
>         arising from use of `uglyPrintStep' at ...
> 
> All data types which are instances of Term are instances of Show as well -
> I know it. Question is - how to persuade GHC?
> 
> I there any want to use typeclass restrictions with traversal, or there is
> no luck for me?
> 
> --
> Dmitry Astapov //ADEpt
> GPG KeyID/fprint: F5D7639D/CA36 E6C4 815D 434D 0498  2B08 7867 4860 F5D7 639D
> _______________________________________________
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell

-- 
Ralf Laemmel
VU & CWI, Amsterdam, The Netherlands
http://www.cs.vu.nl/~ralf/
http://www.cwi.nl/~ralf/