On 7/26/06, Sukit Tretriluxana <[EMAIL PROTECTED]> wrote:
Dear expert Haskellers,

I am a newbie to Haskell and try to write several algorithms with it. One of
them is the string permutation which generates all possible permutations
using the characters in the string. For example, if I say,

permute "abc"

It will return the the result as

 ["abc","acb","bca","bac","cab","cba"]

And here is the program I came up with.

 permute :: String -> [String]
permute str = rotate str len len
   where len = length str

rotate :: String -> Int -> Int -> [String]
rotate _ _ 0 = []
rotate s 1 _ = [s]
rotate (ch:chs) len rcnt =
   map (\x -> ch : x) (rotate chs (len-1) (len-1))
   ++
   rotate (chs ++ [ch]) len (rcnt-1)

I am more than certain that this simple program can be rewritten to be more
succinct and possibly more efficient using Haskell's features. So I would
like to ask if any of you would kindly show me an example.


I like the following definition for simplicity:

perms xs = [x:ps | x <- xs, ps <- perms (xs\\[x])]

It's all quite straightforward, basically take each item in the list,
compute the permutations of the *rest* of the list (i.e. remove the
item from the list) and then put the item in front.

Now, this is pretty inefficient, so let's do some basic algebra here.
Rather than computing the item/rest-of-list pairs in the list
comprhension itself, we first separate it into a function (doing the
exact same thing, for now).

perms xs = [x : ps | (y,ys) <- selections xs, ps <- perms ys]
selections xs = [(x,xs\\[x]) | x <- xs]

So now, this does the same thing. But rather than going through each
item (x) and then computing the rest of the list (x\\[x]) directly, we
simply write a function (selections) which does this for us (i.e.
returns a list of pairs of the item and the rest of the list).

Now, let's rewrite selections in a more efficient way:

selections []     = []
selections (x:xs) = (x,xs) : [(y,x:ys) | (y,ys) <- selections xs]

It's clear that the first (most straightforward) selection we can do
here here is the head and the tail of the list, (x,xs). Now we just
recursively compute the selections of the tail, and re-insert the head
in its rightful position at the front of the list part of each result.

So there you have it. A nice looking and fairly efficient way of
generating permutations, and the steps needed to come up with it.


/S
--

Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
_______________________________________________
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to