[Haskell-cafe] Construct all possible trees

Andrew Coppin andrewcoppin at btinternet.com
Tue Jun 12 14:04:33 EDT 2007


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...)



More information about the Haskell-Cafe mailing list