
On Wed, 31 Dec 2008 17:19:09 +0100, Max cs
Hi Henk-Jan van Tuyl,
Thank you very much for your reply!
I think the concatenation should be different to thhe
treeConcat :: Tree a -> Tree a -> Tree a
the above is a combination of two trees instead of a concatenation, so I think the type of treeConcat should be:
treeConcat :: Tree (Tree a) -> Tree a
instead. How do you think? : ) I tried to implement it .. but it seems confusing.. to me
Thanks
Max
Hello Max, The function treeConcat :: Tree (Tree a) -> Tree a cannot be created, as it has an infinite type; you can however, define a function that replaces leafs with trees, for example treeConcat' in the following module, that replaces all leaves that contains a one with a given tree:
module TreeConcat where
data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving Show
treeConcat' :: Num a => Tree a -> Tree a -> Tree a treeConcat' (Leaf 1) tree = tree treeConcat' (Leaf x) _ = Leaf x treeConcat' (Branch x y) tree = Branch (treeConcat' x tree) (treeConcat' y tree)
main :: IO () main = print $ treeConcat' (Branch (Leaf 1) (Leaf 2)) (Branch (Leaf 3) (Leaf 4))
This displays: Branch (Branch (Leaf 3) (Leaf 4)) (Leaf 2) If this doen't help you either, I need to know more about what you are trying to do. Regards, Henk-Jan van Tuyl -- http://functor.bamikanarie.com http://Van.Tuyl.eu/ --
On Wed, Dec 31, 2008 at 3:33 PM, Henk-Jan van Tuyl
wrote: Hi Max,
A simple way to do this:
module TreeConcat where
data Tree a = Leaf a | Branch (Tree a) (Tree a)
deriving Show
treeConcat :: Tree a -> Tree a -> Tree atreeConcat xs ys = Branch xs ys
main :: IO ()
main = print $ treeConcat (Leaf 1) (Leaf 2)
But perhaps you want a certain ordering? Have a look at:
http://hackage.haskell.org/packages/archive/AvlTree/4.2/doc/html/Data-Tree-A...
-- Regards, Henk-Jan van Tuyl
--