Andy Fugard wrote:

> My main question is really what facilities of the language I should be
> looking at to make this code more elegant!  As you can see I currently know
> only the basics of currying, and some list operations.

Definitely list comprehensions! I digged out some old code:

> module Perms where

Permutations.

> perms                         :: [a] -> [[a]]
> perms []                      =  [ [] ]
> perms (a : x)                 =  [ z | y <- perms x, z <- insertions a y ]
>
> insertions                    :: a -> [a] -> [[a]]
> insertions a []               =  [ [a] ]
> insertions a x@(b : y)        =  (a : x) : [ b : z | z <- insertions a y ]
 
Using deletions instead of insertions; generates the permutations
in lexicographic order, but is a bit slower.
 
> perms'                        :: [a] -> [[a]]
> perms' []                     =  [ [] ]
> perms' x                      =  [ a : z | (a, y) <- deletions x, z <- perms' y ]

> deletions                     :: [a] -> [(a, [a])]
> deletions []                  =  []
> deletions (a : x)             =  (a, x) : [ (b, a : y) | (b, y) <- deletions x ]

Cheers, Ralf

_______________________________________________
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to