Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
System.Random.SplitMix.Distributions
Description
Random samplers for few common distributions, with an interface similar to that of mwc-probability
.
Usage
Compose your random sampler out of simpler ones thanks to the Applicative and Monad interface, e.g. this is how you would declare and sample a binary mixture of Gaussian random variables:
import Control.Monad (replicateM) import System.Random.SplitMix.Distributions (Gen, sample, bernoulli, normal) process ::Gen
Double process = do coin <-bernoulli
0.7 if coin thennormal
0 2 else normal 3 1 dataset :: [Double] dataset =sample
1234 $ replicateM 20 process
and sample your data in a pure (sample
) or monadic (sampleT
) setting.
Initializing the PRNG with a fixed seed makes all results fully reproducible across runs. If this behavior is not desired, one can sample the random seed itself from an IO-based entropy pool, and run the samplers with sampleIO
and samplesIO
.
Implementation details
The library is built on top of splitmix
( https://hackage.haskell.org/package/splitmix ), which provides fast pseudorandom number generation utilities.
Synopsis
- stdUniform :: Monad m => GenT m Double
- uniformR :: Monad m => Double -> Double -> GenT m Double
- exponential :: Monad m => Double -> GenT m Double
- stdNormal :: Monad m => GenT m Double
- normal :: Monad m => Double -> Double -> GenT m Double
- beta :: Monad m => Double -> Double -> GenT m Double
- gamma :: Monad m => Double -> Double -> GenT m Double
- pareto :: Monad m => Double -> Double -> GenT m Double
- dirichlet :: (Monad m, Traversable f) => f Double -> GenT m (f Double)
- logNormal :: Monad m => Double -> Double -> GenT m Double
- laplace :: Monad m => Double -> Double -> GenT m Double
- weibull :: Monad m => Double -> Double -> GenT m Double
- bernoulli :: Monad m => Double -> GenT m Bool
- fairCoin :: Monad m => GenT m Bool
- multinomial :: (Monad m, Foldable t) => Int -> t Double -> GenT m (Maybe [Int])
- categorical :: (Monad m, Foldable t) => t Double -> GenT m (Maybe Int)
- discrete :: (Monad m, Foldable t) => t (Double, b) -> GenT m (Maybe b)
- zipf :: (Monad m, Integral i) => Double -> GenT m i
- crp :: Monad m => Double -> Int -> GenT m [Integer]
- type SMGenState = (Word64, Word64)
- type Gen = GenT Identity
- sample :: Word64 -> Gen a -> a
- samples :: Int -> Word64 -> Gen a -> [a]
- data GenT m a
- sampleT :: Monad m => Word64 -> GenT m a -> m a
- samplesT :: Monad m => Int -> Word64 -> GenT m a -> m [a]
- sampleRunT :: Functor m => SMGenState -> GenT m a -> m (a, SMGenState)
- samplesRunT :: Monad m => Int -> SMGenState -> GenT m a -> m ([a], SMGenState)
- sampleIO :: MonadIO m => GenT m b -> m b
- samplesIO :: MonadIO m => Int -> GenT m a -> m [a]
- withGen :: Monad m => (SMGen -> (a, SMGen)) -> GenT m a
Distributions
Continuous
Uniform between two values
Exponential distribution
Normal distribution
Arguments
:: Monad m | |
=> Double | shape parameter \( \alpha \gt 0 \) |
-> Double | shape parameter \( \beta \gt 0 \) |
-> GenT m Double |
Beta distribution, from two standard uniform samples
Arguments
:: Monad m | |
=> Double | shape parameter \( k \gt 0 \) |
-> Double | scale parameter \( \theta \gt 0 \) |
-> GenT m Double |
Gamma distribution, using Ahrens-Dieter accept-reject (algorithm GD):
Ahrens, J. H.; Dieter, U (January 1982). "Generating gamma variates by a modified rejection technique". Communications of the ACM. 25 (1): 47–54
Arguments
:: Monad m | |
=> Double | shape parameter \( \alpha \gt 0 \) |
-> Double | scale parameter \( x_{min} \gt 0 \) |
-> GenT m Double |
Pareto distribution
Arguments
:: (Monad m, Traversable f) | |
=> f Double | concentration parameters \( \gamma_i \gt 0 , \forall i \) |
-> GenT m (f Double) |
The Dirichlet distribution with the provided concentration parameters. The dimension of the distribution is determined by the number of concentration parameters supplied.
>>>
sample 1234 (dirichlet [0.1, 1, 10])
[2.3781130220132788e-11,6.646079701567026e-2,0.9335392029605486]
Log-normal distribution with specified mean and standard deviation.
Arguments
:: Monad m | |
=> Double | location parameter |
-> Double | scale parameter \( s \gt 0 \) |
-> GenT m Double |
Laplace or double-exponential distribution with provided location and scale parameters.
Weibull distribution with provided shape and scale parameters.
Discrete
Bernoulli trial
fairCoin :: Monad m => GenT m Bool Source #
A fair coin toss returns either value with probability 0.5
Arguments
:: (Monad m, Foldable t) | |
=> Int | number of Bernoulli trials \( n \gt 0 \) |
-> t Double | probability vector \( p_i \gt 0 , \forall i \) (does not need to be normalized) |
-> GenT m (Maybe [Int]) |
Multinomial distribution
NB : returns Nothing
if any of the input probabilities is negative
Arguments
:: (Monad m, Foldable t) | |
=> t Double | probability vector \( p_i \gt 0 , \forall i \) (does not need to be normalized) |
-> GenT m (Maybe Int) |
Categorical distribution
Picks one index out of a discrete set with probability proportional to those supplied as input parameter vector
Arguments
:: (Monad m, Foldable t) | |
=> t (Double, b) | (probability, item) vector \( p_i \gt 0 , \forall i \) (does not need to be normalized) |
-> GenT m (Maybe b) |
Discrete distribution
Pick one item with probability proportional to those supplied as input parameter vector
The Zipf-Mandelbrot distribution.
Note that values of the parameter close to 1 are very computationally intensive.
>>>
samples 10 1234 (zipf 1.1)
[3170051793,2,668775891,146169301649651,23,36,5,6586194257347,21,37911]
>>>
samples 10 1234 (zipf 1.5)
[79,1,58,680,3,1,2,1,366,1]
Arguments
:: Monad m | |
=> Double | concentration parameter \( \alpha \gt 1 \) |
-> Int | number of customers \( n > 0 \) |
-> GenT m [Integer] |
Chinese restaurant process
>>>
sample 1234 $ crp 1.02 50
[24,18,7,1]
>>>
sample 1234 $ crp 2 50
[17,8,13,3,3,3,2,1]
>>>
sample 1234 $ crp 10 50
[5,7,1,6,1,3,5,1,1,3,1,1,1,4,3,1,3,1,1,1]
PRNG
type SMGenState = (Word64, Word64) Source #
Internal state of the splitmix PRNG.
This representation has the benefit of being serializable (e.g. can be passed back and forth between API calls)
Pure
Monadic
Random generator
wraps splitmix
state-passing inside a StateT
monad
useful for embedding random generation inside a larger effect stack
Instances
MonadTrans GenT Source # | |
Defined in System.Random.SplitMix.Distributions | |
MonadReader r m => MonadReader r (GenT m) Source # | |
MonadState s m => MonadState s (GenT m) Source # | |
MonadIO m => MonadIO (GenT m) Source # | |
Defined in System.Random.SplitMix.Distributions | |
Monad m => Applicative (GenT m) Source # | |
Functor m => Functor (GenT m) Source # | |
Monad m => Monad (GenT m) Source # | |
MonadThrow m => MonadThrow (GenT m) Source # | |
Defined in System.Random.SplitMix.Distributions Methods throwM :: (HasCallStack, Exception e) => e -> GenT m a # |
Sample in a monadic context
Sample a batch
Return final PRNG state
Arguments
:: Functor m | |
=> SMGenState | random seed |
-> GenT m a | |
-> m (a, SMGenState) | (result, final PRNG state) |
Sample in a monadic context, returning the final PRNG state as well
This makes it possible to have deterministic chains of invocations, for reproducible results
Arguments
:: Monad m | |
=> Int | size of sample |
-> SMGenState | random seed |
-> GenT m a | |
-> m ([a], SMGenState) | (result, final PRNG state) |
Sample a batch in a monadic context, returning the final PRNG state as well
Same as n
repeated invocations of sampleRunT
, while threading the PRNG state.
IO-based
sampleIO :: MonadIO m => GenT m b -> m b Source #
Initialize a splitmix random generator from system entropy (current time etc.) and sample from the PRNG.
samplesIO :: MonadIO m => Int -> GenT m a -> m [a] Source #
Initialize a splitmix random generator from system entropy (current time etc.) and sample n times from the PRNG.