[Haskell-cafe] Growing Trees

Sebastian Sylvan sebastian.sylvan at gmail.com
Thu Sep 22 18:19:30 EDT 2005


On 9/22/05, Tom Hawkins <tom at confluent.org> wrote:
> I'm porting an ML program to Haskell, but am having difficulty with
> particular data structure: a tree where each node has references to the
> children as well as the parent...
>
> data Tree a
>    = TreeRoot { stuff    :: a
>               , children :: [Tree]
>               }
>    | TreeNode { stuff    :: a
>               , parent   :: Tree
>               , children :: [Tree]
>               }
>
> But because of these bidirectional links, every time I add a node I must
> reconstructing the entire tree.  There is also the add coding complexity
> of threading the tree through various functions to simulate state.
>
> What are my [monadic] options?
>

You can't do trees with mutable references in Haskell without doing it
a state monad (ST, or IO, basically).

However, it is possible to use laziness in order to have bidirectional
"links", but doing so is kinda tedious (you can't pattern match on one
constructor, you need to pattern match against two "levels" so you can
construct the parent and the child at the same time).

Here's a binary tree I threw together just now (not thouroughly
tested!) where each node has a link to its parent.

Note how laziness is used to make the parent refer to the child and
the child refer to the parent.
Some code could be saved by stating that a Root is just a Node with a
Nil parent, but I didn't want to complicate it too much.

-----------

data TreeParent a = Root a (TreeParent a) (TreeParent a)
                                     | Node a (TreeParent a)
(TreeParent a) (TreeParent a)
                                     | Nil


insert :: Ord a => TreeParent a -> a -> TreeParent a

insert (Root a Nil Nil) k = parent
    where parent | k < a =  Root a child Nil
                             | otherwise = Root a Nil child
                child = Node k parent Nil Nil

insert (Root a Nil t2) k
    | k < a = parent
    | otherwise = Root a Nil (insert t2 k)
    where parent = Root a child t2
               child = Node k parent Nil Nil

insert (Root a t1 Nil ) k
    | k < a = Root a (insert t1 k) Nil
    | otherwise = parent
    where parent = Root a t1 child
                child = Node k parent Nil Nil

insert (Root a t1 t2) k
    | k < a = Root a (insert t1 k) t2
    | otherwise = Root a t1 (insert t2 k)

insert (Node a p Nil Nil) k = parent
    where parent | k < a =  Node a p child Nil
                             | otherwise = Node a p Nil child
                child = Node k parent Nil Nil

insert (Node a p Nil t2) k
    | k < a = parent
    | otherwise = Node a p Nil (insert t2 k)
    where parent = Node a p child t2
                child = Node k parent Nil Nil

insert (Node a p t1 Nil ) k
    | k < a = Node a p (insert t1 k) Nil
    | otherwise = parent
    where parent = Node a p t1 child
               child = Node k parent Nil Nil

insert (Node a p t1 t2) k  | k < a = Node a p (insert t1 k) t2
                                            | otherwise = Node a p t1
(insert t2 k)

insert Nil k = Root k Nil Nil


toList Nil = []
toList (Node a _ t1 t2) = toList t1 ++ [a] ++ toList t2
toList (Root a t1 t2) = toList t1 ++ [a] ++ toList t2

-----------


/S
--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862


More information about the Haskell-Cafe mailing list