Random shuffle
The problem
Shuffling a list, i.e. creating a random permutation, is not easy to do correctly. Each permutation should have the same probability.
Imperative algorithm
The standard imperative algorithm can be implemented as follows:
{-# LANGUAGE ScopedTypeVariables #-}
import System.Random
import Data.Array.IO
import Control.Monad
-- | Randomly shuffle a list
-- /O(N)/
shuffle :: forall a. [a] -> IO [a]
shuffle xs = do
let n = length xs
ar <- newListArray (1,n) xs :: IO (IOArray Int a)
forM [1..n] $ \i -> do
j <- randomRIO (i,n)
vi <- readArray ar i
vj <- readArray ar j
writeArray ar j vi
return vj
This is a lot simpler than the purely functional algorithm linked below.