Random Permutations
Ralf Hinze
ralf@informatik.uni-bonn.de
Thu, 6 Mar 2003 11:16:11 +0100
> Is there a library routine for random permutations?
>
> I didn't find any and did a quick hack, which works fine for my
> application (length of list < 100), but what would be a more
> elegant way?
>
> > permute :: StdGen -> [a] -> [a]
> > permute gen [] = []
> > permute gen xs = (head tl) : permute gen' (hd ++ tail tl)
> > where (idx, gen') = randomR (0,length xs - 1) gen
> > (hd, tl) = splitAt idx xs
I've attached some *old* code that generates a random permutation.
Hope it still works ...
Cheers, Ralf
----
%-------------------------------= --------------------------------------------
\section{Generate a random permutation}
%-------------------------------= --------------------------------------------
> module RandomPerm(
> randomPerm, randomPerms)
> where
> import Random
> import Int
> import Array
> import ST
% - - - - - - - - - - - - - - - = - - - - - - - - - - - - - - - - - - - - - - -
\subsection{Signature}
% - - - - - - - - - - - - - - - = - - - - - - - - - - - - - - - - - - - - - - -
> randomPerm :: (RandomGen g) => [a] -> g -> ([a], g)
> randomPerms :: (RandomGen g) => [a] -> g -> [[a]]
% - - - - - - - - - - - - - - - = - - - - - - - - - - - - - - - - - - - - - - -
\subsection{Implementation}
% - - - - - - - - - - - - - - - = - - - - - - - - - - - - - - - - - - - - - - -
For a list of length |n| we calculate a random number between |0| and
|n! - 1|. This random number is converted to the factorial number
system, see \cite[p.66]{Knu97Art2}. Recall that in this system a
sequence of `digits' $b_{n-1}\ldots b_0$ with $0 \leq b_i \leq i$
denotes the number $\sum_{i} b_i\cdot i!$ (note that $b_0$ is
necessarily $0$). This sequence is then used as a recipe for building
a random permutation: we exchange the elements at positions $i$ and
$i + b_i$ for $0 \leq i < n$.
> randomPerm as g = (permute num as, g')
> where (num, g') = generate (length as) g
> randomPerms as g = as' : randomPerms as g'
> where (as', g') = randomPerm as g
Generates a random number between |0| and |n! - 1| in the `factorial'
number system representation.
> generate :: (RandomGen g) => Int -> g -> ([Int], g)
> generate n g = (convert fs r, g')
> where (f : fs) = reverse (take (n + 1) (factorials 0 1))
> (r, g') = randomR (0, f - 1) g
Convert a number to a mixed-radix numeral (the radices are given as the
first argument).
> convert :: [Integer] -> Integer -> [Int]
> convert [] _n = [] -- |_n| should be |0|
> convert (f : fs) n = toInt q : convert fs r
> where (q, r) = divMod n f
The list of factorial numbers.
> factorials :: Int -> Integer -> [Integer]
> factorials i f = f : factorials (i + 1) (f * fromInt (i + 1))
Note that we have to call |factorial i f| such that |f| is |i!|.
The function |permute| permutes the given list according to the
`factorial' numeral.
> permute :: [Int] -> [a] -> [a]
> permute num as = runST (
> do { a <- newSTArray bs undefined;
> sequence_ [
> writeSTArray a i e
> | (i, e) <- zip is as ];
> sequence [
> swap a i (i + r)
> | (i, r) <- zip is num ];
> mapM (readSTArray a) is })
> where bs = (0, length as - 1)
> is = range bs
The operation |swap| exchanges two elements of a mutable array.
> swap :: (Ix ix) => STArray s ix a -> ix -> ix -> ST s ()
> swap a i j = do { x <- readSTArray a i;
> y <- readSTArray a j;
> writeSTArray a i y;
> writeSTArray a j x }