I've abeen recommended on good authority(my son, a Cambridge Pure maths graduate, and Perl/Haskell expert) , and backed by a Google search that Fisher-Yates shuffle is the  one to use, as it produces total unbiased results with every combination equally possible. 
As with most things with computers,don't reinvent the eheel, it's almost certainly been done before by someone brighter that you, Fisher,Yates. & Knuth!
--
Andrew Smith B.Sc(Hons),MBA
Edinburgh,Scotland


On 27 August 2010 21:02, Gaius Hammond <gaius@gaius.org.uk> 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
              put g'
              return v



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
           | (r `elem` acc) ∨ (r ≡  (−1)) = do
               r' ← randInt (x − 1)
               randIndex' acc r'
           | otherwise = do
               r' ← randInt (x − 1)
               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




_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners