
I now realize that my solution is needlessly complicated. Here's a simpler
one.
module Trees where
data Tree = Leaf Int | Branch Tree Tree
deriving (Show)
insert x t@(Leaf y) = [Branch s t, Branch t s] where s = Leaf x
insert x (Branch l r) = [Branch l' r | l' <- insert x l] ++
[Branch l r' | r' <- insert x r]
allTrees [] = []
allTrees (x:xs) = Leaf x : ts ++ [ s | t <- ts, s <- insert x t ]
where ts = allTrees xs
-- Lennart
On 6/13/07, Lennart Augustsson
This doesn't enumerate them in the order you want, but maybe it doesn't matter.
module Trees where
combinations :: [a] -> [[a]] combinations [] = [[]] combinations (x:xs) = combinations xs ++ [ x:xs' | xs' <- combinations xs ]
data Tree = Leaf Int | Branch Tree Tree deriving (Show)
trees [x] = [Leaf x] trees (x:xs) = [ s | t <- trees xs, s <- insert x t ]
insert x t@(Leaf y) = [Branch s t, Branch t s] where s = Leaf x insert x (Branch l r) = [Branch l' r | l' <- insert x l] ++ [Branch l r' | r' <- insert x r]
allTrees xs = [ t | ys <- combinations xs, not (null ys), t <- trees ys ]
-- Lennart
On 6/12/07, Andrew Coppin
wrote: I'm trying to construct a function
all_trees :: [Int] -> [Tree]
such that all_trees [1,2,3] will yield
[ Leaf 1, Leaf 2, Leaf 3, Branch (Leaf 1) (Leaf 2), Branch (Leaf 1) (Leaf 3), Branch (Leaf 2) (Leaf 1), Branch (Leaf 2) (Leaf 3), Branch (Leaf 3) (Leaf 1), Branch (Leaf 3) (Leaf 2), Branch (Branch (Leaf 1) (Leaf 2)) (Leaf 3), Branch (Branch (Leaf 1) (Leaf 3)) (Leaf 1), Branch (Branch (Leaf 2) (Leaf 1)) (Leaf 3), Branch (Branch (Leaf 2) (Leaf 3)) (Leaf 1), Branch (Branch (Leaf 3) (Leaf 1)) (Leaf 2), Branch (Branch (Leaf 3) (Leaf 2)) (Leaf 1), Branch (Leaf 1) (Branch (Leaf 2) (Leaf 3)), Branch (Leaf 1) (Branch (Leaf 3) (Leaf 2)), Branch (Leaf 2) (Branch (Leaf 1) (Leaf 3)), Branch (Leaf 2) (Branch (Leaf 3) (Leaf 2)), Branch (Leaf 3) (Branch (Leaf 1) (Leaf 2)), Branch (Leaf 3) (Branch (Leaf 2) (Leaf 1)) ]
So far I'm not doing too well. Here's what I've got:
data Tree = Leaf Int | Branch Tree Tree
pick :: [x] -> [(x,[x])] pick = pick_from []
pick_from :: [x] -> [x] -> [(x,[x])] pick_from ks [] = [] pick_from ks [x] = [] pick_from ks xs = (head xs, ks ++ tail xs) : pick_from (ks ++ [head xs])
(tail xs)
setup :: [Int] -> [Tree] setup = map Leaf
tree2 :: [Tree] -> [Tree] tree2 xs = do (x0,xs0) <- pick xs (x1,xs1) <- pick xs0 return (Branch x0 x1)
all_trees ns = (setup ns) ++ (tree2 $ setup ns)
Clearly I need another layer of recursion here. (The input list is of arbitrary length.) However, I need to somehow avoid creating duplicate subtrees...
(BTW, I'm really impressed with how useful the list monad is for constructing tree2...)
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe