[Haskell-beginners] Re: [Haskell-begin] Looking for cunning ways to update a tree

Tillmann Rendel rendel at daimi.au.dk
Tue Jul 29 18:20:51 EDT 2008


Hi Matt,

Quergle Quergle wrote:
> I have the following bit of code that
> updates a tree structure given a route to a leaf:
> 
> data Tree a = Leaf a | Node (Tree a) (Tree a)
>               deriving (Show, Eq)
> data PathSelector = GoLeft | GoRight
>                     deriving (Show, Eq)
> type Path = [PathSelector]
> 
> selectChild (Node left _) GoLeft = left
> selectChild (Node  _ right ) GoRight = right
> 
> updateNode (Node _ right) GoLeft newLeft = Node newLeft right
> updateNode (Node left _) GoRight newRight = Node left newRight
> 
> updateLeaf new (Leaf previous) = Leaf new
> 
> updateTree :: Tree a -> Path -> a -> Tree a
> updateTree tree path newValue = case path of
>                                  [] -> updateLeaf newValue tree
>                                  (p:ps) -> updateNode tree p (updateTree'
> (selectChild tree p) ps newValue)
> 
> I wanted to rewrite updateTree without using explicit recursion.
> Unfortunately, the best I could come up with is:
> 
> upDownRecurse :: (a -> b -> a) -> (a -> c) -> (a -> b -> c -> c) -> a -> [b]
> -> c
> upDownRecurse down bottoming up = upDownRecurse'
>     where upDownRecurse' acc [] = bottoming acc
>           upDownRecurse' acc (x:xs) = up acc x (upDownRecurse' (down acc x)
> xs)
> 
> updateTree' :: Tree a -> Path -> a -> Tree a
> updateTree' tree path newValue = upDownRecurse selectChild (updateLeaf
> newValue) updateNode tree path
> 
> So what's the sexier way of doing this?

I would approach that problem sligthly differently, by writing 
combinators for tree updaters. A combinator is a function which works on 
function and produces new functions, like (.), which composes two 
functions. Combinators can be very helpful to produce complex functions 
out of simple ones.

A tree updater is a function of type (Tree a -> Tree a). A simple tree 
updater works only on Leafs, and sets the value stored in the leaf:

   onLeaf :: a -> Tree a -> Tree a
   onLeaf new (Leaf previous) = Leaf new
   onLeaf new (Node left right) = error "not a leaf"

Note that the type of onLeaf can be read as (a -> (Tree a -> Tree a)), 
emphasizing that it takes a new value, and returns a tree updater.

Given such a tree updater and Tree, we can do the following things:

   (1) apply the updater to the tree
   (2) apply the updater to the left subtree, leave the right unchanged
   (3) apply the updater to the right subtree, leave the left unchanged

Case (1) is just function application, but for (2) and (3) we can define 
the following combinators:

   onLeft :: (Tree a -> Tree a) -> Tree a -> Tree a
   onLeft updater (Leaf x) = error "not a node"
   onLeft updater (Node a b) = Node (updater a) b

   onRight :: (Tree a -> Tree a) -> Tree a -> Tree a
   onRight updater (Leaf x) = error "not a node"
   onRight updater (Node a b) = Node a (updater b)

Note that the types of onLeft and onRight can be read (Tree a -> Tree a) 
-> (Tree a -> Tree a), emphasizing their function as "tree updater 
transformer". They take a tree updater, and return a different tree updater.

Now, we want to transform a call to updateTree such as

   updateTree tree [GoLeft, GoLeft, GoRight] 42

into

   onLeft (onLeft (onRight (onLeaf 42))).

As a first step, note that the nested tree updater above can be written as

   onLeft . onLeft . onRight . onLeaf $ 42

using the (.) and ($) combinators. Try to implement

   onPath :: Path -> (Tree a -> Tree a) -> Tree a -> Tree a

and updateTree in terms of onPath and onLeaf. (onPath path updater) is 
supposed to apply updater to the subtree denoted by path.

You can also try to write some more combinators, like

   onNode :: (Tree a -> Tree a) -> (Tree a -> Tree a) -> Tree a -> Tree a
   applyLeaf :: (a -> a) -> Tree a -> Tree a
   onTree :: (Tree a -> Tree a) -> (Tree a -> Tree a) -> Tree a -> Tree a
   everywhere :: (Tree a -> Tree a) -> Tree a -> Tree a

(onNode f g) works for Nodes, and applies f to the left, and g to
the right subtree.

(applyLeaf f) works for Leafs, and applies f to the value stored in the 
leaf.

(onTree f g) works for Leafs and Nodes, and applies f to the tree if it 
is a Leaf, and g if it is a Node.

(everywhere f) works for whole trees, and applies f to each subtree, and 
each subtree of each subtree, and so on.

It is possible to write onLeaf, onLeft and onRight in terms of these 
more general combinators. What is the minimum choice of combinators you 
need to define with pattern matching on Tree, so that all other 
combinators can be defined using only other combinators?

   Tillmann


More information about the Beginners mailing list