Skip to content

Instantly share code, notes, and snippets.

@quephird
Last active September 3, 2015 22:39
Show Gist options
  • Save quephird/1ce8cefdcb4530161ff1 to your computer and use it in GitHub Desktop.
Save quephird/1ce8cefdcb4530161ff1 to your computer and use it in GitHub Desktop.
Solution to exercise in PureScript by Example book to estimate pi
module Pi where
import Control.Monad.Eff (Eff(..), forE)
import Control.Monad.Eff.Random (RANDOM(..), random)
import Control.Monad.ST (ST(..), modifySTRef, newSTRef, readSTRef)
import Data.Array ((:), filter, length)
import Data.Int (toNumber)
import Data.Tuple (Tuple(..))
import Prelude (($), (<=), (+), (*), (/), bind, return, unit)
pi :: forall eff r. Int -> Eff (st :: ST r, random :: RANDOM | eff) Number
pi n = do
ref <- newSTRef ([] :: Array (Tuple Number Number))
forE 0.0 (toNumber n) $ \i -> do
x <- random
y <- random
modifySTRef ref (\o -> Tuple x y : o)
return unit
tuples <- readSTRef ref
all <- return $ toNumber $ length tuples
inside <- return $ toNumber $ length $ filter (\(Tuple x y) -> x*x + y*y <= 1.0) tuples
return (4.0 * inside / all)
@queertypes
Copy link

Your solution looks good to me. The primary improvement I'd suggest is how you arrive at the answer. The key is to take advantage of ST to use even less local state. The other observations is that all will always be the same length as the input value n. With these two things, you can do something like:

pi :: forall eff r. Int -> Eff (st :: ST r, random :: RANDOM) Number
pi n = do
  ref <- newSTRef 0 -- might require Number type annotation
  forE 0 (toNumber n) $ \i -> do
    x <- random  -- random returns a number between 0 and 1
    y <- random
    let v = x*x + y*y
    guard $ v <= 1.0  -- skips this modification if condition check fails
    modifySTRef ref (\o -> o + v)
    return unit
  val <- readSTRef ref
  return (4.0 * val / n)

@quephird
Copy link
Author

quephird commented Sep 3, 2015

Ah... DUH... pfffft... what the hell was I thinking about needing all? (-‸ლ)

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment