Haskell Quiz/Sampling/Solution Dolio

From HaskellWiki
< Haskell Quiz‎ | Sampling
Revision as of 11:09, 27 October 2006 by Dolio (talk | contribs) (creation)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search


This is a somewhat naive algorithm, but it manages to run the challenge problem in a reasonable amount of time. It simply uses the IntSet data structure, testing and adding random numbers until enough are found.

module Main where
import qualified Data.IntSet as I
import System
import System.Random

build n k s (r:rs)
    | k `seq` s `seq` False = undefined -- strictness
    | k >= n             = s
    | not $ I.member r s = build n (k+1) (I.insert r s) rs
    | otherwise          = build n k s rs

main = do [n, l] <- fmap (map read) getArgs
          g <- getStdGen
          if n > l
           then putStrLn "Your request is impossible."
           else putStr . unlines . map show . I.elems
                       $ build n 0 I.empty (randomRs (0, l-1) g)

A run of the sample problem on my machine took about 1 minute.