On 29/12/2011 21:51, Jerzy Karczmarczuk wrote:
Steve Horne :
I only meant that there's random number handling support in the Haskell library and, and least judging by type signatures, it's pure functional code with no hint of the IO monad.
Look well at those functions, please.
Challenge accepted. Some code (intended to be loaded into GHCi and played with) that I once wrote when doing the ninety-nine problems thing (the one that doesn't have ninety-nine problems - originally based on a Prolog tutorial IIRC)...

   --  Randomly select the specified number of items from the list
   --
   --  Usage in GHCi...
   --
   --  import System.Random
   --  randSelect "this is a list" 5 (mkStdGen 9877087)
   --
   --  This will give the same results each time (for the same seed
   given to mkStdGen)
   --
   --  randSelect' does the real work, but needs to know the length of
   the remaining
   --  list and doesn't do error checks (for efficiency reasons).
   module P23 (randSelect) where
      import System.Random

      randSelect' :: RandomGen g => [x] -> Int -> Int -> g -> ([x], g)

      randSelect' [] n l g = ([], g)  --  n and l should be == 0, but
   no need for run-time check

      --  optimisation cases - no choice left
      randSelect' xs n l g | (n == l) = (xs, g)
                           | (n == 0) = ([], g)

      randSelect' (x:xs) n l g = let xsLen      = (l - 1)
                                     (rnd, g')  = randomR (0, xsLen) g
                                     (keep, n') = if (rnd < n) then
   (True, (n-1)) else (False, n)
                                     (xs', g'') = randSelect' xs n'
   xsLen g'
                                 in ((if keep then (x:xs') else xs'), g'')

      randSelect :: RandomGen g => [x] -> Int -> g -> ([x], g)

      randSelect xs n g = let len = (length xs)
                          in if (n > len) then error "Not enough items
   in the list!"
                                          else randSelect' xs n len g

I see no IO monad anywhere in there. Of course I'm cheating - providing a constant seed at runtime. It's a bit like the classic "chosen by a throw of a fair die" joke in a way. But the functions I'm using are pure.

I don't claim to know every Haskell library function, of course. If there's further functions for that, all well and good - but there's still a perfectly adequate pure functional subset.

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to