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

Stabilityexperimental
MaintainerPatrick Perry <patperry@gmail.com>

Control.Monad.MC.Class

Contents

Description

The abstract MonadMC interface and utility functions for Monte Carlo computations.

Synopsis

The Monte Carlo monad type class

class HasRNG m Source

Associated Types

type RNG m Source

The random number generator type for the monad.

Instances

HasRNG MC 
Monad m => HasRNG (MCT m) 

class (Monad m, HasRNG m) => MonadMC m whereSource

Methods

getRNG :: m (RNG m)Source

Get the current random number generator.

setRNG :: RNG m -> m ()Source

Set the current random number generator.

uniform :: Double -> Double -> m DoubleSource

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

uniformInt :: Int -> m 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 -> m DoubleSource

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

exponential :: Double -> m DoubleSource

exponential mu generates an Exponential variate with mean mu.

levy :: Double -> Double -> m DoubleSource

levy c alpha gets a Levy alpha-stable variate with scale c and exponent alpha. The algorithm only works for 0 < alpha <= 2.

levySkew :: Double -> Double -> Double -> m DoubleSource

levySkew c alpha beta gets a skew Levy alpha-stable variate with scale c, exponent alpha, and skewness beta. The skew parameter must lie in the range [-1,1]. The algorithm only works for 0 < alpha <= 2.

poisson :: Double -> m IntSource

poisson mu generates a Poisson random variable with mean mu.

unsafeInterleaveMC :: m a -> m aSource

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

Instances

MonadMC MC 
Monad m => MonadMC (MCT m) 

Random distributions

bernoulli :: MonadMC m => Double -> m BoolSource

Generate True events with the given probability

Sampling from lists

sample :: MonadMC m => [a] -> m aSource

sample xs samples a value uniformly from the elements of xs. The results are undefined if length xs is zero.

sampleWithWeights :: MonadMC m => [(Double, a)] -> m aSource

sampleWithWeights wxs samples a value from the list with the given weight.

sampleSubset :: MonadMC m => Int -> [a] -> m [a]Source

sampleSubset k xs samples a subset of size k from xs by sampling without replacement. The return value is a list of length k with the elements in the subset in the order that they were sampled. Note also that the elements are lazily generated.

sampleSubset' :: MonadMC m => Int -> [a] -> m [a]Source

Strict version of sampleSubset.

Sampling Ints

sampleInt :: MonadMC m => Int -> m IntSource

sampleInt n samples integers uniformly from [ 0..n-1 ]. It is an error to call this function with a non-positive n.

sampleIntWithWeights :: MonadMC m => [Double] -> Int -> m IntSource

sampleIntWithWeights ws n samples integers from [ 0..n-1 ] with the probability of choosing i proportional to ws !! i. The list ws must have length equal to n. Also, the elements of ws must be non-negative with at least one nonzero entry.

sampleIntSubset :: MonadMC m => Int -> Int -> m [Int]Source

sampleIntSubset k n samples a subset of size k by sampling without replacement from the integers { 0, ..., n-1 }. The return value is a list of length k with the elements in the subset in the order that they were sampled. Note also that the elements are lazily generated.

sampleIntSubset' :: MonadMC m => Int -> Int -> m [Int]Source

Strict version of sampleIntSubset.

Shuffling

shuffle :: MonadMC m => [a] -> m [a]Source

shuffle xs randomly permutes the list xs and returns the result. All permutations of the elements of xs are equally likely.

shuffleInt :: MonadMC m => Int -> m [(Int, Int)]Source

shuffleInt n generates a sequence of swaps equivalent to a uniformly-chosen random permutatation of the integers {0, ..., n-1}. For an input of n, there are n-1 swaps, which are lazily generated.

shuffleInt' :: MonadMC m => Int -> m [(Int, Int)]Source

Strict version of shuffleInt.

Repeating computations

repeatMC :: MonadMC m => m a -> m [a]Source

Produce a lazy infinite list of values from the given Monte Carlo generator.

replicateMC :: MonadMC m => Int -> m a -> m [a]Source

Produce a lazy list of the given length using the specified generator.