module Rand9b where
import Control.Applicative (Applicative(..), (<$>), (<*>))
import Control.Monad (ap, liftM)
type Seed = Int
newtype Random a = Rand { unRand :: (Seed -> (a, Seed)) }
randomNext :: Seed -> Seed
randomNext rand = if newRand > 0 then newRand else newRand + 2147483647
where newRand = 16807 * lo - 2836 * hi
(hi,lo) = rand `divMod` 127773
rollDie :: Random Int
rollDie = Rand $ \ seed -> ((seed `mod` 6) + 1, randomNext seed)
instance Monad Random where
(>>=) = randomBind
return = randomReturn
instance Functor Random where
fmap = liftM
instance Applicative Random where
pure = return
(<*>) = ap
randomBind :: Random a -> (a -> Random b) -> Random b
m `randomBind` g = Rand $ \seed0 ->
let (result1, seed1) = unRand m $ seed0
(result2, seed2) = unRand (g result1) $ seed1
in (result2, seed2)
randomReturn :: a -> Random a
randomReturn x = Rand $ \ seed0 -> (x, seed0)
sumTwoDice :: Random Int
sumTwoDice = (+) <$> rollDie <*> rollDie
I also threw in instances of Functor and Applicative, so that I could simplify sumTwoDice using applicative form (much nicer, no? Applicative is totally rockin')
Now you need one more thing, a way to convert a series of Random actions into a pure function:
runRandom s f = fst . unRand f $ s
Prelude> :reload
[1 of 1] Compiling Rand9b ( rand9b.hs, interpreted )
Ok, modules loaded: Rand9b.
*Rand9b> runRandom 0 sumTwoDice
3