Re: [Haskell-cafe] Construct all possible trees

2007-06-15 Thread Andrew Coppin




Andrew Coppin wrote:
trees
:: [Int] - [Tree]
  
trees = map fst . (\ts - all_trees 1 (2 * length ts) ts) . map Leaf
  
  
all_trees :: Int - Int - [Tree] - [(Tree,[Tree])]
  
all_trees n m ts
  
| n  m = []
  
| otherwise = pick ts ++ sub_trees n m ts
  
  
sub_trees :: Int - Int - [Tree] - [(Tree,[Tree])]
  
sub_trees n m ts = do
  
let n2 = n * 2
  
(t0,ts0) - all_trees n2 m ts
  
(t1,ts1) - all_trees n2 m ts0
  
return (Branch t0 t1, ts1)
  


Idiot...

The size of the deepest possible balanced tree with N leaves is
log2 N. The deepest possible unbalanced tree has N nodes!

For small N, it doesn't matter too much. But as N gets larger, the
difference becomes... uh... large? (!)

*sigh* I hate being wrong. :-(



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Construct all possible trees

2007-06-14 Thread Mirko Rahn


I'm afraid, but you are missing a case here. For example the tree

Branch (Leaf 1) (Branch (Leaf 3) (Leaf 2))

is not constructed by your program. Correct is

insert x t@(Leaf y) = [Branch s t, Branch t s]  where s = Leaf x
insert x t@(Branch l r) = [Branch l' r | l' - insert x l] ++
  [Branch l r' | r' - insert x r] ++
   {- missed this: -} [Branch s t,Branch t s] where s = Leaf x

With this modification, your program becomes essentially the same as my 
version but with suboptimal sharing (you construct Leaf x twice and with 
the correction even three times). As a consequence my version is faster 
and eats less memory.


/BR


--
-- Mirko Rahn -- Tel +49-721 608 7504 --
--- http://liinwww.ira.uka.de/~rahn/ ---
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Construct all possible trees

2007-06-14 Thread Andrew Coppin

Well, I eventually came up with this:

-

data Tree = Leaf Int | Branch Tree Tree deriving Show

pick :: [x] - [(x,[x])]
pick = pick_from []

pick_from :: [x] - [x] - [(x,[x])]
pick_from ks [] = []
pick_from ks xs = (head xs, ks ++ tail xs) : pick_from (ks ++ [head xs]) 
(tail xs)


trees :: [Int] - [Tree]
trees = map fst . (\ts - all_trees 1 (2 * length ts) ts) . map Leaf

all_trees :: Int - Int - [Tree] - [(Tree,[Tree])]
all_trees n m ts
 | n  m = []
 | otherwise = pick ts ++ sub_trees n m ts

sub_trees :: Int - Int - [Tree] - [(Tree,[Tree])]
sub_trees n m ts = do
 let n2 = n * 2
 (t0,ts0) - all_trees n2 m ts
 (t1,ts1) - all_trees n2 m ts0
 return (Branch t0 t1, ts1)

-

For example, trees [1,2,3] now gives

Leaf 1
Leaf 2
Leaf 3
Branch (Leaf 1) (Leaf 2)
Branch (Leaf 1) (Leaf 3)
Branch (Leaf 1) (Branch (Leaf 2) (Leaf 3))
Branch (Leaf 1) (Branch (Leaf 3) (Leaf 2))
Branch (Leaf 2) (Leaf 1)
Branch (Leaf 2) (Leaf 3)
Branch (Leaf 2) (Branch (Leaf 1) (Leaf 3))
Branch (Leaf 2) (Branch (Leaf 3) (Leaf 1))
Branch (Leaf 3) (Leaf 1)
Branch (Leaf 3) (Leaf 2)
Branch (Leaf 3) (Branch (Leaf 1) (Leaf 2))
Branch (Leaf 3) (Branch (Leaf 2) (Leaf 1))
Branch (Branch (Leaf 1) (Leaf 2)) (Leaf 3)
Branch (Branch (Leaf 1) (Leaf 3)) (Leaf 2)
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)

which looks pretty comprehensive to me!


The derivation wasn't easy. It goes something like this:

First, the pick function takes a list and picks a single element from 
it, returning the element picked and the remaining unpicked elements. It 
does this inside the list monad, thus representing every possibel 
choice. (It's defined in terms of pick_from, which isn't used anywhere 
else. The algorithm should be fairly self-evident.)


Next, we have trees which transforms a list of integers into a list of 
trivial 1-leaf trees to be processed by all_trees. The all_trees 
function calls pick to select all possible trivial trees, and then calls 
sub_trees to pick all possible nontrivial trees.


The code for sub_trees would go something like this:

 sub_trees ts = do
   t0 - ts
   t1 - ts
   return (Branch t0 t1)

