Generating the n! permutations in Haskell

Included below is a Haskell Program I wrote to generate the n! permutations of a set of n elements. There are comments that explain it throughout the program. Both of the algorithms that appear in the cut the knot site use assignment, so are not very suitable for Haskell. Regards, Shlomi Fish -- (gradual_transfer set empty_set) -- -- Gradually pops elements out of set and [1..5] pushes them into -- empty_set, -- and makes a list of both stacks in their intermediate phases. -- -- E.g: -- gradual_transfer [1 .. 5] [] = -- [([1,2,3,4,5],[]),([2,3,4,5],[1]),([3,4,5],[2,1]), -- ([4,5],[3,2,1]),([5],[4,3,2,1])] gradual_transfer :: [a] -> [a] -> [([a],[a])] -- I stop when the list contains a single element, not when it contains -- no elements at all. The reason for this is that gen_perms like it -- better -- this way, as it has no use of a zero element (a:as). gradual_transfer (a:[]) ps = [((a:[]),ps)] gradual_transfer (a:as) ps = ((a:as),ps):(gradual_transfer as (a:ps)) -- (dump ps as) is equivalent to (reverse ps) ++ as, only it should -- be much faster. dump :: [a] -> [a] -> [a] dump [] as = as dump (p:ps) as = dump ps (p:as) gen_perms :: [a] -> [[a]] gen_perms [] = [[]] gen_perms set = [ (a:rest) | (a:as,ps) <- (gradual_transfer set []), rest <- gen_perms(dump ps as) ] print_perms [] = return () print_perms (a:as) = do print a print_perms as main = print_perms (gen_perms [1 .. 8]) ---------------------------------------------------------------------- Shlomi Fish shlomif@vipe.technion.ac.il Home Page: http://t2.technion.ac.il/~shlomif/ Home E-mail: shlomif@iglu.org.il He who re-invents the wheel, understands much better how a wheel works.

Shlomi Fish wrote: | Included below is a Haskell Program I wrote to | generate the n! permutations of a set of n elements. Just to also share some programming idiom with you, I often find myself using the following function: selections :: [a] -> [(a,[a])] Given a list xs, it returns a list of pairs of the same length as xs, where each pair (y,ys) represents one "selection" from the list xs, i.e. an element from xs (y) and the rest (ys). Sadly, it is not a standard Haskell function (it should be! :-). Here is its implementation: selections [] = [] selections (x:xs) = (x,xs) : [ (y,x:ys) | (y,ys) <- selections xs ] Using this function, it is really easy to write a permutations function: permutations :: [a] -> [[a]] permutations xs = [ y : zs | (y,ys) <- selections xs , zs <- permutations ys ] My apologies if this thread now turns into a "here-is-my- favorite-way-to-do-permutations-discussion". /Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen Chalmers University, Gothenburg, Sweden.

I wrote: | permutations :: [a] -> [[a]] | permutations xs = | [ y : zs | | (y,ys) <- selections xs | , zs <- permutations ys | ] ... and of course my cut-and-paste technology produced a message that has a built-in find-the-missing-base-case puzzle! :-) /K
participants (2)
-
Koen Claessen
-
Shlomi Fish