[Haskell-cafe] Tree with collections

Henning Thielemann lemming at henning-thielemann.de
Sat Mar 11 08:04:47 EST 2006


I have a problem with defining an instance.

> module CollTree where

> import Data.List(intersperse)

Say, I want to define a tree structure based on lists.
I omit the data attached to the nodes here for simplicity.

> data ListTree = ListNode [ListTree]
>         deriving Show

This is simple enough for an automatically derived Show instance.

Now I want to generalise that structure from lists
to arbitrary types of collections.

> data CollTree coll = CollNode (coll (CollTree coll))

This got too complicated for automatic derivation.
So I have to define a Show instance for CollTree manually.
But how to formulate the instance context?
How to avoid undecidable instances?

   instance ??? => Show (CollTree coll) where
      show (CollNode xs) = "CollNode " ++ show xs


Currently I see only one solution using a new class providing a special 
'show' routine, which handles the structure of the collection, but must be 
assisted by a custom 'show' function for the collection members.

> class CollShow coll where
>    collShow :: (a -> String) -> (coll a -> String)

> instance CollShow coll => Show (CollTree coll) where
>    show (CollNode xs) = "CollNode " ++ collShow show xs

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?


More information about the Haskell-Cafe mailing list