[Haskell-cafe] Showable mutually recursive (fixed-point) datatypes

Remi Turk rturk at science.uva.nl
Wed Feb 16 18:49:17 EST 2005


[WARNING: braindamag(ed|ing) experience following]

Hi all,

a few days ago I decided I desperately needed a set which could
contain (among others) itself. My first idea was

> module Main where

> import List
> import Monad

> data Elem s a = V a | R (s (Elem s a))

Now, a self-containing list can be defined as

> l :: [Elem [] Integer]
> l = [V 42, R [V 6, V 7], R l]

As my brain could handle that, and I noticed quite some
similiarity between Elem and Either, I decided to try to abstract
the thing a little. This is what I ultimately came up with

> newtype Comp f g x  = Comp (f (g x))
> newtype Rec f       = In (f (Rec f))

The idea is that `Elem s a' is basically just `Either a (s
SELF)'. Then, instead of defining a special-purpose
mutually-recursive "fixed-point type", another type `Comp' is
defined to compose two types into one, to enable the standard
Fix/Mu/Rec type to be used.

> type RecCont s a= s (Either a (RecElem s a))

A recursive container is a container with simple elements
(Left a) and recursive container-elements (Right (RecElem s a))

> type RecElem s a= Rec (Comp s (Either a))

And a recursive container-element is, err, a slightly obscured
recursive container. (s (Either a SELF))

> el              :: a -> Either a (RecElem s a)
> el              = Left

> rec             :: RecCont s a -> Either a (RecElem s a)
> rec             = Right . In . Comp

> unRec           :: RecElem s a -> RecCont s a
> unRec (In (Comp f)) = f

And indeed, a list (or set, or whatever) which contains itself is
easily defined.

> s :: RecCont [] Integer
> s = [el 42, rec [el 6, el 7], rec s]

The next step was to try to get it an instance of Show. Funny
enough, around that time, Shin-Cheng Mu posed the question of how
to make Rec an instance of Show[1], the (Haskell98) solution of
which I had just found on the HaWiki.[2]

> class RecShow f where
>     recShow :: Show a => f a -> String

> instance RecShow f => Show (Rec f) where
>     show (In f) = "(In (" ++ recShow f ++ "))"

> instance Show a => RecShow (Either a)  where recShow = show

However, I didn't just want some `Rec f' to be an instance of
Show, I wanted `Rec (Comp f g)' to be an instance of Show.
Which turned out not to be all that easy.

My best solution works, but I hope someone has a better idea...?

> class CompShow f where
>     compShow :: (Show a, RecShow g) => f (g a) -> String

> instance (CompShow f, RecShow g, Show a) => Show (Comp f g a) where
>     show (Comp f)= "(Comp (" ++ compShow f ++ "))"

> instance CompShow [] where
>     compShow l = "[" ++ (concat $ intersperse "," $ map recShow l) ++ "]"

> instance (CompShow f, RecShow g)
>                 => RecShow (Comp f g)  where recShow = show

Anyway, once this worked I just had to find some use for it ;)

> flatten         :: (Monad s, Functor s) => RecCont s a -> s a
> flatten         = join . fmap (either return (flatten . unRec))

> noI'mNotEvil    :: Num a => a -> RecCont IO a
> noI'mNotEvil n  = do
>                     putStrLn $ showString "Attempt #" $ shows n
>                              $ ": Hi, what's The Answer?"
>                     s <- getLine
>                     return $ if s == "42"
>                                 then el n
>                                 else rec (noI'mNotEvil (n+1))

> main = do
>   n <- flatten (noI'mNotEvil 1)
>   if n > 1
>       then putStrLn "Did that really have to take so long?"
>       else putStrLn "Well done!"


[1] http://www.haskell.org//pipermail/haskell/2005-February/015325.html
[2] http://www.haskell.org/hawiki/PreludeExts

-- 
Nobody can be exactly like me. Even I have trouble doing it.


More information about the Haskell-Cafe mailing list