randomize the order of a list

Gaius Hammond wrote:
I am trying to randomly reorder a list (e.g. shuffle a deck of cards) . My initial approach is to treat it as an array, generate a list of unique random numbers between 0 and n - 1, then use those numbers as new indexes.
Felipe Lessa wrote:
Note: you could use random-shuffle package [1].
Heinrich Apfelmus wrote:
For another approach, see also
http://apfelmus.nfshost.com/articles/random-permutations.html
Thanks for the link apfelmus, it's fairly interesting. The key to making it work is the weighting of lists during merging based on their lengths. I wonder if other sort algorithm can be adapted in such a way, while preserving uniformity. Quicksort for example : is it enough to choose the result position of the pivot randomly, and then placing elements on either side with a probability of 1/2 ? There is another sort-based approach that is probably less elegant, but simpler in the sense that you don't have to rewrite your sorting routines : pick random "weights" for each of your elements, and sort the list based on the weights. This approach has been studied and criticized by [Oleg], whose analysis is the base of the random-shuffle package. Oleg rightly points out that this method does not achieve uniformity in general. What he failed to notice is that there is a simple workaround to regain uniformity with minimal changes. [Oleg] http://okmij.org/ftp/Haskell/perfect-shuffle.txt The uniformity breaker is the case were two elements get equal weights. In his example, weights for a 2-size lists are choosed in {0, 1}. In the two corner case were both elements get picked the same weight, the sorting routine make an arbitrary choice : for example, if it is stable, it will put first the element occuring sooner in the list. This arbitrary choice breaks uniformity. The workaround is simple : pick weights that are all differents. If the weights are picked among [1, n] were n is the size of the list, it is difficult and inneficient to generate a list of unique random numbers. But you can choose weights in arbitrary intervals. The bigger it is, the smaller the chance you have to pick weights again becomes (though due to the birthday paradox, it does not decrease that fast). To sum it up, here is the algorithm to shuffle a list : - for each element in the list, pick a random list - pick another weight list while two equal weights were picked - once you've picked *unique* weights, shuffle the elements of the list by comparing their weights If the weight are taken in a big enough interval (say [1, 2^64]), the average number of repicks necessary is small enough for this algorithm to be just a sorting using your preferred algorithm. I haven't went through the trouble of computing the necessary interval bound to get a small enough chance of conflict, but I believe the forth power of the size of the list should be enough. An even better technique is to use lazy lists of {0, 1} (representing real numbers) as weights, with each list element lazily randomly computed. You are sure than no two such lists are equal (they're different with probability 1). This amounts to a dynamical random refining of weights during the sorting : "two of my real number weights are equal at granularity 2^-N ? Let's make a random choice so that their {N-1}th digit is different !"

