[Haskell-cafe] How to use randomized algorithm within the implementation of pure data structures?

Travis Cardwell travis.cardwell at extellisys.com
Sat Nov 1 11:59:43 UTC 2014


Hi Ishii-san,

お久しぶりです。

On 2014年11月01日 18:25, Hiromi ISHII wrote:
> Since C-Z algorithm is a randomized algorithm, we have to have an access
> for random number generator when calculating algebraic number arithmetics
> e.g. writing Num instance for algebraic numbers.
> 
> Here is the problem: how to pass-around random number generator throughout pure computaion?
> 
> I think one immediate solution is to create global state with `newStdGen` and `unsafePerformIO` like below:
<SNIP>
> But this hack seems rather dirty and unsafe.
> 
> Is there any workaround to achieve the same thing?

If it works with the algorithm, you could use a pseudo-random number
generator with a fixed seed.  For example, here is a program to estimate
the value of π (purely) using a Monte Carlo simulation:

    {-# LANGUAGE BangPatterns #-}

    module Main where

    import System.Random (mkStdGen, randomRs)

    -- | Estamate pi via monte-carlo simulation
    mcpi :: Int     -- ^ number of iterations
         -> Double  -- ^ estimated value of pi
    mcpi count = step (randomRs (0.0, 1.0) (mkStdGen 1331)) 0 count
      where
        step :: [Double] -> Int -> Int -> Double
        step (x:y:rs) !qrt !i
          | i < 1     = 4.0 * fromIntegral qrt / fromIntegral count
          | hit x y   = step rs (qrt + 1) (i - 1)
          | otherwise = step rs qrt (i - 1)
        step _ _ _ = error "impossible"

        hit :: Double -> Double -> Bool
        hit x y = x ^ (2 :: Int) + y ^ (2 :: Int) <= 1.0

    main :: IO ()
    main = putStrLn $ "pi ~= " ++ show (mcpi 1000000)

Cheers,

Travis


More information about the Haskell-Cafe mailing list