MonadRandom-0.4.2.3: Random-number generation monad.

Copyright2006-2007 Cale Gibbard, Russell O'Connor, Dan Doel, Remi Turk, Eric Kidd.
LicenseOtherLicense
Stabilityexperimental
Portabilitynon-portable (multi-parameter type classes, undecidable instances)
Safe HaskellTrustworthy
LanguageHaskell2010

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 => 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.

type Rand g = RandT g Identity Source #

A basic random monad.

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) Source # 

Methods

ask :: RandT g m r #

local :: (r -> r) -> RandT g m a -> RandT g m a #

reader :: (r -> a) -> RandT g m a #

MonadState s m => MonadState s (RandT g m) Source # 

Methods

get :: RandT g m s #

put :: s -> RandT g m () #

state :: (s -> (a, s)) -> RandT g m a #

MonadWriter w m => MonadWriter w (RandT g m) Source # 

Methods

writer :: (a, w) -> RandT g m a #

tell :: w -> RandT g m () #

listen :: RandT g m a -> RandT g m (a, w) #

pass :: RandT g m (a, w -> w) -> RandT g m a #

(Monad m, RandomGen g) => MonadSplit g (RandT g m) Source # 

Methods

getSplit :: RandT g m g Source #

MonadTrans (RandT g) Source # 

Methods

lift :: Monad m => m a -> RandT g m a #

Monad m => Monad (RandT g m) Source # 

Methods

(>>=) :: RandT g m a -> (a -> RandT g m b) -> RandT g m b #

(>>) :: RandT g m a -> RandT g m b -> RandT g m b #

return :: a -> RandT g m a #

fail :: String -> RandT g m a #

Functor m => Functor (RandT g m) Source # 

Methods

fmap :: (a -> b) -> RandT g m a -> RandT g m b #

(<$) :: a -> RandT g m b -> RandT g m a #

MonadFix m => MonadFix (RandT g m) Source # 

Methods

mfix :: (a -> RandT g m a) -> RandT g m a #

(Functor m, Monad m) => Applicative (RandT g m) Source # 

Methods

pure :: a -> RandT g m a #

(<*>) :: RandT g m (a -> b) -> RandT g m a -> RandT g m b #

(*>) :: RandT g m a -> RandT g m b -> RandT g m b #

(<*) :: RandT g m a -> RandT g m b -> RandT g m a #

MonadIO m => MonadIO (RandT g m) Source # 

Methods

liftIO :: IO a -> RandT g m a #

(Functor m, MonadPlus m) => Alternative (RandT g m) Source # 

Methods

empty :: RandT g m a #

(<|>) :: RandT g m a -> RandT g m a -> RandT g m a #

some :: RandT g m a -> RandT g m [a] #

many :: RandT g m a -> RandT g m [a] #

MonadPlus m => MonadPlus (RandT g m) Source # 

Methods

mzero :: RandT g m a #

mplus :: RandT g m a -> RandT g m a -> RandT g m a #

(Monad m, RandomGen g) => MonadRandom (RandT g m) Source # 

Methods

getRandom :: Random a => RandT g m a Source #

getRandoms :: Random a => RandT g m [a] Source #

getRandomR :: Random a => (a, a) -> RandT g m a Source #

getRandomRs :: Random a => (a, a) -> RandT g m [a] Source #

Special lift functions

liftRand Source #

Arguments

:: (g -> (a, g))

action returning value and new generator state

-> Rand g a 

Lift arbitrary action to Rand

liftRandT Source #

Arguments

:: (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)

Orphan instances

MonadRandom IO Source # 

Methods

getRandom :: Random a => IO a Source #

getRandoms :: Random a => IO [a] Source #

getRandomR :: Random a => (a, a) -> IO a Source #

getRandomRs :: Random a => (a, a) -> IO [a] Source #

MonadSplit StdGen IO Source # 
MonadSplit g m => MonadSplit g (MaybeT m) Source # 

Methods

getSplit :: MaybeT m g Source #

(Error e, MonadSplit g m) => MonadSplit g (ErrorT e m) Source # 

Methods

getSplit :: ErrorT e m g Source #

MonadSplit g m => MonadSplit g (ExceptT e m) Source # 

Methods

getSplit :: ExceptT e m g Source #

(MonadSplit g m, Monoid w) => MonadSplit g (WriterT w m) Source # 

Methods

getSplit :: WriterT w m g Source #

(MonadSplit g m, Monoid w) => MonadSplit g (WriterT w m) Source # 

Methods

getSplit :: WriterT w m g Source #

MonadSplit g m => MonadSplit g (StateT s m) Source # 

Methods

getSplit :: StateT s m g Source #

MonadSplit g m => MonadSplit g (StateT s m) Source # 

Methods

getSplit :: StateT s m g Source #

MonadSplit g m => MonadSplit g (IdentityT * m) Source # 

Methods

