[Haskell-beginners] Applicative Functors: Rose Trees with an alternate behavior

Brent Yorgey byorgey at seas.upenn.edu
Wed Aug 11 10:06:36 EDT 2010


On Tue, Aug 10, 2010 at 12:08:01PM -0700, Travis Erdman wrote:
> > The correct implementation of pure looks like this:
> > 
> >   pure x = Node x (repeat (pure x))
> > 
> > (Hooray for lazy infinite data structures!) With this definition the
> > standard sequenceA works just fine.
> 
> Ha, I would never have arrived at that solution in a million years on my own, 
> but now that you show me, it makes perfect sense!
> Following the discussion of ZipLists from 
> http://learnyouahaskell.com/functors-applicative-functors-and-monoids, my 
> initial solution attempt was
> pure x = Node x (repeat x)
> but that doesn't even compile.  I had suspected that I needed to make the pure 
> tree "go down", but I couldn't see how to do it.
> 
> OK, some follow-on questions if I may ...
> 
> sequenceA [Tree a] now returns Tree [a], as indicated.
> 
> Now, I'd also like sequenceA Tree [a] to return [Tree a].  To do that, I need to 
> make Tree an instance of Traversable and, hence, Foldable.
> 
> Here's my stab at doing that ...
> 
> instance Foldable Tree where
>     foldMap f (Node cargo subtrees) = f cargo `mappend` foldMap (foldMap f) 
> subtrees
> 
> instance Traversable Tree where
>     traverse f (Node cargo subtrees) = Node <$> f cargo <*> traverse (traverse 
> f) subtrees  

These are correct.  Note that (unlike Applicative) there is
essentially only one possible instance of Foldable and Traversable for
any given type (the only thing you can do is change the order in which
the folding/traversing happens, but that's usually not very
interesting).  You may be interested to know that if you have ghc
6.12.1 or later, ghc can automatically derive these instances for you,
which you can read about in a blog post of mine [1].

> The Foldable code appears to be correct; at least, I can the fold the trees.  
> "Foldable" also allows the toList Tree a to work as expected.
> Given that, I don't really "get" Traversable, and the code here is just my best 
> guess as to what it should be.  But, I think it must not
> be correct, because sequenceA Tree [a] is not returning what I think it should 
> be returning (ie [Tree a]).

Traversable is a bit tricky to wrap your head around.  Essentially
what traverse does is to walk over the entire structure, applying a
function to each element and rebuilding the structure *in some
Applicative context*.  Anyway, your traverse is correct; the reason it
is not doing what you expect (I assume) is that you are using lists
instead of ZipLists.  sequenceA :: Tree [a] -> [Tree a] will give you
a list of trees built by selecting an element at each node in all
possible ways, since the traversal will rebuild the tree in the []
Applicative context, which represents nondeterministic choice.
sequenceA :: Tree (ZipList a) -> ZipList (Tree a) will just "unzip"
the trees, choosing all the first elements to go in the nodes of the
first tree, all the second elements to go in the nodes of the second
tree, and so on.  So if you want a function of type Tree [a] -> [Tree
a] with the unzipping behavior, just stick in an fmap ZipList and
getZipList in the appropriate places.

> Aside from this, what other things can I do with a Traversable Tree?  

You can do anything where you want to map a function over the contents
of the tree, but processing each element of the tree may have some
"side effects".  For example you can write some sort of stateful
algorithm to process and update all the elements of the tree.  Or
generate multiple nondeterministic results for each element of the
tree.  And so on.

> My 
> intuition suggests I might be able to do Scan's on a tree, say
> calculate a cumulative sums Tree from root to leaves (or vice versa).  But I've 
> no idea how to implement that using it's "Traversability".
> 
> As of now, I have implemented this up-and-down scanning thusly ...
> 
> treeScanDown :: (a -> b -> a) -> a -> Tree b -> Tree a
> treeScanDown f x (Node y subtrees) = Node g (fmap (treeScanDown f g) subtrees)
>     where g = f x y
> 
> treeScanUp :: (a -> [a] -> a) -> Tree a -> Tree a
> treeScanUp f (Node x []) = Node x []
> treeScanUp f (Node x subtrees) = Node (f x (fmap fromNode g)) g
>     where g = fmap (treeScanUp f) subtrees

I don't think you can implement these with Traversable or Foldable.
This is the sort of thing that becomes very easy with an attribute
grammar system, and I'll leave it to someone else to note whether
these correspond to any sort of greekomorphism.  But if I were you I'd
just stick with those manual scanning functions for now.

-Brent

[1] http://byorgey.wordpress.com/2010/03/03/deriving-pleasure-from-ghc-6-12-1/


More information about the Beginners mailing list