Haskell Quiz/Sampling/Solution Kuklewicz
< Haskell Quiz | Sampling
This puzzle seems far too simple for the use of data structures or even monads. A single tail recursive helper function does the trick.
-- Linear solution by Chris Kuklewicz <haskell@list.mightyreason.com>
-- It is important to realize you are picking from the possible
-- combinations of the digits from 0 to (n-1). The probability that
-- an element is chosen is (r/n). This "rolls the dice" for each element
-- of the range in ascending order.
module Main where
import System.Random
import System(getArgs)
main = do [r,n] <- fmap (map read) getArgs
g <- newStdGen
mapM_ print (pick r n g)
pick :: Int -> Int -> StdGen -> [Int]
pick r n g | 0<=r && r<=n = pick' r n g 0
| otherwise = error "r must be between 0 and n"
where pick' 0 _ _ _ = []
pick' r n g1 i | r==n = [i..(i+n-1)]
| otherwise =
let (x,g2) = randomR (1,n) g1
in if x <= r
then i : (pick' (pred r) (pred n) g2 $! (succ i))
else pick' r (pred n) g2 $! (succ i)