monte-carlo-0.1: A monad and transformer for Monte Carlo calculations.

Stabilityexperimental
MaintainerPatrick Perry <patperry@stanford.edu>

Control.Monad.MC.GSL

Contents

Description

 

Synopsis

The Monte Carlo monad

data MC a Source

A Monte Carlo monad with an internal random number generator.

runMC :: MC a -> RNG -> (a, RNG)Source

Run this Monte Carlo monad with the given initial random number generator, getting the result and the new random number generator.

evalMC :: MC a -> RNG -> aSource

Evaluate this Monte Carlo monad and throw away the final random number generator. Very much like fst composed with runMC.

execMC :: MC a -> RNG -> RNGSource

Exicute this Monte Carlo monad and return the final random number generator. Very much like snd composed with runMC.

unsafeInterleaveMC :: MC a -> MC aSource

Get the baton from the Monte Carlo monad without performing any computations. Useful but dangerous.

The Monte Carlo monad transformer

data MCT m a Source

A parameterizable Monte Carlo monad for encapsulating an inner monad.

Instances

MonadTrans MCT 
MonadReader r m => MonadReader r (MCT m) 
MonadState s m => MonadState s (MCT m) 
Monad m => MonadState RNG (MCT m) 
MonadError e m => MonadError e (MCT m) 
MonadWriter w m => MonadWriter w (MCT m) 
Monad m => Monad (MCT m) 
Monad m => Functor (MCT m) 
MonadPlus m => MonadPlus (MCT m) 
MonadCont m => MonadCont (MCT m) 
MonadIO m => MonadIO (MCT m) 

runMCT :: Monad m => MCT m a -> RNG -> m (a, RNG)Source

Similar to runMC.

evalMCT :: Monad m => MCT m a -> RNG -> m aSource

Similar to evalMC.

execMCT :: Monad m => MCT m a -> RNG -> m RNGSource

Similar to execMC.

liftMCT :: Monad m => MC a -> MCT m aSource

Take a Monte Carlo computations and lift it to an MCT computation.

Pure random number generator creation

data RNG

Instances

mt19937 :: Word64 -> RNGSource

Get a Mersenne Twister random number generator seeded with the given value.

Random distributions

uniform :: Double -> Double -> MC DoubleSource

uniform a b generates a value uniformly distributed in [a,b).

uniformInt :: Int -> MC IntSource

uniformInt n generates an integer uniformly in the range [0,n-1]. It is an error to call this function with a non-positive value.

normal :: Double -> Double -> MC DoubleSource

normal mu sigma generates a Normal random variable with mean mu and standard deviation sigma.

poisson :: Double -> MC IntSource

poisson mu generates a Poisson random variable with mean mu.