[Haskell] String permutation

CHA Reeseo reeseo at korea.ac.kr
Wed Jul 26 03:06:43 EDT 2006


On Wednesday 26 July 2006 13:44, Sukit Tretriluxana 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.

Sorry for my rough English.

How about this?  This is just ANOTHER way which is not so
succincter or more efficient than yours.  :)

(.^) = (.) . (.)	-- (.^) uf bf x y = uf (bf x y)
(.^^) = (.) . (.) . (.)	-- (.^^) uf tf x y z = uf (tf x y z)
(^.) = (.) . flip (.)	-- (^.) f g = (. f) . g

shuffle :: [a] -> [[a]]
shuffle []	= [[]]
shuffle (x:xs)	= concatMap (insertAll x) (shuffle xs) where
	insertAll :: a -> [a] -> [[a]]
	insertAll e []		= [[e]]
	insertAll e (x:xs)	= (e:x:xs) : map (x:) (insertAll e xs)

combine, permute :: [a] -> Integer -> [[a]]
combine _ r | r < 0	= error "Zero or more elements should be extracted."
combine _ 0		= [[]]
combine [] _		= []
combine (x:xs) r	= map (x:) (combine xs (r - 1)) ++ combine xs r
permute = concatMap shuffle .^ combine

Please note that I'm using different names from yours.
The function "shuffle" above means so-called "full shuffle"
which may be similar to your "permute" function,
and my "combine" and "permute" generate all the cases of
nCr and nPr, respectively.

-- 
CHA Reeseo
http://www.reeseo.net/
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 198 bytes
Desc: not available
Url : http://www.haskell.org//pipermail/haskell/attachments/20060726/8a757ad3/attachment.bin


More information about the Haskell mailing list