[Haskell-cafe] Monad for binary tree data structure

Sjoerd Visscher sjoerd at w3future.com
Sat Jul 23 11:59:14 CEST 2011


On Jul 23, 2011, at 7:31 AM, Александр wrote:

> data Tree a = Empty 
>               | Node a (Tree a) (Tree a)
>               deriving (Eq, Ord, Read, Show)
> 
> How can i make Monad type class instance for this tree?

Like David said, you'll need a sensible way to merge 2 trees. As we have no Ord a, the only sensible thing to do is to append them, so the order of the elements is maintained and then the Monad instance will work like the list monad. First we'll have to agree on the ordering, I'll assume:

toList :: Tree a -> [a]
toList Empty = []
toList (Node a l r) = toList l ++ [a] ++ toList r

Next is the append function. Let's make a Monoid instance for extra fun. (You'll need to import Data.Monoid)

instance Monoid (Tree a) where
  mempty = Empty
  mappend Empty x = x
  mappend (Node a l r) x = Node a l (mappend r x)

This will generate unbalanced trees, but it'll have to do. Now the Monad instance:

instance Monad Tree where
  return a = Node a Empty Empty
  Empty >>= _ = Empty
  Node a l r >>= f = case f a of
    Empty -> (l >>= f) `mappend` (r >>= f)
    Node b lb rb -> Node b ((l >>= f) `mappend` lb) (rb `mappend` (r >>= f))

Let's see if this indeed behaves like the list monad.

fromList :: [a] -> Tree a
fromList [] = Empty
fromList xs = Node a (fromList l) (fromList r) where
  (l, a:r) = splitAt (length xs `div` 2) xs

> toList $ fromList [10,20,30] >>= (\x -> fromList [x - 1, x, x + 1])
[9,10,11,19,20,21,29,30,31]

It works!
--
Sjoerd Visscher







More information about the Haskell-Cafe mailing list