[Haskell-cafe] Foldable Rose Trees

Dominic Steinitz dominic.steinitz at blueyonder.co.uk
Tue Dec 18 09:46:36 EST 2007


I've been trying to re-label nodes in a rose tree without re-inventing
wheels (although I'm beginning to wish I had). I've got as far as this
but haven't yet cracked the general case for Traversable.

Any help would be much appreciated.

Thanks, Dominic.

> *Main> let (p,_) = runState (unwrapMonad (traverse (\x -> WrapMonad update) (Rose' 3 [Rose' 5 [Rose' 11 [Rose' 19 []], Rose' 13 [], Rose' 17[]], Rose' 7 []]))) 0 in p
> Rose' 0 [Rose' 1 [Rose' 2 [Rose' 3 []],Rose' 4 [],Rose' 5 []],Rose' 6 []]


> import Control.Applicative
> import Data.Foldable
> import Data.Traversable
> import Data.Monoid
> import Control.Monad.State
> 
> update :: MonadState Int m => m Int
> update =
>    do x <- get
>       put (x + 1)
>       return x
> 
> data Rose' a = Rose' a [Rose' a]
>    deriving Show
> 
> instance Functor Rose' where
>   fmap f (Rose' x rs) = Rose' (f x) (map (fmap f) rs)
> 
> instance Foldable Rose' where
>    foldMap f (Rose' x rs) =  f x `mappend` (mconcat (map (foldMap f) rs))
> 
> instance Traversable Rose' where
>    traverse f (Rose' x []) = Rose' <$> f x <*> pure []
>    traverse f (Rose' x [x0]) = Rose' <$> f x <*> (pure (\x -> [x]) <*> traverse f x0)
>    traverse f (Rose' x [x0,x1]) = Rose' <$> f x <*> (pure (\x y -> x:y:[]) <*> traverse f x0 <*> traverse f x1)
>    traverse f (Rose' x [x0,x1,x2]) = Rose' <$> f x <*> (pure (\x y z -> x:y:z:[]) <*> traverse f x0 <*> traverse f x1 <*> traverse f x2)




More information about the Haskell-Cafe mailing list