Portability | non-portable (multi-parameter type classes, undecidable instances) |
---|---|
Stability | experimental |
A random number generation monad. See http://www.haskell.org/haskellwiki/NewMonads/MonadRandom for the original version of this code.
The actual interface is defined by
MonadRandom
.
- Computation type:
- Computations which consume random values.
- Binding strategy:
- The computation proceeds in the same fashion as the identity monad, but it carries a random number generator that may be queried to generate random values.
- Useful for:
- Monte Carlo algorithms and simulating random processes.
- module System.Random
- module Control.Monad.Random.Class
- evalRandT :: (Monad m, RandomGen g) => RandT g m a -> g -> m a
- runRandT :: (Monad m, RandomGen g) => RandT g m a -> g -> m (a, g)
- evalRand :: RandomGen g => Rand g a -> g -> a
- runRand :: RandomGen g => Rand g a -> g -> (a, g)
- evalRandIO :: Rand StdGen a -> IO a
- fromList :: MonadRandom m => [(a, Rational)] -> m a
- data Rand g a
- data RandomGen g => RandT g m a
Documentation
module System.Random
module Control.Monad.Random.Class
evalRandT :: (Monad m, RandomGen g) => RandT g m a -> g -> m aSource
Evaluate a RandT computation using the generator g
. Note that the
generator g
is not returned, so there's no way to recover the
updated version of g
.
runRandT :: (Monad m, RandomGen g) => RandT g m a -> g -> m (a, g)Source
Run a RandT computation using the generator g
, returning the result and
the updated generator.
evalRand :: RandomGen g => Rand g a -> g -> aSource
Evaluate a random computation using the generator g
. Note that the
generator g
is not returned, so there's no way to recover the
updated version of g
.
runRand :: RandomGen g => Rand g a -> g -> (a, g)Source
Run a random computation using the generator g
, returning the result
and the updated generator.
evalRandIO :: Rand StdGen a -> IO aSource
Evaluate a random computation in the IO monad, using the random number
generator supplied by getStdRandom
.
fromList :: MonadRandom m => [(a, Rational)] -> m aSource
Sample a random value from a weighted list. The total weight of all elements must not be 0.
A basic random monad.
RandomGen g => MonadSplit g (Rand g) | |
Monad (Rand g) | |
Functor (Rand g) | |
RandomGen g => MonadRandom (Rand g) |
data RandomGen g => RandT g m a Source
A monad transformer which adds a random number generator to an existing monad.
(MonadReader r m, RandomGen g) => MonadReader r (RandT g m) | |
(MonadState s m, RandomGen g) => MonadState s (RandT g m) | |
(MonadWriter w m, RandomGen g, Monoid w) => MonadWriter w (RandT g m) | |
(Monad m, RandomGen g) => MonadSplit g (RandT g m) | |
MonadTrans (RandT g) | |
Monad m => Monad (RandT g m) | |
Monad m => Functor (RandT g m) | |
MonadIO m => MonadIO (RandT g m) | |
(Monad m, RandomGen g) => MonadRandom (RandT g m) |
Example
The die
function simulates the roll of a die, picking a number between 1
and 6, inclusive, and returning it in the Rand
monad. Notice that this
code will work with any source of random numbers g
.
die :: (RandomGen g) => Rand g Int die = getRandomR (1,6)
The dice
function uses replicate
and sequence
to simulate the roll of
n
dice.
dice :: (RandomGen g) => Int -> Rand g [Int] dice n = sequence (replicate n die)
To extract a value from the Rand
monad, we can can use evalRandIO
.
main = do values <- evalRandIO (dice 2) putStrLn (show values)