Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- runPopulationCl :: forall m cl a b. (Monad m, MonadDistribution m) => Int -> (forall x m. MonadDistribution m => PopulationT m x -> PopulationT m x) -> ClSF (PopulationT m) cl a b -> ClSF m cl a [(b, Log Double)]
- type StochasticProcess time a = forall m. MonadDistribution m => Behaviour m time a
- type StochasticProcessF time a b = forall m. MonadDistribution m => BehaviourF m time a b
- whiteNoise :: Double -> StochasticProcess td Double
- whiteNoiseVarying :: StochasticProcessF td Double Double
- levy :: (MonadDistribution m, VectorSpace v (Diff td)) => (Diff td -> m v) -> Behaviour m td v
- wiener :: (MonadDistribution m, Diff td ~ Double) => Diff td -> Behaviour m td Double
- brownianMotion :: (MonadDistribution m, Diff td ~ Double) => Diff td -> Behaviour m td Double
- wienerVarying :: Diff td ~ Double => StochasticProcessF td (Diff td) Double
- brownianMotionVarying :: Diff td ~ Double => StochasticProcessF td (Diff td) Double
- wienerLogDomain :: Diff td ~ Double => Diff td -> StochasticProcess td (Log Double)
- wienerVaryingLogDomain :: Diff td ~ Double => StochasticProcessF td (Diff td) (Log Double)
- poissonInhomogeneous :: (MonadDistribution m, Real (Diff td), Fractional (Diff td)) => BehaviourF m td (Diff td) Int
- poissonHomogeneous :: (MonadDistribution m, Real (Diff td), Fractional (Diff td)) => Diff td -> BehaviourF m td () Int
- gammaInhomogeneous :: (MonadDistribution m, Real (Diff td), Fractional (Diff td), Floating (Diff td)) => Diff td -> BehaviourF m td (Diff td) Int
- bernoulliInhomogeneous :: MonadDistribution m => BehaviourF m td Double Bool
Inference methods
:: forall m cl a b. (Monad m, MonadDistribution m) | |
=> Int | Number of particles |
-> (forall x m. MonadDistribution m => PopulationT m x -> PopulationT m x) | Resampler (see |
-> ClSF (PopulationT m) cl a b | A signal function modelling the stochastic process on which to perform inference.
|
-> ClSF m cl a [(b, Log Double)] |
Run the Sequential Monte Carlo algorithm continuously on a ClSF
.
Short standard library of stochastic processes
type StochasticProcess time a = forall m. MonadDistribution m => Behaviour m time a Source #
A stochastic process is a behaviour that uses, as only effect, random sampling.
type StochasticProcessF time a b = forall m. MonadDistribution m => BehaviourF m time a b Source #
Like StochasticProcess
, but with a live input.
whiteNoise :: Double -> StochasticProcess td Double Source #
White noise, that is, an independent normal distribution at every time step.
whiteNoiseVarying :: StochasticProcessF td Double Double Source #
Like whiteNoise
, that is, an independent normal distribution at every time step.
:: (MonadDistribution m, VectorSpace v (Diff td)) | |
=> (Diff td -> m v) | The increment function at every time step. The argument is the difference between times. |
-> Behaviour m td v |
Construct a Lévy process from the increment between time steps.
:: (MonadDistribution m, Diff td ~ Double) | |
=> Diff td | Time scale of variance. |
-> Behaviour m td Double |
The Wiener process, also known as Brownian motion.
:: (MonadDistribution m, Diff td ~ Double) | |
=> Diff td | Time scale of variance. |
-> Behaviour m td Double |
The Wiener process, also known as Brownian motion.
wienerVarying :: Diff td ~ Double => StochasticProcessF td (Diff td) Double Source #
The Wiener process, also known as Brownian motion, with varying variance parameter.
brownianMotionVarying :: Diff td ~ Double => StochasticProcessF td (Diff td) Double Source #
The Wiener process, also known as Brownian motion, with varying variance parameter.
The wiener
process transformed to the Log domain, also called the geometric Wiener process.
wienerVaryingLogDomain :: Diff td ~ Double => StochasticProcessF td (Diff td) (Log Double) Source #
See wienerLogDomain
and wienerVarying
.
poissonInhomogeneous :: (MonadDistribution m, Real (Diff td), Fractional (Diff td)) => BehaviourF m td (Diff td) Int Source #
Inhomogeneous Poisson point process, as described in: https://en.wikipedia.org/wiki/Poisson_point_process#Inhomogeneous_Poisson_point_process
- The input is the inverse of the current rate or intensity. It corresponds to the average duration between two events.
- The output is the number of events since the last tick.
:: (MonadDistribution m, Real (Diff td), Fractional (Diff td)) | |
=> Diff td | The (constant) rate of the process |
-> BehaviourF m td () Int |
Like poissonInhomogeneous
, but the rate is constant.
:: (MonadDistribution m, Real (Diff td), Fractional (Diff td), Floating (Diff td)) | |
=> Diff td | The scale parameter |
-> BehaviourF m td (Diff td) Int |
The Gamma process, https://en.wikipedia.org/wiki/Gamma_process.
The live input corresponds to inverse shape parameter, which is variance over mean.
bernoulliInhomogeneous :: MonadDistribution m => BehaviourF m td Double Bool Source #
The inhomogeneous Bernoulli process, https://en.wikipedia.org/wiki/Bernoulli_process
Throws a coin to a given probability at each tick. The live input is the probability.