Copyright | 2006-2007 Cale Gibbard, Russell O'Connor, Dan Doel, Remi Turk, Eric Kidd. |
---|---|
License | OtherLicense |
Stability | experimental |
Portability | non-portable (multi-parameter type classes, undecidable instances) |
Safe Haskell | None |
Language | Haskell2010 |
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 => RandT g m a -> g -> m a
- runRandT :: RandT g m a -> g -> m (a, g)
- evalRand :: Rand g a -> g -> a
- runRand :: Rand g a -> g -> (a, g)
- evalRandIO :: Rand StdGen a -> IO a
- fromList :: MonadRandom m => [(a, Rational)] -> m a
- uniform :: MonadRandom m => [a] -> m a
- type Rand g = RandT g Identity
- data RandT g m a
- liftRand :: (g -> (a, g)) -> Rand g a
- liftRandT :: (g -> m (a, g)) -> RandT g m a
Documentation
module System.Random
module Control.Monad.Random.Class
evalRandT :: Monad m => RandT g m a -> g -> m a Source
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 :: 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 :: Rand g a -> g -> a Source
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 :: 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 a Source
Evaluate a random computation in the IO monad, splitting the global standard generator to get a new one for the computation.
fromList :: MonadRandom m => [(a, Rational)] -> m a Source
Sample a random value from a weighted list. The total weight of all elements must not be 0.
uniform :: MonadRandom m => [a] -> m a Source
Sample a value from a uniform distribution of a list of elements.
A monad transformer which adds a random number generator to an existing monad.
MonadReader r m => MonadReader r (RandT g m) Source | |
MonadState s m => MonadState s (RandT g m) Source | |
MonadWriter w m => MonadWriter w (RandT g m) Source | |
(Monad m, RandomGen g) => MonadSplit g (RandT g m) Source | |
MonadTrans (RandT g) Source | |
Monad m => Monad (RandT g m) Source | |
Functor m => Functor (RandT g m) Source | |
MonadFix m => MonadFix (RandT g m) Source | |
(Functor m, Monad m) => Applicative (RandT g m) Source | |
MonadIO m => MonadIO (RandT g m) Source | |
(Monad m, RandomGen g) => MonadRandom (RandT g m) Source |
Special lift functions
:: (g -> (a, g)) | action returning value and new generator state |
-> Rand g a |
Lift arbitrary action to Rand
:: (g -> m (a, g)) | action returning value and new generator state |
-> RandT g m a |
Lift arbitrary action to RandT
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)