MonadRandom-0.1.13: Random-number generation monad.

Portabilitynon-portable (multi-parameter type classes, undecidable instances)
Stabilityexperimental
Safe HaskellNone

Control.Monad.Random

Contents

Description

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.

Synopsis

Documentation

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, splitting the global standard generator to get a new one for the computation.

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.

uniform :: MonadRandom m => [a] -> m aSource

Sample a value from a uniform distribution of a list of elements.

data Rand g a Source

A basic random monad.

Instances

data RandT g m a Source

A monad transformer which adds a random number generator to an existing monad.

Instances

MonadReader r m => MonadReader r (RandT g m) 
(MonadState s m, RandomGen g) => MonadState s (RandT g m) 
MonadWriter w m => MonadWriter w (RandT g m) 
(Monad m, RandomGen g) => MonadSplit g (RandT g m) 
MonadTrans (RandT g) 
Monad m => Monad (RandT g m) 
Functor m => Functor (RandT g m) 
MonadFix m => MonadFix (RandT g m) 
(Functor m, Monad m) => Applicative (RandT g m) 
MonadIO m => MonadIO (RandT g m) 
(Monad m, RandomGen g) => MonadRandom (RandT g m) 

Special lift functions

liftRandSource

Arguments

:: (RandomGen g, Random a) 
=> (g -> (a, g))

action returning value and new generator state

-> Rand g a 

Lift arbitrary action to Rand

liftRandTSource

Arguments

:: (Monad m, RandomGen g, Random a) 
=> (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)