[Haskell-cafe] Importance of MonadRandom

Yitzchak Gale gale at sefer.org
Thu Feb 1 09:47:26 EST 2007


I would like to point out the importance of Cale Gibbard's
MonadRandom, beyond what is currently mentioned
on its wiki page:

http://www.haskell.org/haskellwiki/New_monads/MonadRandom

This monad makes it possible to write functions that
use randomness without having to specify in
advance whether the source of randomness will
be a pure pseudorandom number generator, as
in System.Random, or physical randomness via
the IO monad, such as your operating system's
source of physical randomness, or random.org,
or a hardware random generator.

Before use of MonadRandom becomes widespread -
and I think it ought to - I would like to suggest a change
to the interface. (I mentioned this once to
Cale on #haskell, but I didn't say what change
I meant.)

Currently, the members of the MonadRandom
class mimic the members of the Random class
in System.Random. I think it would be better if
instead they mimicked the members of
RandomGen. Like this:

\begin{code}

class (Monad m) => MonadRandom m where
  nextR :: m Int
  splitR :: m (m ())
  rangeR :: m (Int, Int)
  getR :: (forall g . RandomGen g => g -> a) -> m a

\end{code}

The extra function getR provides access not
only to the member functions of Random, but
to any function that generates random variables
of any type. You would use

getR random, getR $ randomR (a, b), etc.

instead of

getRandom, getRandomR (a, b), etc.


Provide a default method for getR as follows:

\begin{code}

  getR f = do
    r <- nextR
    (lo, hi) <- rangeR
    return $ f $ TrivialGen r lo hi

data TrivialGen = TrivialGen Int Int Int

instance RandomGen TrivialGen where
  next (TrivialGen r _ _) = r
  genRange (TrivialGen _ lo hi) = (lo, hi)
  split _ = undefined

\end{code}

We would use the default method of getR for
MonadRandom instances of things like
DevRandom, DevURandom, RandomDotOrg,
etc. For the Rand and RandT instances we
provide explicit methods:

\begin{code}

-- For RandT:
  getR f = RandT $ gets f

--For Rand:
  getR =Rand $ getR f

\end{code}

I think this is better for several reasons:

o We anyway need getR for general random variables
o We could lose precision getting other random
  variables via getRandom in the case where
  genRange /= (minBound, maxBound)
o I think it is a better semantic fit

Regards,
Yitz


More information about the Haskell-Cafe mailing list