Thanks everyone! As always with Haskell, it's surprising how easy it is when you know how :-) G On 30 Aug 2010, at 10:14, Gabriel Scherer wrote:
Gaius Hammond wrote:
I am trying to randomly reorder a list (e.g. shuffle a deck of cards) . My initial approach is to treat it as an array, generate a list of unique random numbers between 0 and n - 1, then use those numbers as new indexes.
Felipe Lessa wrote:
Note: you could use random-shuffle package [1].
Heinrich Apfelmus wrote:
For another approach, see also
http://apfelmus.nfshost.com/articles/random-permutations.html
Thanks for the link apfelmus, it's fairly interesting. The key to making it work is the weighting of lists during merging based on their lengths. I wonder if other sort algorithm can be adapted in such a way, while preserving uniformity. Quicksort for example : is it enough to choose the result position of the pivot randomly, and then placing elements on either side with a probability of 1/2 ?
There is another sort-based approach that is probably less elegant, but simpler in the sense that you don't have to rewrite your sorting routines : pick random "weights" for each of your elements, and sort the list based on the weights. This approach has been studied and criticized by [Oleg], whose analysis is the base of the random-shuffle package. Oleg rightly points out that this method does not achieve uniformity in general. What he failed to notice is that there is a simple workaround to regain uniformity with minimal changes.
[Oleg] http://okmij.org/ftp/Haskell/perfect-shuffle.txt
The uniformity breaker is the case were two elements get equal weights. In his example, weights for a 2-size lists are choosed in {0, 1}. In the two corner case were both elements get picked the same weight, the sorting routine make an arbitrary choice : for example, if it is stable, it will put first the element occuring sooner in the list. This arbitrary choice breaks uniformity.
The workaround is simple : pick weights that are all differents. If the weights are picked among [1, n] were n is the size of the list, it is difficult and inneficient to generate a list of unique random numbers. But you can choose weights in arbitrary intervals. The bigger it is, the smaller the chance you have to pick weights again becomes (though due to the birthday paradox, it does not decrease that fast).
To sum it up, here is the algorithm to shuffle a list :
- for each element in the list, pick a random list - pick another weight list while two equal weights were picked - once you've picked *unique* weights, shuffle the elements of the list by comparing their weights
If the weight are taken in a big enough interval (say [1, 2^64]), the average number of repicks necessary is small enough for this algorithm to be just a sorting using your preferred algorithm. I haven't went through the trouble of computing the necessary interval bound to get a small enough chance of conflict, but I believe the forth power of the size of the list should be enough.
An even better technique is to use lazy lists of {0, 1} (representing real numbers) as weights, with each list element lazily randomly computed. You are sure than no two such lists are equal (they're different with probability 1). This amounts to a dynamical random refining of weights during the sorting : "two of my real number weights are equal at granularity 2^-N ? Let's make a random choice so that their {N-1}th digit is different !"

Gabriel Scherer wrote:
Heinrich Apfelmus wrote:
For another approach, see also
http://apfelmus.nfshost.com/articles/random-permutations.html
Thanks for the link apfelmus, it's fairly interesting. The key to making it work is the weighting of lists during merging based on their lengths. I wonder if other sort algorithm can be adapted in such a way, while preserving uniformity. Quicksort for example : is it enough to choose the result position of the pivot randomly, and then placing elements on either side with a probability of 1/2 ?
Interesting question! Adapting quick sort is not that easy, though. First, you can skip choosing the pivot position because it is already entailed by the choices of elements left and right to it. Second, probability 1/2 won't work, it doesn't give a uniform distribution. In order to get that, the remaining input xs has to be partitioned into two lists xs = (ls,rs) such that probability that length ys == k is 1/(n `over` k) where n `over` k = n! / (k! * (n-k)!) is the binomial coefficient. After all, calling "quickrandom" recursively on each of the two lists will give two permutations with probability 1/k! and 1/(n-k)! and the probability for a compound permutation is 1/(n `over` k) * 1/k! * 1/(n-k)! = 1/n! as desired. In contrast, distributing elements with probability 1/2 would give probability that length ys == k is (n `over` k) * 2^(-n) which would skew the distribution heavily towards permutations where the pivot element is in the middle. However, it is possible to divide the list properly, though I haven't worked out the exact numbers. The method would be divide (x:xs) = do (ls,rs) <- divide xs random <- uniform (0, 1) :: Random Double if random <= p (length xs) (length ls) then return (x:ls, rs) else return (ls, x:rs) where the probability p of putting the element x into the left part has to be chosen such that 1/(n `over` k) = 1/(n-1 `over` k-1) * p (n-1) (k-1) + 1/(n-1 `over` k ) * (1 - p (n-1) k) Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

Gabriel Scherer wrote:
Thanks for the link apfelmus, it's fairly interesting. The key to making it work is the weighting of lists during merging based on their lengths. I wonder if other sort algorithm can be adapted in such a way, while preserving uniformity. Quicksort for example : is it enough to choose the result position of the pivot randomly, and then placing elements on either side with a probability of 1/2 ?
to which Heinrich Apfelmus answered:
Interesting question! Adapting quick sort is not that easy, though.
First, you can skip choosing the pivot position because it is already entailed by the choices of elements left and right to it.
I don't think this is true...
Second, probability 1/2 won't work, it doesn't give a uniform distribution.
... because of this. In fact, it appears to me that the proposed modification to quicksort is uniform and simple. Why do you think otherwise? Cheers, John

John Dorsey wrote:
Gabriel Scherer wrote:
Thanks for the link apfelmus, it's fairly interesting. The key to making it work is the weighting of lists during merging based on their lengths. I wonder if other sort algorithm can be adapted in such a way, while preserving uniformity. Quicksort for example : is it enough to choose the result position of the pivot randomly, and then placing elements on either side with a probability of 1/2 ?
to which Heinrich Apfelmus answered:
Interesting question! Adapting quick sort is not that easy, though.
First, you can skip choosing the pivot position because it is already entailed by the choices of elements left and right to it.
I don't think this is true...
Second, probability 1/2 won't work, it doesn't give a uniform distribution.
.... because of this.
In fact, it appears to me that the proposed modification to quicksort is uniform and simple. Why do you think otherwise?
Why should it be uniform just because it looks nice? Looks can be deceiving, you need a mathematical proof to be certain. Embarrassingly, the analysis in my previous message is wrong, though. Here an actually correct assessment of the algorithm. Or rather, of the two algorithms; the results are different depending on whether you use a pivot *element* or just a pivot *position*. It will turn out that the former is not uniform, while, to my surprise, the latter is uniform! Let's being with some code for the algorithms, so we know what exactly we are analyzing here. First, the partition function which divides a list into two parts where each element has a chance of 1/2 of landing in either part: partition :: [a] -> Random ([a],[a]) partition = go ([],[]) where go (ls,rs) [] = return (ls,rs) go (ls,rs) (x:xs) = do b <- uniform [True,False] -- flip a coin if b then go (x:ls,rs) xs -- element goes left else go (ls,x:rs) xs -- element goes right Now, algorithm A which puts the pivot element between the two parts: quickshuffleA :: [a] -> Random [a] quickshuffleA [] = return [] quickshuffleA [x] = return [x] quickshuffleA (x:xs) = do (ls, rs) <- partition xs sls <- quickshuffleA ls srs <- quickshuffleA rs return (sls ++ [x] ++ srs) And then algorithm B which splits the list into two parts without putting a pivot element in between. quickshuffleB :: [a] -> Random [a] quickshuffleB [] = return [] quickshuffleB [x] = return [x] quickshuffleB xs = do (ls, rs) <- partition xs sls <- quickshuffleB ls srs <- quickshuffleB rs return (sls ++ srs) Note that algorithm B does not necessarily terminate, since it repeats itself if ls or rs become empty by chance! Analysis of algorithm A: Imagine the course of the algorithm from beginning to end. We want to keep track of the set P of permutations that are still possible as outcomes during each step. Before the algorithm starts, every permutation is still possible. Then, for the first call of partition , imagine that the set of possible permutations is divided into 2^(n-1) disjoint classes of the form l x rrr...rr l x rrr...rr -- different l than the previous one ... ll x rr...rr ... lll x r...rr ... lll...ll x r where the l and r denote elements from the parts ls and rs respectively. The call to the partition function picks one of these classes at random, with a uniform distribution. However, the problem is that these classes contain different amounts of permutations! Namely, the class ll..ll x rr..rr k elements on the left n-1-k elements on the right contains k! * (n-1-k)! permutations. So, to be uniform, the partition function would have to return each class with a probability proportional to its size. But this is not the case, so algorithm A cannot return of a uniform distribution of permutations. Another way to convince yourself of the non-uniformity of algorithm A is to actually calculate the distribution for small n by using one of the probabilistic functional programming packages on Hackage: http://hackage.haskell.org/package/ProbabilityMonads http://hackage.haskell.org/package/probability Analysis of algorithm B: As before, we can imagine that the first call partition splits the set of possible permutations into 2^n classes. But this time, the classes are no longer disjoint, so the previous analysis does not apply! Without the pivot element, the situation has become much more symmetric, though, and that's the reason why algorithm B gives a uniform distribution. In particular, imagine that we somehow manage to calculate the probability that quickshuffleB [1,2,3,4] will return the trivial permutation [1,2,3,4] (we will perform that calculation in a moment, too). But since the algorithm is highly symmetric, the same calculation also applies to, say, the permutation [3,4,1,2], and all the other permutation as well! For instance, for the result [1,2,3,4], we had to consider the case ls = [1,2] ; but this case corresponds to the case ls = [3,4] which appears in the calculation for the result [3,4,1,2]. Hence, all outcomes have equal probability. Let's calculate this from first principles as well, i.e. let p be the probability, that the result is the permutation [1,2,3,4]. This is only possible if first call to partition gives one of the following five results: ls = [], ls = [1], ls = [1,2], ls = [1,2,3], ls = [1,2,3,4] By mathematical induction, we can assume that smaller inputs like quickshuffle [1,2,3] give a uniform distribution. Then, the probability of the outcome [1,2,3,4] in each of the five cases is ls = [] => probability 2^(-4) * 1/0! * p ls = [1] => probability 2^(-4) * 1/1! * 1/3! ls = [1,2] => probability 2^(-4) * 1/2! * 1/2! ls = [1,2,3] => probability 2^(-4) * 1/3! * 1/1! ls = [1,2,3,4] => probability 2^(-4) * p * 1/0! and their sum is p = 2^(-4) * (1/0!*p + 1/1!*1/3! + 1/2!*1/2! + 1/3!*1/1! + p*1/0!) = 2^(-n) * ( sum [1/k!*1/(n-k)! | k<-[0..n]] + 2*(p - 1/n!) ) Expressing the factorials in terms of binomial coefficients and applying the binomial theorem, we can see that the sum is equal to 2^n / n! and we obtain p = 1/n! + 2^(-n)*2*(p - 1/n!) This implies that p - 1/n! = 0, i.e. p = 1/n! as desired. Furthermore, the calculation does not depend on the fact that we were considering the trivial permutation [1,2,3,4]. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

Heinrich Apfelmus wrote:
Why should it be uniform just because it looks nice? Looks can be deceiving, you need a mathematical proof to be certain.
My claim was that it is "uniform and simple"; naturally neither follows from the other, but each has merit.
Embarrassingly, the analysis in my previous message is wrong, though. Here an actually correct assessment of the algorithm. Or rather, of the two algorithms; the results are different depending on whether you use a pivot *element* or just a pivot *position*. It will turn out that the former is not uniform, while, to my surprise, the latter is uniform!
And this was my point. I never considered a pivot *element*, which you correctly point out wouldn't work so well. I was referring to a pivot taken from a randomly chosen *position*. On re-reading Gabriel Scherer's original musing:
Thanks for the link apfelmus, it's fairly interesting. The key to making it work is the weighting of lists during merging based on their lengths. I wonder if other sort algorithm can be adapted in such a way, while preserving uniformity. Quicksort for example : is it enough to choose the result position of the pivot randomly, and then placing elements on either side with a probability of 1/2 ?
I may have misunderstood his original intent, as he refers to a random "result position" for a pivot (chosen how?). But if that's changed to choosing the pivot from a random position, then it works out nicely. I think you agree with this later in your email. And finally, re-reading your earlier comment:
First, you can skip choosing the pivot position because it is already entailed by the choices of elements left and right to it.
I think I understand now what you were referring to... (redundantly) choosing the destination for a pivot chosen by some other unspecified means. It seems we were talking beside each other; I'm sorry if I misunderstood you earlier. Cheers, John Dorsey

John Dorsey wrote:
Heinrich Apfelmus wrote:
Embarrassingly, the analysis in my previous message is wrong, though. Here an actually correct assessment of the algorithm. Or rather, of the two algorithms; the results are different depending on whether you use a pivot *element* or just a pivot *position*. It will turn out that the former is not uniform, while, to my surprise, the latter is uniform!
And this was my point. I never considered a pivot *element*, which you correctly point out wouldn't work so well. I was referring to a pivot taken from a randomly chosen *position*. On re-reading Gabriel Scherer's original musing:
Thanks for the link apfelmus, it's fairly interesting. The key to making it work is the weighting of lists during merging based on their lengths. I wonder if other sort algorithm can be adapted in such a way, while preserving uniformity. Quicksort for example : is it enough to choose the result position of the pivot randomly, and then placing elements on either side with a probability of 1/2 ?
I may have misunderstood his original intent, as he refers to a random "result position" for a pivot (chosen how?). But if that's changed to choosing the pivot from a random position, then it works out nicely. I think you agree with this later in your email.
And finally, re-reading your earlier comment:
First, you can skip choosing the pivot position because it is already entailed by the choices of elements left and right to it.
I think I understand now what you were referring to... (redundantly) choosing the destination for a pivot chosen by some other unspecified means.
It probably helps to write down some code for the different possibilities. :) * Pivot element, position chosen by a dice roll. This is closest to quicksort in spirit. quickshuffle (x:xs) = do k <- uniform [0..length xs] (ls,rs) <- partition k xs -- satisfies length ls == k sls <- quickshuffle ls srs <- quickshuffle rs return (ls ++ [x] ++ rs) * Pivot element, position fixed. This is Gabriel's solution. quickshuffle (x:xs) = do let k = length xs `div` 2 (ls,rs) <- partition k xs -- satisfies length ls == k sls <- quickshuffle ls srs <- quickshuffle rs return (ls ++ [x] ++ rs) * Pivot element, position entailed by the random partition. quickshuffle (x:xs) = do (ls,rs) <- partition xs sls <- quickshuffle ls srs <- quickshuffle rs return (ls ++ [x] ++ rs) * Pivot position, chosen by a dice roll. The arguments to the recursive calls to quickshuffle are no longer guaranteed to be smaller; the algorithm might run for an arbitrarily long time. quickshuffle xs = do k <- uniform [0..length xs] (ls,rs) <- partition k xs -- satisfies length ls == k sls <- quickshuffle ls srs <- quickshuffle rs return (ls ++ rs) * Pivot position, entailed by the random partition. This is the only algorithm where picking elements to the left or the right with probability 1/2 gives a uniform permutation. Same problem with potentially arbitrarily long running times, though. quickshuffle xs = do (ls,rs) <- partition xs sls <- quickshuffle ls srs <- quickshuffle rs return (ls ++ rs) The partition functions needed to get permutations with uniform probability are quite different for the different algorithms. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

