[Haskell-cafe] Monte Carlo Pi calculation (newbie learnings)

Andrew Coppin andrewcoppin at btinternet.com
Mon Nov 5 15:36:10 EST 2007


Alex Young wrote:
> rand :: IO Int
> rand = getStdRandom (randomR (0, randMax))
>
> randListTail accum 0 = accum
> randListTail accum n = randListTail (rand : accum) (n - 1)
>
> randList :: Int -> [IO Int]
> randList n = randListTail [] n
>
> randPairs :: Int -> [(IO Int, IO Int)]
> randPairs n = zip (randList n) (randList n)

This looks entirely broken. How about this?

  randList :: Int -> IO [Int]
  randList n = mapM (\x -> randomRIO (0, randMax)) [1..n]

(Sorry, I'm not very familiar with the Random module. However, I believe 
this works.) This then gives you an ordinary list of integers, which 
elides some of the stuff below...

> pairIsInside x y = if x*x + y*y < unitRadius then 1 else 0

This is fairly atypical in Haskell. More likely you'd do something like

  pairIsInside :: (Int,Int) -> Bool
  pairIsInside x y = x*x + y*y < unitRadius

and then later write

  length . filter pairIsInside

instead of using "sum".

> doCountPair :: (IO Int, IO Int) -> IO Int
> doCountPair (a, b) = do
>   x <- a
>   y <- b
>   return (pairIsInside x y)
>
> fSumListTail :: Int -> [(IO Int, IO Int)] -> IO Int
> fSumListTail total [] = do
>   return total
> fSumListTail total (x:xs) = do
>   y <- doCountPair x
>   fSumListTail (total+y) xs
>
> fSumList :: [(IO Int, IO Int)] -> IO Int
> fSumList l = fSumListTail 0 l

Most of this goes away if you use an "IO [Int]" rather than "[IO Int]".

> piAsDouble :: Int -> Int -> Double
> piAsDouble a b =
>   (fromInteger (toInteger a)) / (fromInteger (toInteger b))

I don't *think* you need the toInteger there - I may be wrong...

> calculatePi total = do
>   count <- fSumList (randPairs total)
>   return (piAsDouble (4*count) total)

This looks OK.

> main = do
>   args <- getArgs
>   (calculatePi (read (args !! 0))) >>= (putStr . show)

This looks OK too - if a little confusing. As a matter of style, I'd write

  main = do
    args <- getArgs
    case args of
      [size] -> print $ calculatePi $ read size
      _ -> putStrLn "Usage: CALCPI <size>"

But that's just me...



More information about the Haskell-Cafe mailing list