Difference between revisions of "99 questions/Solutions/24"

From HaskellWiki
Jump to navigation Jump to search
(Undo revision 43086 by Blazedaces (Talk))
Line 31: Line 31:
 
</haskell>
 
</haskell>
 
(Note that this doesn't really solve the problem, since it doesn't generate ''distinct'' numbers).
 
(Note that this doesn't really solve the problem, since it doesn't generate ''distinct'' numbers).
 
Alternative solution producing ''distinct'' numbers:
 
<haskell>
 
import System.Random
 
import Control.Monad (replicateM)
 
 
diff_select :: Int -> Int -> IO [Int]
 
diff_select n m
 
| n <= 0 = return []
 
| otherwise = replicateM n $ getStdRandom $ randomR(1,m)
 
</haskell>
 

Revision as of 12:48, 20 November 2011

Lotto: Draw N different random numbers from the set 1..M.

import System.Random
diff_select :: Int -> Int -> IO [Int]
diff_select n to = diff_select' n [1..to]

diff_select' 0 _  = return []
diff_select' _ [] = error "too few elements to choose from"
diff_select' n xs = do r <- randomRIO (0,(length xs)-1)
                       let remaining = take r xs ++ drop (r+1) xs
                       rest <- diff_select' (n-1) remaining
                       return ((xs!!r) : rest)

The random numbers have to be distinct!

In order to use randomRIO here, we need import module System.Random.

As can be seen, having implemented problem 23, rnd_select, the solution is trivial.

diff_select n to = rnd_select [1..to] n

Alternative solution:

diffSelect :: Int -> Int -> IO [Int]
diffSelect n m = do
  gen <- getStdGen
  return . take n $ randomRs (1, m) gen

(Note that this doesn't really solve the problem, since it doesn't generate distinct numbers).