
Hi folk, as an exercise I'm trying to write a binary tree whose nodes also include a reference to its parent. I've got the data structure I want to use and some helper functions, but there seems to be a bug in insert or find or both (although I assume it's in insert). Here's what I got so far: data BinTree a = Leaf | Node { value :: a , left :: BinTree a , right :: BinTree a , father :: BinTree a } instance Show a => Show (BinTree a) where show Leaf = "[]" show (Node v l r _) = "(Node " ++ show v ++ " " ++ show l ++ " " ++ show r ++ ")" mkRoot :: a -> BinTree a mkRoot value = let root = Node value Leaf Leaf root in root member :: Ord a => a -> BinTree a -> Bool member v Leaf = False member v (Node v' l r _) = if v == v' then True else if v <= v' then member v l else member v r find :: Ord a => a -> BinTree a -> Maybe (BinTree a) find v Leaf = Nothing find v n@(Node v' l r _) = if v == v' then Just n else if v <= v' then find v l else find v r insert :: Ord a => a -> BinTree a -> BinTree a insert v' Leaf = mkRoot v' insert v' n@(Node v l r f) = insert' v' n f where insert' :: Ord a => a -> BinTree a -> BinTree a -> BinTree a insert' v' Leaf f' = Node v' Leaf Leaf f' insert' v' n@(Node v l r f) f' = if v' == v then n else if v' <= v then let inserted = insert' v' l result result = Node v inserted r f in result else let inserted = insert' v' r result result = Node v l inserted f in result I thought this should do the trick, but here's what I get in ghci: *Main> find 3 (insert 7 (insert 3 (insert 5 Leaf))) >>= return . parent Just (Node 5 (Node 3 [] []) []) I'm expecting to see Just (Node 5 (Node 3 [] []) (Node 7 [] [])) Inserting into an empty tree (i.e. a leaf) works fine, as does mkRoot. Also, it seems as inserting an existing value works fine as well - but obviously I couldn't test that one exhaustingly so far. I'm grateful for any pointers towards a solution. Best regards, Michael P.S.: For those unfamiliar with this problem, here is a list of URLs of what I read of the subject: [1] http://www.haskell.org/haskellwiki/Tying_the_Knot#Migrated_from_the_old_wiki [2] http://debasishg.blogspot.de/2009/02/learning-haskell-solving-josephus.html [3] http://blog.sigfpe.com/2006/12/tying-knots-generically.html

You are right that the problem is with your insert algorithm. When
you are inserting, what you are doing is you traverse down the correct
side of the tree, you make a new node and then you return that node,
thereby trashing the rest of the tree.
Here is the general approach of what you should do. You know you are
going left or right down the tree, and you know you are probably going
to change it, that means you have to change every node down along the
length of the tree.
insert v' Leaf = mkRoot v'
insert v' n@(Node v l r f) = case compare v v' of
EQ -> n
GT -> (Node v (insert v' l) r f)
LT -> (Node v l (insert v' r) f)
The only problem with this is that the parent node is not getting set
with this algorithm. The problem is that Leaves do not know their
parents, so one solution is to change your data type to this:
data BinTree a =
Leaf { lfather :: BinTree a } |
Node { value :: a
, left :: BinTree a
, right :: BinTree a
, father :: BinTree a
}
then insert would become
insert v' (Leaf parent) = let result = Node v' (Leaf result) (Leaf
result) parent
insert v' n = ...
Otherwise you'll have to pass the parent down along the tree as you
modify it as such:
insert v' Leaf = mkRoot v'
insert v' n@(Node v l r f) = case compare v v' of
EQ -> n
GT -> (Node v (insert' v' l n) r f)
LT -> (Node v l (insert' v' r n) f)
insert' v' Leaf parent = Node v' Leaf Leaf parent
insert' v' n@(Node v l r f) parent = case compare v v' of
EQ -> n
GT -> let result = Node v (insert' v' l result) r parent in result
LT -> let result = Node v l (insert' v' r result) parent in result
You require a base case because the first node has no parent to insert with.
On Fri, Apr 13, 2012 at 12:16 PM, Michael Schober
Hi folk,
as an exercise I'm trying to write a binary tree whose nodes also include a reference to its parent. I've got the data structure I want to use and some helper functions, but there seems to be a bug in insert or find or both (although I assume it's in insert).
Here's what I got so far:
data BinTree a = Leaf | Node { value :: a , left :: BinTree a , right :: BinTree a , father :: BinTree a }
instance Show a => Show (BinTree a) where show Leaf = "[]" show (Node v l r _) = "(Node " ++ show v ++ " " ++ show l ++ " " ++ show r ++ ")"
mkRoot :: a -> BinTree a mkRoot value = let root = Node value Leaf Leaf root in root
member :: Ord a => a -> BinTree a -> Bool member v Leaf = False member v (Node v' l r _) = if v == v' then True else if v <= v' then member v l else member v r
find :: Ord a => a -> BinTree a -> Maybe (BinTree a) find v Leaf = Nothing find v n@(Node v' l r _) = if v == v' then Just n else if v <= v' then find v l else find v r
insert :: Ord a => a -> BinTree a -> BinTree a insert v' Leaf = mkRoot v' insert v' n@(Node v l r f) = insert' v' n f where insert' :: Ord a => a -> BinTree a -> BinTree a -> BinTree a insert' v' Leaf f' = Node v' Leaf Leaf f' insert' v' n@(Node v l r f) f' = if v' == v then n else if v' <= v then let inserted = insert' v' l result result = Node v inserted r f in result else let inserted = insert' v' r result result = Node v l inserted f in result
I thought this should do the trick, but here's what I get in ghci:
*Main> find 3 (insert 7 (insert 3 (insert 5 Leaf))) >>= return . parent Just (Node 5 (Node 3 [] []) [])
I'm expecting to see
Just (Node 5 (Node 3 [] []) (Node 7 [] []))
Inserting into an empty tree (i.e. a leaf) works fine, as does mkRoot. Also, it seems as inserting an existing value works fine as well - but obviously I couldn't test that one exhaustingly so far.
I'm grateful for any pointers towards a solution.
Best regards, Michael
P.S.: For those unfamiliar with this problem, here is a list of URLs of what I read of the subject: [1] http://www.haskell.org/haskellwiki/Tying_the_Knot#Migrated_from_the_old_wiki [2] http://debasishg.blogspot.de/2009/02/learning-haskell-solving-josephus.html [3] http://blog.sigfpe.com/2006/12/tying-knots-generically.html
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Sorry this snippet should have been:
then insert would become:
insert v' (Leaf parent) = let result = Node v' (Leaf result) (Leaf
result) parent in result
insert v' n = ...
I did not test that code, but it should work.
On Fri, Apr 13, 2012 at 1:49 PM, David McBride
You are right that the problem is with your insert algorithm. When you are inserting, what you are doing is you traverse down the correct side of the tree, you make a new node and then you return that node, thereby trashing the rest of the tree.
Here is the general approach of what you should do. You know you are going left or right down the tree, and you know you are probably going to change it, that means you have to change every node down along the length of the tree.
insert v' Leaf = mkRoot v' insert v' n@(Node v l r f) = case compare v v' of EQ -> n GT -> (Node v (insert v' l) r f) LT -> (Node v l (insert v' r) f)
The only problem with this is that the parent node is not getting set with this algorithm. The problem is that Leaves do not know their parents, so one solution is to change your data type to this:
data BinTree a = Leaf { lfather :: BinTree a } | Node { value :: a , left :: BinTree a , right :: BinTree a , father :: BinTree a }
then insert would become insert v' (Leaf parent) = let result = Node v' (Leaf result) (Leaf result) parent insert v' n = ...
Otherwise you'll have to pass the parent down along the tree as you modify it as such:
insert v' Leaf = mkRoot v' insert v' n@(Node v l r f) = case compare v v' of EQ -> n GT -> (Node v (insert' v' l n) r f) LT -> (Node v l (insert' v' r n) f)
insert' v' Leaf parent = Node v' Leaf Leaf parent insert' v' n@(Node v l r f) parent = case compare v v' of EQ -> n GT -> let result = Node v (insert' v' l result) r parent in result LT -> let result = Node v l (insert' v' r result) parent in result
You require a base case because the first node has no parent to insert with.
On Fri, Apr 13, 2012 at 12:16 PM, Michael Schober
wrote: Hi folk,
as an exercise I'm trying to write a binary tree whose nodes also include a reference to its parent. I've got the data structure I want to use and some helper functions, but there seems to be a bug in insert or find or both (although I assume it's in insert).
Here's what I got so far:
data BinTree a = Leaf | Node { value :: a , left :: BinTree a , right :: BinTree a , father :: BinTree a }
instance Show a => Show (BinTree a) where show Leaf = "[]" show (Node v l r _) = "(Node " ++ show v ++ " " ++ show l ++ " " ++ show r ++ ")"
mkRoot :: a -> BinTree a mkRoot value = let root = Node value Leaf Leaf root in root
member :: Ord a => a -> BinTree a -> Bool member v Leaf = False member v (Node v' l r _) = if v == v' then True else if v <= v' then member v l else member v r
find :: Ord a => a -> BinTree a -> Maybe (BinTree a) find v Leaf = Nothing find v n@(Node v' l r _) = if v == v' then Just n else if v <= v' then find v l else find v r
insert :: Ord a => a -> BinTree a -> BinTree a insert v' Leaf = mkRoot v' insert v' n@(Node v l r f) = insert' v' n f where insert' :: Ord a => a -> BinTree a -> BinTree a -> BinTree a insert' v' Leaf f' = Node v' Leaf Leaf f' insert' v' n@(Node v l r f) f' = if v' == v then n else if v' <= v then let inserted = insert' v' l result result = Node v inserted r f in result else let inserted = insert' v' r result result = Node v l inserted f in result
I thought this should do the trick, but here's what I get in ghci:
*Main> find 3 (insert 7 (insert 3 (insert 5 Leaf))) >>= return . parent Just (Node 5 (Node 3 [] []) [])
I'm expecting to see
Just (Node 5 (Node 3 [] []) (Node 7 [] []))
Inserting into an empty tree (i.e. a leaf) works fine, as does mkRoot. Also, it seems as inserting an existing value works fine as well - but obviously I couldn't test that one exhaustingly so far.
I'm grateful for any pointers towards a solution.
Best regards, Michael
P.S.: For those unfamiliar with this problem, here is a list of URLs of what I read of the subject: [1] http://www.haskell.org/haskellwiki/Tying_the_Knot#Migrated_from_the_old_wiki [2] http://debasishg.blogspot.de/2009/02/learning-haskell-solving-josephus.html [3] http://blog.sigfpe.com/2006/12/tying-knots-generically.html
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hi again, thanks for your comments. I've tried your code, but unfortunately that doesn't seem to do the trick. The problem is that Leaves do not know their
parents, so one solution is to change your data type to this:
data BinTree a = Leaf { lfather :: BinTree a } | Node { value :: a , left :: BinTree a , right :: BinTree a , father :: BinTree a }
then insert would become insert v' (Leaf parent) = let result = Node v' (Leaf result) (Leaf result) parent insert v' n = ...
I was reluctant to this version at first, but I gave it a try. You can find it attached in the alt-linked-tree.hs (I hope it's okay to attach code in files, but the code grew beyond snippetery and this way it's probably more comfortable to test it). Unfortunately, this doesn't work as well. The actual insert code in this version looks like this: -- inserts an element into a binary search tree insert :: Ord a => a -> BinTree a -> BinTree a insert v' (Leaf parent) = let result = Node v' (Leaf result) (Leaf result) parent in result insert v' n@(Node v l r p) = case compare v' v of EQ -> n LT -> let inserted = insert v' l result = Node v inserted r p in result GT -> let inserted = insert v' r result = Node v l inserted p in result I think the problem here is, that I don't modify the parent, but I cannot seem to wrap my head around it today.
Otherwise you'll have to pass the parent down along the tree as you modify it as such:
insert v' Leaf = mkRoot v' insert v' n@(Node v l r f) = case compare v v' of EQ -> n GT -> (Node v (insert' v' l n) r f) LT -> (Node v l (insert' v' r n) f)
insert' v' Leaf parent = Node v' Leaf Leaf parent insert' v' n@(Node v l r f) parent = case compare v v' of EQ -> n GT -> let result = Node v (insert' v' l result) r parent in result LT -> let result = Node v l (insert' v' r result) parent in result
You require a base case because the first node has no parent to insert with.
This looks pretty much like my code from the beginning, but it doesn't work as well. However, in the meantime I played around with some complexer trees to come across a deficit pattern, but it's really strange. It seems to me as if random subtrees are missing. Sometimes there are siblings as expected, sometimes even children of these siblings, but there never seems to be a working tree. I have an intuition that it could be the case that I have to modify the parent as well in the recursive case, but I don't know how yet. Anyway, I'll let it go for the weekend and return to doubly linked lists for now. Maybe implementing more features for those will help me get a better intuition for these kind of problems.

Michael, I had some code lying around, experimenting on tying-the-knot in the context of trees. I've just pushed it to github, hoping it can be helpful to you. The data type is slightly different to yours but the ideas should apply. https://github.com/ozgurakgun/knot-tree/blob/master/KnotBinTree.hs HTH, Ozgur

Hi Michael
When you have a tree with nodes pointing back to their parents then
you essentially have a graph. If you plan to change that graph, then
you have to rebuild *the entire structure*, and there's no going
around that. (And you cant use any of the nodes you pattern match,
only the numbers.)
They say that for this or similar reasons you have to use a zipper,
but I know nothing more about them than this :-)
On Sat, Apr 14, 2012 at 3:04 PM, Michael Schober
Hi again,
thanks for your comments. I've tried your code, but unfortunately that doesn't seem to do the trick.
The problem is that Leaves do not know their
parents, so one solution is to change your data type to this:
data BinTree a = Leaf { lfather :: BinTree a } | Node { value :: a , left :: BinTree a , right :: BinTree a , father :: BinTree a }
then insert would become insert v' (Leaf parent) = let result = Node v' (Leaf result) (Leaf result) parent insert v' n = ...
I was reluctant to this version at first, but I gave it a try. You can find it attached in the alt-linked-tree.hs (I hope it's okay to attach code in files, but the code grew beyond snippetery and this way it's probably more comfortable to test it).
Unfortunately, this doesn't work as well. The actual insert code in this version looks like this:
-- inserts an element into a binary search tree
insert :: Ord a => a -> BinTree a -> BinTree a insert v' (Leaf parent) = let result = Node v' (Leaf result) (Leaf result) parent in result insert v' n@(Node v l r p) = case compare v' v of EQ -> n LT -> let inserted = insert v' l result = Node v inserted r p in result GT -> let inserted = insert v' r result = Node v l inserted p in result
I think the problem here is, that I don't modify the parent, but I cannot seem to wrap my head around it today.
Otherwise you'll have to pass the parent down along the tree as you modify it as such:
insert v' Leaf = mkRoot v' insert v' n@(Node v l r f) = case compare v v' of EQ -> n GT -> (Node v (insert' v' l n) r f) LT -> (Node v l (insert' v' r n) f)
insert' v' Leaf parent = Node v' Leaf Leaf parent insert' v' n@(Node v l r f) parent = case compare v v' of EQ -> n GT -> let result = Node v (insert' v' l result) r parent in result LT -> let result = Node v l (insert' v' r result) parent in result
You require a base case because the first node has no parent to insert with.
This looks pretty much like my code from the beginning, but it doesn't work as well. However, in the meantime I played around with some complexer trees to come across a deficit pattern, but it's really strange. It seems to me as if random subtrees are missing. Sometimes there are siblings as expected, sometimes even children of these siblings, but there never seems to be a working tree.
I have an intuition that it could be the case that I have to modify the parent as well in the recursive case, but I don't know how yet.
Anyway, I'll let it go for the weekend and return to doubly linked lists for now. Maybe implementing more features for those will help me get a better intuition for these kind of problems.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Markus Läll

Hi Markus,
They say that for this or similar reasons you have to use a zipper, but I know nothing more about them than this :-)
Thanks for the hint. I hadn't heard of zippers before and after some reading, they indeed seem to do the trick, although I have yet to implement it in my solution. Anyways, here are the resources which worked best for my understanding: [1] http://en.wikibooks.org/wiki/Haskell/Zippers [2] http://learnyouahaskell.com/zippers Best, Michael
participants (4)
-
David McBride
-
Markus Läll
-
Michael Schober
-
Ozgur Akgun