
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?

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.

On Sat, 11 Mar 2006, Roberto Zunino wrote:
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
Yes, this solves the problem. Thanks a lot!
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).
I tried similar things with GHC 6.2 and Hugs and they looped.
participants (2)
-
Henning Thielemann
-
Roberto Zunino