[Haskell-beginners] randomize the order of a list

Daniel Fischer daniel.is.fischer at web.de
Fri Aug 27 16:36:32 EDT 2010


On Friday 27 August 2010 22:02:59, Gaius Hammond wrote:
> Hi all,
>
>
>
> 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. I am using a function to generate random
> numbers in the State monad as follows:
>
>
>
> randInt∷  Int →  State StdGen Int
> randInt x = do g ←  get
>                 (v,g') ←  return $ randomR (0, x) g

value <- return $ expression

is always awkward. Bind it with a let:

let value = expression

>                 put g'
>                 return v

Here, it would be simpler to just write

randInt x = State $ randomR (0,x)

>
>
>
> This is pretty much straight from the documentation. My function for
> the new indexes is:
>
>
>
> -- return a list of numbers 0 to x-1 in random
> order
> randIndex∷ Int → StdGen → ([Int], StdGen)
> randIndex x = runState $ do
>      let randIndex' acc r
>
>              | (length acc ≡ x) = acc

If you need many random values, it would be faster to pass the number of 
values you still require as a parameter, that avoids traversing the list to 
get its length in each step.

>              | (r `elem` acc) ∨ (r ≡  (−1)) = do

You will get a skewed distribution of shuffles that way, that may or may 
not be a problem.

>
>                  r' ← randInt (x − 1)
>                  randIndex' acc r'
>
>              | otherwise = do
>
>                  r' ← randInt (x − 1)
>                  randIndex' r:acc r'

This is parsed as

            (randIndex' r) : (acc r')

, remember, function application binds tightest.

So the compiler sees a list and infers the type [a] for this do-block. Thus 
it would require (randInt x) to be a list too, of type [b]. However, it is 
of type (State StdGen Int).

You need parentheses around the list pattern:

        randIndex' (r:acc) r'


>          in
>          randIndex' [] (−1)
>
>
>
> This fails to compile on
>
>
>
>
>     Couldn't match expected type `[a]'
>             against inferred type `State StdGen b'
>      In a stmt of a 'do' expression: r' <- randInt (x - 1)
>      In the expression:
>          do { r' <- randInt (x - 1);
>               randIndex' acc r' }
>
>
>
>
> I can see what's happening here - it's treating randIndex' as the
> second argument to randInt instead of invisibly putting the State in
> there. Or am I going about this completely the wrong way?
>
>
> Thanks,
>
>
>
> G



More information about the Beginners mailing list