getSplit :: IdentityT * m g Source #

MonadSplit g m => MonadSplit g (ContT * r m) Source # 

Methods

getSplit :: ContT * r m g Source #

MonadSplit g m => MonadSplit g (ReaderT * r m) Source # 

Methods

getSplit :: ReaderT * r m g Source #

(MonadSplit g m, Monoid w) => MonadSplit g (RWST r w s m) Source # 

Methods

getSplit :: RWST r w s m g Source #

(MonadSplit g m, Monoid w) => MonadSplit g (RWST r w s m) Source # 

Methods

getSplit :: RWST r w s m g Source #

MonadRandom m => MonadRandom (MaybeT m) Source # 

Methods

getRandom :: Random a => MaybeT m a Source #

getRandoms :: Random a => MaybeT m [a] Source #

getRandomR :: Random a => (a, a) -> MaybeT m a Source #

getRandomRs :: Random a => (a, a) -> MaybeT m [a] Source #

MonadRandom m => MonadRandom (ExceptT e m) Source # 

Methods

getRandom :: Random a => ExceptT e m a Source #

getRandoms :: Random a => ExceptT e m [a] Source #

getRandomR :: Random a => (a, a) -> ExceptT e m a Source #

getRandomRs :: Random a => (a, a) -> ExceptT e m [a] Source #

(Error e, MonadRandom m) => MonadRandom (ErrorT e m) Source # 

Methods

getRandom :: Random a => ErrorT e m a Source #

getRandoms :: Random a => ErrorT e m [a] Source #

getRandomR :: Random a => (a, a) -> ErrorT e m a Source #

getRandomRs :: Random a => (a, a) -> ErrorT e m [a] Source #

MonadRandom m => MonadRandom (StateT s m) Source # 

Methods

getRandom :: Random a => StateT s m a Source #

getRandoms :: Random a => StateT s m [a] Source #

getRandomR :: Random a => (a, a) -> StateT s m a Source #

getRandomRs :: Random a => (a, a) -> StateT s m [a] Source #

MonadRandom m => MonadRandom (StateT s m) Source # 

Methods

getRandom :: Random a => StateT s m a Source #

getRandoms :: Random a => StateT s m [a] Source #

getRandomR :: Random a => (a, a) -> StateT s m a Source #

getRandomRs :: Random a => (a, a) -> StateT s m [a] Source #

(MonadRandom m, Monoid w) => MonadRandom (WriterT w m) Source # 

Methods

getRandom :: Random a => WriterT w m a Source #

getRandoms :: Random a => WriterT w m [a] Source #

getRandomR :: Random a => (a, a) -> WriterT w m a Source #

getRandomRs :: Random a => (a, a) -> WriterT w m [a] Source #

(MonadRandom m, Monoid w) => MonadRandom (WriterT w m) Source # 

Methods

getRandom :: Random a => WriterT w m a Source #

getRandoms :: Random a => WriterT w m [a] Source #

getRandomR :: Random a => (a, a) -> WriterT w m a Source #

getRandomRs :: Random a => (a, a) -> WriterT w m [a] Source #

MonadRandom m => MonadRandom (IdentityT * m) Source # 

Methods

getRandom :: Random a => IdentityT * m a Source #

getRandoms :: Random a => IdentityT * m [a] Source #

getRandomR :: Random a => (a, a) -> IdentityT * m a Source #

getRandomRs :: Random a => (a, a) -> IdentityT * m [a] Source #

MonadRandom m => MonadRandom (ContT * r m) Source # 

Methods

getRandom :: Random a => ContT * r m a Source #

getRandoms :: Random a => ContT * r m [a] Source #

getRandomR :: Random a => (a, a) -> ContT * r m a Source #

getRandomRs :: Random a => (a, a) -> ContT * r m [a] Source #

MonadRandom m => MonadRandom (ReaderT * r m) Source # 

Methods

getRandom :: Random a => ReaderT * r m a Source #

getRandoms :: Random a => ReaderT * r m [a] Source #

getRandomR :: Random a => (a, a) -> ReaderT * r m a Source #

getRandomRs :: Random a => (a, a) -> ReaderT * r m [a] Source #

(MonadRandom m, Monoid w) => MonadRandom (RWST r w s m) Source # 

Methods

getRandom :: Random a => RWST r w s m a Source #

getRandoms :: Random a => RWST r w s m [a] Source #

getRandomR :: Random a => (a, a) -> RWST r w s m a Source #

getRandomRs :: Random a => (a, a) -> RWST r w s m [a] Source #

(MonadRandom m, Monoid w) => MonadRandom (RWST r w s m) Source # 

Methods

getRandom :: Random a => RWST r w s m a Source #

getRandoms :: Random a => RWST r w s m [a] Source #

getRandomR :: Random a => (a, a) -> RWST r w s m a Source #

getRandomRs :: Random a => (a, a) -> RWST r w s m [a] Source #