[Haskell-cafe] Re: Foldable Rose Trees

apfelmus apfelmus at quantentunnel.de
Tue Dec 18 10:36:24 EST 2007


Dominic Steinitz wrote:
> 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.

Solution 1) Data.Tree is already an instance of Traversable. :)

Solution 2) The key observation is that you the instances for rose trees 
can/should be bootstrapped from corresponding instances for lists []. 
With this, we have

>> instance Functor Rose' where
>>   fmap f (Rose' x rs) = Rose' (f x) (map (fmap f) rs)

      fmap f (Rose' x rs) = Rose' (f x) (fmap (fmap f) rs)

(fmap instead of map to highlight the general structure)

>> instance Foldable Rose' where
>>    foldMap f (Rose' x rs) =  f x `mappend` (mconcat (map (foldMap f) rs))

       foldMap f (Rose' x rs) =  f x `mappend` (foldMap (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)

       traverse f (Rose' x xs) = Rose' <$> f x <*> traverse (traverse f) xs



>> *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 []]

This can be made shorter:

  Data.Traversable.mapM m = unwrapMonad . traverse . (\x -> WrapMonad (m x))


Regards,
apfelmus



More information about the Haskell-Cafe mailing list