I must apologize : a part of my post about quicksort didn't make sense : if one choose the pivot position randomly, elements shouldn't be splitted with even probability, because there would be no control over the size of the results list. If I understand it correctly, your solution doesn't pick a pivot position, but dynamically adapt list size probabilities during traversal. I have a different solution, that pick a pivot position, then choose the elements with carefully weighted probability to get the right left-hand and right-hand sizes. The key idea comes from your analysis (more precisely, from the presence of the n `over` k probabilities) : for a given k (the pivot), choose a random subset of k elements as the left-hand side of the pivot. import Random (Random, StdGen, randomRIO) import Control.Monad (liftM) quickshuffle :: [a] -> IO [a] quickshuffle [] = return [] quickshuffle [x] = return [x] quickshuffle xs = do (ls, rs) <- partition xs sls <- quickshuffle ls srs <- quickshuffle rs return (sls ++ srs) -- The idea is that to partition a list of length n, we choose a pivot -- position randomly (1 < k < n), then choose a subset of k elements -- in the list to be on the left side, and the other n-k on the right -- side. -- -- To choose a random subset of length k among n, scan the list and -- add each element with probability -- (number of elements left to pick) / (number of elements left to scan) -- partition :: [a] -> IO ([a], [a]) partition xs = do let n = length xs k <- randomRIO (1, n-1) split n k ([], []) xs where split n k (ls, rs) [] = return (ls, rs) split n k (ls, rs) (x:xs) = do p <- randomRIO (1, n) if p <= k then split (n - 1) (k - 1) (x:ls, rs) xs else split (n - 1) k (ls, x:rs) xs I have also written an implementation for my former algorithm : import Data.List (mapAccumL, sortBy) import System.Random (RandomGen, split, randoms) import Data.Ord (Ordering) import Data.Function (on) -- compare two real numbers as infinite sequences of booleans real_cmp :: [Bool] -> [Bool] -> Ordering real_cmp (True:_) (False:_) = LT real_cmp (False:_) (True:_) = GT real_cmp (_:xs) (_:ys) = real_cmp xs ys -- weight each element with a random real number weight_list :: RandomGen g => g -> [a] -> [([Bool], a)] weight_list g = snd . mapAccumL weight g where weight g x = let (g1, g2) = split g in (g1, (randoms g2, x)) -- shuffle by sorting on weights shuffle :: RandomGen g => g -> [a] -> [a] shuffle g = map snd . sort_on_weights . weight_list g where sort_on_weights = sortBy (real_cmp `on` fst)
Interesting question! Adapting quick sort is not that easy, though.
First, you can skip choosing the pivot position because it is already entailed by the choices of elements left and right to it.
Second, probability 1/2 won't work, it doesn't give a uniform distribution. In order to get that, the remaining input xs has to be partitioned into two lists xs = (ls,rs) such that
probability that length ys == k is 1/(n `over` k)
where
n `over` k = n! / (k! * (n-k)!)
is the binomial coefficient. After all, calling "quickrandom" recursively on each of the two lists will give two permutations with probability 1/k! and 1/(n-k)! and the probability for a compound permutation is
1/(n `over` k) * 1/k! * 1/(n-k)! = 1/n!
as desired. In contrast, distributing elements with probability 1/2 would give
probability that length ys == k is (n `over` k) * 2^(-n)
which would skew the distribution heavily towards permutations where the pivot element is in the middle.
However, it is possible to divide the list properly, though I haven't worked out the exact numbers. The method would be
divide (x:xs) = do (ls,rs) <- divide xs random <- uniform (0, 1) :: Random Double if random <= p (length xs) (length ls) then return (x:ls, rs) else return (ls, x:rs)
where the probability p of putting the element x into the left part has to be chosen such that
1/(n `over` k) = 1/(n-1 `over` k-1) * p (n-1) (k-1) + 1/(n-1 `over` k ) * (1 - p (n-1) k)
Regards, Heinrich Apfelmus