But now t0 == t1 sometimes, which we cannot allow. Hence the pick 
function:


 sub_trees ts = do
   (t0,ts0) - pick ts
   (t1,ts1) - pick ts0
   return (Branch t0 t1, ts1)

And now the problem is solved.

However, this only generates all possible 2-leaf trees. To make *all* 
possible trees, we must be recursive:


 sub_trees ts = do
   (t0,ts0) - all_trees ts
   (t1,ts1) - all_trees ts0
   return (Branch t0 t1, ts1)

And now it works properly.

Er... wait. Now we have an infinite recursive loop! all_trees -- 
sub_trees -- all_trees (with the same arguments)!


The only way I could figure out to avoid that is to count how big the 
input list is - and hence how deep the tree can possibly be. Then you 
keep track of how deep you are, and abort when you get too deep. I added 
lots of hackery to avoid recomputing stuff. Makes the code look very 
messy and ugly...


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Construct all possible trees

2007-06-13 Thread Mirko Rahn

Andrew Coppin wrote:


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


Just another way (assuming the given order is not relevant), based on 
the idea that it is quite easy to insert a new node on all possible 
positions in an already existing tree.


data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving Show

decomp (Branch l r) = [(l,flip Branch r),(r,Branch l)]
decomp _= []

insert x t = Branch x t
   : Branch t x
   : [re b | (part,re) - decomp t, b - insert x part]

all_trees [] = []
all_trees (x:xs) =
let this = Leaf x
more = all_trees xs
in this : more ++ concatMap (insert this) more

/BR

--
-- Mirko Rahn -- Tel +49-721 608 7504 --
--- http://liinwww.ira.uka.de/~rahn/ ---
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Construct all possible trees

2007-06-13 Thread Tom Pledger

*Andrew Coppin wrote:
*

| I'm trying to construct a function
| 
|   all_trees :: [Int] - [Tree]
| 
| such that all_trees [1,2,3] will yield

:

If you write a helper function that takes an N element list, and returns 
all 2^N ways of dividing those elements into 2 lists, e.g.


   splits ab -- [(ab,),(b,a),(a,b),(,ab)]

then you can use it both for dividing the initial list into kept and 
discarded elements, and for dividing a list between a left subtree and a 
right subtree.


Regards,
Tom

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Construct all possible trees

2007-06-13 Thread Henning Thielemann

On Thu, 14 Jun 2007, Tom Pledger wrote:

 *Andrew Coppin wrote:
 *

  | I'm trying to construct a function
  |
  |   all_trees :: [Int] - [Tree]
  |
  | such that all_trees [1,2,3] will yield
  :

 If you write a helper function that takes an N element list, and returns
 all 2^N ways of dividing those elements into 2 lists, e.g.

 splits ab -- [(ab,),(b,a),(a,b),(,ab)]

 then you can use it both for dividing the initial list into kept and
 discarded elements, and for dividing a list between a left subtree and a
 right subtree.

This one was discussed recently:
 http://www.haskell.org/pipermail/haskell-cafe/2007-May/025767.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Construct all possible trees

2007-06-13 Thread Andrew Coppin

Colin DeVilbiss wrote:

On 6/12/07, Andrew Coppin [EMAIL PROTECTED] wrote:

Based on the sample output, I'm guessing that the desired output is
every tree which, when flattened, gives a permutation of a non-empty
subset of the supplied list.  This limits the output to trees with up
to n leaves.


Every possible tree, using the supplied elements as leaf elements, 
without ever duplicating them. (Note, however, that the initial list may 
contain duplicates in the first place, so you can't just test for and 
remove duplicates in the produced lists; you must avoid repeating 
elements by construction.)



Branch (Branch (Leaf 1) (Leaf 3)) (Leaf 1),


If I'm guessing the desired output correctly, this must be a typo?


Erm... yes.


I'd be tempted to solve the list-only problem first (generate all
sub-permutations of a list), then solve the tree problem (generate
all un-flattenings of a list).


I can already create all possible 2-element trees. It seems like there 
should be a way to recurse that... but without duplicating elements.


Hmm, I don't know - there's probably several correct solutions to this 
problem. ;-)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Construct all possible trees

2007-06-13 Thread 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 [EMAIL PROTECTED] 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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Construct all possible trees

2007-06-12 Thread Andrew Coppin

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


Re: [Haskell-cafe] Construct all possible trees

2007-06-12 Thread Colin DeVilbiss

On 6/12/07, Andrew Coppin [EMAIL PROTECTED] wrote:

Based on the sample output, I'm guessing that the desired output is
every tree which, when flattened, gives a permutation of a non-empty
subset of the supplied list.  This limits the output to trees with up
to n leaves.


Branch (Branch (Leaf 1) (Leaf 3)) (Leaf 1),


If I'm guessing the desired output correctly, this must be a typo?

I'd be tempted to solve the list-only problem first (generate all
sub-permutations of a list), then solve the tree problem (generate
all un-flattenings of a list).

Colin DeVilbiss
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe