| Stability | experimental |
|---|---|
| Maintainer | Patrick Perry <patperry@gmail.com> |
Control.Monad.MC.Class
Contents
Description
The abstract MonadMC interface and utility functions for Monte Carlo computations.
- class HasRNG m where
- type RNG m
- class (Monad m, HasRNG m) => MonadMC m where
- getRNG :: m (RNG m)
- setRNG :: RNG m -> m ()
- uniform :: Double -> Double -> m Double
- uniformInt :: Int -> m Int
- normal :: Double -> Double -> m Double
- exponential :: Double -> m Double
- levy :: Double -> Double -> m Double
- levySkew :: Double -> Double -> Double -> m Double
- poisson :: Double -> m Int
- cauchy :: Double -> m Double
- beta :: Double -> Double -> m Double
- logistic :: Double -> m Double
- pareto :: Double -> Double -> m Double
- weibull :: Double -> Double -> m Double
- gamma :: Double -> Double -> m Double
- multinomial :: Int -> Vector Double -> m (Vector Int)
- dirichlet :: Vector Double -> m (Vector Double)
- unsafeInterleaveMC :: m a -> m a
- bernoulli :: MonadMC m => Double -> m Bool
- sample :: MonadMC m => [a] -> m a
- sampleWithWeights :: MonadMC m => [(Double, a)] -> m a
- sampleSubset :: MonadMC m => [a] -> Int -> m [a]
- sampleSubset' :: MonadMC m => [a] -> Int -> m [a]
- sampleSubsetWithWeights :: MonadMC m => [(Double, a)] -> Int -> m [a]
- sampleSubsetWithWeights' :: MonadMC m => [(Double, a)] -> Int -> m [a]
- sampleInt :: MonadMC m => Int -> m Int
- sampleIntWithWeights :: MonadMC m => [Double] -> Int -> m Int
- sampleIntSubset :: MonadMC m => Int -> Int -> m [Int]
- sampleIntSubset' :: MonadMC m => Int -> Int -> m [Int]
- sampleIntSubsetWithWeights :: MonadMC m => [Double] -> Int -> Int -> m [Int]
- sampleIntSubsetWithWeights' :: MonadMC m => [Double] -> Int -> Int -> m [Int]
- shuffle :: MonadMC m => [a] -> m [a]
- shuffleInt :: MonadMC m => Int -> m [(Int, Int)]
- shuffleInt' :: MonadMC m => Int -> m [(Int, Int)]
- repeatMC :: MonadMC m => m a -> m [a]
- replicateMC :: MonadMC m => Int -> m a -> m [a]
The Monte Carlo monad type class
class (Monad m, HasRNG m) => MonadMC m whereSource
Methods
Get the current random number generator.
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.
cauchy :: Double -> m DoubleSource
cauchy a generates a Cauchy random variable with scale
parameter a.
beta :: Double -> Double -> m DoubleSource
beta a b generates a beta random variable with
parameters a and b.
logistic :: Double -> m DoubleSource
logistic a generates a logistic random variable with
parameter a.
pareto :: Double -> Double -> m DoubleSource
pareto a b generates a Pareto random variable with
exponent a and scale b.
weibull :: Double -> Double -> m DoubleSource
weibull a b generates a Weibull random variable with
scale a and exponent b.
gamma :: Double -> Double -> m DoubleSource
gamma a b generates a gamma random variable with
parameters a and b.
multinomial :: Int -> Vector Double -> m (Vector Int)Source
multinomial n ps generates a multinomial random
variable with parameters ps formed by n trials.
dirichlet :: Vector Double -> m (Vector Double)Source
dirichlet alphas generates a Dirichlet random variable
with parameters alphas.
unsafeInterleaveMC :: m a -> m aSource
Get the baton from the Monte Carlo monad without performing any computations. Useful but dangerous.
Random distributions
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 => [a] -> Int -> m [a]Source
sampleSubset xs k 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 => [a] -> Int -> m [a]Source
Strict version of sampleSubset.
sampleSubsetWithWeights :: MonadMC m => [(Double, a)] -> Int -> m [a]Source
Sample a subset of the elements with the given weights. Return the elements of the subset lazily in the order they were sampled.
sampleSubsetWithWeights' :: MonadMC m => [(Double, a)] -> Int -> m [a]Source
Strict version of sampleSubsetWithWeights.
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 n k 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.
sampleIntSubsetWithWeights :: MonadMC m => [Double] -> Int -> Int -> m [Int]Source
sampleIntSubsetWithWeights ws n k samplea size k subset of
{ 0, ..., n-1 } with the given weights by sampling elements without
replacement. It returns the elements of the subset lazily in the order
they were sampled.
sampleIntSubsetWithWeights' :: MonadMC m => [Double] -> Int -> Int -> m [Int]Source
Strict version of sampleIntSubsetWithWeights.
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.