A small remark I forgot.
First, It seems to me that the choice of k need not be random, but
only arbitrary. I believe that any fixed k would work. In particular,
it is interesting to compare this algorithm with k = n/2, and Heinrich
Apfelmus's algorithm based on mergesort (
http://apfelmus.nfshost.com/articles/random-permutations.html ):
- mergeshuffle split the unshuffled list directly, shuffle each part,
then merge them carefully
- quickshuffle split the unshuffled list carefully, shuffle each part,
then merge them directly
mergeshuffle's `merge` and quickshuffle's `split` are very similar
and, in a sense, dual.
`merge` reason on the probability (number of elements in the left list
to merge) / (total number of elements to merge)
`split` reason on the probability (number of elements left to put in
the left list) / (total number of elements left to split)
On Thu, Sep 2, 2010 at 3:34 PM, Gabriel Scherer
I must apologize : a part of my post about quicksort didn't make sense : if one choose the pivot position randomly, elements shouldn't be splitted with even probability, because there would be no control over the size of the results list.
If I understand it correctly, your solution doesn't pick a pivot position, but dynamically adapt list size probabilities during traversal.
I have a different solution, that pick a pivot position, then choose the elements with carefully weighted probability to get the right left-hand and right-hand sizes. The key idea comes from your analysis (more precisely, from the presence of the n `over` k probabilities) : for a given k (the pivot), choose a random subset of k elements as the left-hand side of the pivot.
import Random (Random, StdGen, randomRIO) import Control.Monad (liftM)
quickshuffle :: [a] -> IO [a] quickshuffle [] = return [] quickshuffle [x] = return [x] quickshuffle xs = do (ls, rs) <- partition xs sls <- quickshuffle ls srs <- quickshuffle rs return (sls ++ srs)
-- The idea is that to partition a list of length n, we choose a pivot -- position randomly (1 < k < n), then choose a subset of k elements -- in the list to be on the left side, and the other n-k on the right -- side. -- -- To choose a random subset of length k among n, scan the list and -- add each element with probability -- (number of elements left to pick) / (number of elements left to scan) -- partition :: [a] -> IO ([a], [a]) partition xs = do let n = length xs k <- randomRIO (1, n-1) split n k ([], []) xs where split n k (ls, rs) [] = return (ls, rs) split n k (ls, rs) (x:xs) = do p <- randomRIO (1, n) if p <= k then split (n - 1) (k - 1) (x:ls, rs) xs else split (n - 1) k (ls, x:rs) xs
I have also written an implementation for my former algorithm :
import Data.List (mapAccumL, sortBy) import System.Random (RandomGen, split, randoms) import Data.Ord (Ordering) import Data.Function (on) -- compare two real numbers as infinite sequences of booleans real_cmp :: [Bool] -> [Bool] -> Ordering real_cmp (True:_) (False:_) = LT real_cmp (False:_) (True:_) = GT real_cmp (_:xs) (_:ys) = real_cmp xs ys -- weight each element with a random real number weight_list :: RandomGen g => g -> [a] -> [([Bool], a)] weight_list g = snd . mapAccumL weight g where weight g x = let (g1, g2) = split g in (g1, (randoms g2, x)) -- shuffle by sorting on weights shuffle :: RandomGen g => g -> [a] -> [a] shuffle g = map snd . sort_on_weights . weight_list g where sort_on_weights = sortBy (real_cmp `on` fst)
Interesting question! Adapting quick sort is not that easy, though.
First, you can skip choosing the pivot position because it is already entailed by the choices of elements left and right to it.
Second, probability 1/2 won't work, it doesn't give a uniform distribution. In order to get that, the remaining input xs has to be partitioned into two lists xs = (ls,rs) such that
probability that length ys == k is 1/(n `over` k)
where
n `over` k = n! / (k! * (n-k)!)
is the binomial coefficient. After all, calling "quickrandom" recursively on each of the two lists will give two permutations with probability 1/k! and 1/(n-k)! and the probability for a compound permutation is
1/(n `over` k) * 1/k! * 1/(n-k)! = 1/n!
as desired. In contrast, distributing elements with probability 1/2 would give
probability that length ys == k is (n `over` k) * 2^(-n)
which would skew the distribution heavily towards permutations where the pivot element is in the middle.
However, it is possible to divide the list properly, though I haven't worked out the exact numbers. The method would be
divide (x:xs) = do (ls,rs) <- divide xs random <- uniform (0, 1) :: Random Double if random <= p (length xs) (length ls) then return (x:ls, rs) else return (ls, x:rs)
where the probability p of putting the element x into the left part has to be chosen such that
1/(n `over` k) = 1/(n-1 `over` k-1) * p (n-1) (k-1) + 1/(n-1 `over` k ) * (1 - p (n-1) k)
Regards, Heinrich Apfelmus

