Henning Thielemann wrote:

Now I have to write 'show' related code for each collection type. This way I probably duplicate a lot of code that is already written for the Show instances of the collections. To be honest, I use a more special tree structure with even more special "collections" so this may be not really a problem.

Here an instance for a custom list type:

newtype NewList a = NewList [a]


instance CollShow NewList where
   collShow shw (NewList xs) =
      "(NewList [" ++
         concat (intersperse ", " (map shw xs)) ++ "])"


Is there a more straightforward way, preferrably Haskell98?


This avoids duplicating code between Show/ShowColl .

> instance ShowColl coll => Show (CollTree coll) where
>    show (CollNode n) = "CollNode " ++ showColl n
>
> class ShowColl coll where
>    showColl :: coll (CollTree coll) -> String
>
> instance ShowColl [] where
>    showColl = show

Also, with GHC extensions and undecidable instances, the following incantation seems to work:

> {-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-}
> module CollTree where
> data CollTree coll = CollNode (coll (CollTree coll))
>
> instance Show (coll (CollTree coll)) => Show (CollTree coll) where
>    show (CollNode n) = "CollNode " ++ show n

*CollTree> show (CollNode [CollNode [],CollNode []])
"CollNode [CollNode [],CollNode []]"

However, I can not figure why the typechecker does not loop here (GHC 6.4.1).

Regards,
Roberto Zunino.


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to