License | GPL-3 |
---|---|
Maintainer | hackage@mail.kevinl.io |
Stability | experimental |
Safe Haskell | Safe |
Language | Haskell2010 |
This module contains convenience functions to
construct Sample
s or StochProcess
es corresponding
to several probability distributions.
It also contains functions that can be used for
running the constructed StochProcess
es and generating
datapoints, or sampling from a constructed Sample
.
Some examples for usage can be found here: http://kevinl.io/posts/2016-08-17-sampling-monad.html
- mkSample :: (RandomGen g, Sampleable d) => d a -> Sample g d a
- certain :: (RandomGen g, Sampleable d) => a -> Sample g d a
- discreteUniform :: RandomGen g => [a] -> Sample g Distribution a
- discrete :: RandomGen g => [(a, Double)] -> Sample g Distribution a
- bernoulli :: RandomGen g => Double -> Sample g Distribution Bool
- normal :: RandomGen g => Mean -> StDev -> Sample g Distribution Double
- uniform :: RandomGen g => Sample g Distribution Double
- gamma :: RandomGen g => Double -> Double -> Sample g Distribution Double
- beta :: RandomGen g => Double -> Double -> Sample g Distribution Double
- sample :: (RandomGen g, Sampleable d) => Sample g d a -> g -> (a, g)
- sample_ :: (RandomGen g, Sampleable d) => Sample g d a -> g -> a
- sampleN :: (RandomGen g, Sampleable d, Integral i) => i -> Sample g d a -> g -> Seq a
- sampleIO :: Sampleable d => Sample StdGen d a -> IO (a, StdGen)
- sampleIO_ :: Sampleable d => Sample StdGen d a -> IO a
- sampleION :: (Sampleable d, Integral i) => i -> Sample StdGen d a -> IO (Seq a)
- toProcess :: Sample StdGen Distribution Double -> StochProcess
- certainProcess :: Double -> StochProcess
- discreteUniformProcess :: [Double] -> StochProcess
- discreteProcess :: [(Double, Double)] -> StochProcess
- normalProcess :: Mean -> StDev -> StochProcess
- uniformProcess :: StochProcess
- gammaProcess :: Double -> Double -> StochProcess
- betaProcess :: Double -> Double -> StochProcess
- composeProcess :: Integral i => i -> StochProcess -> (Double -> StochProcess) -> StochProcess
- runProcess :: StochProcess -> StdGen -> (Seq Double, StdGen)
- runProcess_ :: StochProcess -> StdGen -> Seq Double
- runProcessN :: Integral i => i -> StochProcess -> StdGen -> Seq (Seq Double)
- sampleProcess :: StochProcess -> StdGen -> (Double, StdGen)
- sampleProcess_ :: StochProcess -> StdGen -> Double
- sampleProcessN :: Integral i => i -> StochProcess -> StdGen -> Seq Double
- sampleProcessIO :: StochProcess -> IO (Double, StdGen)
- sampleProcessION :: Integral i => i -> StochProcess -> IO (Seq Double)
- module Data.Stochastic.Types
- module Data.Stochastic.Internal
Constructing a Sample
mkSample :: (RandomGen g, Sampleable d) => d a -> Sample g d a Source #
Function to make a Sample
out of a provided
Distribution
.
certain :: (RandomGen g, Sampleable d) => a -> Sample g d a Source #
Sample
for a distribution where we always sample
the same value.
discreteUniform :: RandomGen g => [a] -> Sample g Distribution a Source #
Sample
for a discrete uniform distribution
given a list of provided values.
bernoulli :: RandomGen g => Double -> Sample g Distribution Bool Source #
Sample
for a Bernoulli distribution with given
probability to produce True.
uniform :: RandomGen g => Sample g Distribution Double Source #
Sample
for a continuous uniform distribution
with support [0, 1].
:: RandomGen g | |
=> Double | The shape parameter. |
-> Double | The scale parameter. |
-> Sample g Distribution Double |
Sample
for a gamma distribution given shape parameter
and scale parameter.
beta :: RandomGen g => Double -> Double -> Sample g Distribution Double Source #
Sample
for a beta distribution.
Sampling from a Sample
sampleN :: (RandomGen g, Sampleable d, Integral i) => i -> Sample g d a -> g -> Seq a Source #
Get a certain number of samples from the Sample
sampleION :: (Sampleable d, Integral i) => i -> Sample StdGen d a -> IO (Seq a) Source #
Produce several samples from the Sample
using the random number generator
in the IO monad.
Constructing a StochProcess
toProcess :: Sample StdGen Distribution Double -> StochProcess Source #
Function to create a StochProcess
out of a provided
Sample
over Double
s.
certainProcess :: Double -> StochProcess Source #
StochProcess
for a distribution over Double
s that always
returns the same value when sampled, and records that value.
discreteUniformProcess :: [Double] -> StochProcess Source #
StochProcess
for a discrete uniform distribution
over Double
s that records the value sampled from it.
discreteProcess :: [(Double, Double)] -> StochProcess Source #
StochProcess
for a discrete distribution over Double
s
that records the value sampled from the normal distribution.
normalProcess :: Mean -> StDev -> StochProcess Source #
StochProcess
sample for a normal distribution that records
the value sampled from the normal distribution.
uniformProcess :: StochProcess Source #
StochProcess
for a discrete uniform distribution
over Double
s that records the value sampled from it.
gammaProcess :: Double -> Double -> StochProcess Source #
StochProcess
for a gamma distribution with
provided shape and scale parameters.
betaProcess :: Double -> Double -> StochProcess Source #
StochProcess
for a beta distribution.
composeProcess :: Integral i => i -> StochProcess -> (Double -> StochProcess) -> StochProcess Source #
Function to construct a StochProcess
computation
given an initial computation, a StochProcess
function,
and number of times to apply the function with bind.
Running a StochProcess
runProcess :: StochProcess -> StdGen -> (Seq Double, StdGen) Source #
Run a StochProcess
computation and retrieve the recorded
results along with a new RandomGen
.
runProcess_ :: StochProcess -> StdGen -> Seq Double Source #
Run a StochProcess
computation and retrieve the recorded
results, discarding the new RandomGen
.
runProcessN :: Integral i => i -> StochProcess -> StdGen -> Seq (Seq Double) Source #
Runs a StochProcess
computation a given number times
and produces a Sequence
of Sequence
s of Doubles.
Sampling from a StochProcess
sampleProcess :: StochProcess -> StdGen -> (Double, StdGen) Source #
Sample from the StochProcess
computation, returning
the value of type a and a new RandomGen
.
sampleProcess_ :: StochProcess -> StdGen -> Double Source #
Sample from the StochProcess
computation, discarding
the new RandomGen
.
sampleProcessN :: Integral i => i -> StochProcess -> StdGen -> Seq Double Source #
Get a certain number of samples from the StochProcess
computation.
sampleProcessIO :: StochProcess -> IO (Double, StdGen) Source #
Sample from the StochProcess
computation
in the IO monad, returning a Double
and a RandomGen
created in the IO monad.
sampleProcessION :: Integral i => i -> StochProcess -> IO (Seq Double) Source #
Get a certain number of samples from the StochProcess
computation in the IO monad.
The types
module Data.Stochastic.Types
Internal functions for your viewing pleasure
module Data.Stochastic.Internal