Gabriel Scherer wrote:
I must apologize : a part of my post about quicksort didn't make sense : if one choose the pivot position randomly, elements shouldn't be splitted with even probability, because there would be no control over the size of the results list.
No worries, my statement about the probability of the length of the left part being k doesn't make sense, either, since the probabilities 1/(n `over` k) don't even add up to a total of one. What is clear is that there is no *a priori* reason that 1/2 should work.
If I understand it correctly, your solution doesn't pick a pivot position, but dynamically adapt list size probabilities during traversal.
Yes. Note, however, that I intended to pick a pivot *element*, i.e. an element which, just like in ordinary quick sort, will not be permuted subsequently. This is subtly different from a pivot *position* that divides the list into two parts but has no element associated to it. I think this is important when trying to analyze the naive 1/2 scheme, but it's immaterial in your proposal:
I have a different solution, that pick a pivot position, then choose the elements with carefully weighted probability to get the right left-hand and right-hand sizes. The key idea comes from your analysis (more precisely, from the presence of the n `over` k probabilities) : for a given k (the pivot), choose a random subset of k elements as the left-hand side of the pivot.
import Random (Random, StdGen, randomRIO) import Control.Monad (liftM)
quickshuffle :: [a] -> IO [a] quickshuffle [] = return [] quickshuffle [x] = return [x] quickshuffle xs = do (ls, rs) <- partition xs sls <- quickshuffle ls srs <- quickshuffle rs return (sls ++ srs)
-- The idea is that to partition a list of length n, we choose a pivot -- position randomly (1 < k < n), then choose a subset of k elements -- in the list to be on the left side, and the other n-k on the right -- side. -- -- To choose a random subset of length k among n, scan the list and -- add each element with probability -- (number of elements left to pick) / (number of elements left to scan) -- partition :: [a] -> IO ([a], [a]) partition xs = do let n = length xs k <- randomRIO (1, n-1) split n k ([], []) xs where split n k (ls, rs) [] = return (ls, rs) split n k (ls, rs) (x:xs) = do p <- randomRIO (1, n) if p <= k then split (n - 1) (k - 1) (x:ls, rs) xs else split (n - 1) k (ls, x:rs) xs
Yes, this algorithm should work. Of course, while the probability (number of elements left to pick) / (number of elements left to scan) for picking an element x seems to be the only sensible choice, one still has to prove that this gives a uniform distribution. (Embarrassingly, my article about "merge shuffle" lacks a proof, too, I plan to rewrite it at some point.) Proving uniformity proceeds in two steps: First, we have to argue that picking the first k elements uniformly and then permuting them does give a uniform *total* permutation. This is fairly obvious, though. Namely, the set of possible permutations of n elements can be partitioned into (n `over` k) classes, where two permutations belong to the same class if they have the same first k elements (in any order). For instance, k = 3, n = 5 [1,2,3,5,4] is the same class as [3,2,1,4,5] because the first k elements are {1,2,3} [1,2,3,5,4] is in a different class than [4,2,1,3,5] because the first k elements are {1,2,3} and {1,2,4} resp. Now, to pick a random permutation, we first pick a class at random and then pick a permutation from this class. The point is that for reasons of symmetry, all classes have the same size! Namely, there are k! * (n-k)! permutations in every class. That means we should pick the class with uniform probability, and that's exactly what the split function intends to do. Second, we have to argue that split does indeed pick a class (= a set of k elements) *uniformly*. The reasoning for that is as follows: Consider a particular element x . There are (n-1 `over` k-1) classes that contain x (n-1 `over` k ) classes that don't contain x (This correctly adds up to (n `over` k) classes in total). Hence, the probability that the class contains x is classes with x / total classes = (n-1 `over` k-1) / (n `over` k) = ( (n-1)! / ((k-1)!(n-k)!) ) / ( n! / (k!(n-k)!) ) = (n-1)! / n! * k! / (k-1)! = k / n = elements left to pick / elements left to scan This shows that split does indeed use the correct probability for including x . Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com
participants (4)
-
Gabriel Scherer
-
Gaius Hammond
-
Heinrich Apfelmus
-
John Dorsey