I now realize that my solution is needlessly complicated.&nbsp; Here&#39;s a simpler one.<br><br>module Trees where<br><br>data Tree = Leaf Int | Branch Tree Tree<br>&nbsp;&nbsp;&nbsp; deriving (Show)<br><br>insert x t@(Leaf y) = [Branch s t, Branch t s]&nbsp; where s = Leaf x
<br>insert x (Branch l r) = [Branch l&#39; r | l&#39; &lt;- insert x l] ++<br>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; [Branch l r&#39; | r&#39; &lt;- insert x r]<br><br>allTrees [] = []<br>allTrees (x:xs) = Leaf x : ts ++ [ s | t &lt;- ts, s &lt;- insert x t ]
<br>&nbsp; where ts = allTrees xs<br><br>&nbsp; -- Lennart<br><br><br><div><span class="gmail_quote">On 6/13/07, <b class="gmail_sendername">Lennart Augustsson</b> &lt;<a href="mailto:lennart@augustsson.net">lennart@augustsson.net</a>
&gt; wrote:</span><blockquote class="gmail_quote" style="border-left: 1px solid rgb(204, 204, 204); margin: 0pt 0pt 0pt 0.8ex; padding-left: 1ex;">This doesn&#39;t enumerate them in the order you want, but maybe it doesn&#39;t matter.
<br><br>module Trees where<br><br>combinations :: [a] -&gt; [[a]]<br>combinations [] = [[]]<br>combinations (x:xs)<br>&nbsp;&nbsp;&nbsp; = combinations xs ++ [ x:xs&#39; | xs&#39; &lt;- combinations xs ]
<span class="q"><br><br>data Tree = Leaf Int | Branch Tree Tree<br></span>&nbsp;&nbsp;&nbsp; deriving (Show)<br><br>trees [x] = [Leaf x]<br>trees (x:xs) = [ s | t &lt;- trees xs, s &lt;- insert x t ]<br><br>insert x t@(Leaf y) = [Branch s t, Branch t s]&nbsp; where s = Leaf x
<br>insert x (Branch l r) = [Branch l&#39; r | l&#39; &lt;- insert x l] ++<br>&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; [Branch l r&#39; | r&#39; &lt;- insert x r]<br><br>allTrees xs = [ t | ys &lt;- combinations xs, not (null ys), t &lt;- trees ys ]
<br><span class="sg"><br>&nbsp; -- Lennart<br><br><br></span><div><span class="q"><span class="gmail_quote">On 6/12/07, <b class="gmail_sendername">Andrew Coppin</b> &lt;<a href="mailto:andrewcoppin@btinternet.com" target="_blank" onclick="return top.js.OpenExtLink(window,event,this)">
andrewcoppin@btinternet.com</a>&gt; wrote:</span></span><div><span class="e" id="q_11326eaa4c95458f_6"><blockquote class="gmail_quote" style="border-left: 1px solid rgb(204, 204, 204); margin: 0pt 0pt 0pt 0.8ex; padding-left: 1ex;">

I&#39;m trying to construct a function<br><br>&nbsp;&nbsp;all_trees :: [Int] -&gt; [Tree]<br><br>such that all_trees [1,2,3] will yield<br><br>[<br>Leaf 1,<br>Leaf 2,<br>Leaf 3,<br>Branch (Leaf 1) (Leaf 2),<br>Branch (Leaf 1) (Leaf 3),
<br>Branch (Leaf 2) (Leaf 1),<br>Branch (Leaf 2) (Leaf 3),<br>Branch (Leaf 3) (Leaf 1),<br>Branch (Leaf 3) (Leaf 2),<br>Branch (Branch (Leaf 1) (Leaf 2)) (Leaf 3),<br>Branch (Branch (Leaf 1) (Leaf 3)) (Leaf 1),<br>Branch (Branch (Leaf 2) (Leaf 1)) (Leaf 3),
<br>Branch (Branch (Leaf 2) (Leaf 3)) (Leaf 1),<br>Branch (Branch (Leaf 3) (Leaf 1)) (Leaf 2),<br>Branch (Branch (Leaf 3) (Leaf 2)) (Leaf 1),<br>Branch (Leaf 1) (Branch (Leaf 2) (Leaf 3)),<br>Branch (Leaf 1) (Branch (Leaf 3) (Leaf 2)),
<br>Branch (Leaf 2) (Branch (Leaf 1) (Leaf 3)),<br>Branch (Leaf 2) (Branch (Leaf 3) (Leaf 2)),<br>Branch (Leaf 3) (Branch (Leaf 1) (Leaf 2)),<br>Branch (Leaf 3) (Branch (Leaf 2) (Leaf 1))<br>]<br><br><br><br>So far I&#39;m not doing too well. Here&#39;s what I&#39;ve got:
<br><br>data Tree = Leaf Int | Branch Tree Tree<br><br>pick :: [x] -&gt; [(x,[x])]<br>pick = pick_from []<br><br>pick_from :: [x] -&gt; [x] -&gt; [(x,[x])]<br>pick_from ks [] = []<br>pick_from ks [x] = []<br>pick_from ks xs = (head xs, ks ++ tail xs) : pick_from (ks ++ [head xs])
<br>(tail xs)<br><br>setup :: [Int] -&gt; [Tree]<br>setup = map Leaf<br><br>tree2 :: [Tree] -&gt; [Tree]<br>tree2 xs = do<br>&nbsp;&nbsp;(x0,xs0) &lt;- pick xs<br>&nbsp;&nbsp;(x1,xs1) &lt;- pick xs0<br>&nbsp;&nbsp;return (Branch x0 x1)<br><br>all_trees ns = (setup ns) ++ (tree2 $ setup ns)
<br><br>Clearly I need another layer of recursion here. (The input list is of<br>arbitrary length.) However, I need to somehow avoid creating duplicate<br>subtrees...<br><br>(BTW, I&#39;m really impressed with how useful the list monad is for
<br>constructing tree2...)<br><br>_______________________________________________<br>Haskell-Cafe mailing list<br><a href="mailto:Haskell-Cafe@haskell.org" target="_blank" onclick="return top.js.OpenExtLink(window,event,this)">
Haskell-Cafe@haskell.org</a><br><a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank" onclick="return top.js.OpenExtLink(window,event,this)">
http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br></blockquote></span></div></div><br>
</blockquote></div><br>