Copyright | Copyright (c) 2009-2017 David Sorokin <david.sorokin@gmail.com> |
---|---|
License | BSD3 |
Maintainer | David Sorokin <david.sorokin@gmail.com> |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Tested with: GHC 8.0.1
This module defines helper functions, which are useful to hold
the Process
computation for a time interval according to some
random distribution.
Synopsis
- randomUniformProcess :: MonadDES m => Double -> Double -> Process m Double
- randomUniformProcess_ :: MonadDES m => Double -> Double -> Process m ()
- randomUniformIntProcess :: MonadDES m => Int -> Int -> Process m Int
- randomUniformIntProcess_ :: MonadDES m => Int -> Int -> Process m ()
- randomTriangularProcess :: MonadDES m => Double -> Double -> Double -> Process m Double
- randomTriangularProcess_ :: MonadDES m => Double -> Double -> Double -> Process m ()
- randomNormalProcess :: MonadDES m => Double -> Double -> Process m Double
- randomNormalProcess_ :: MonadDES m => Double -> Double -> Process m ()
- randomLogNormalProcess :: MonadDES m => Double -> Double -> Process m Double
- randomLogNormalProcess_ :: MonadDES m => Double -> Double -> Process m ()
- randomExponentialProcess :: MonadDES m => Double -> Process m Double
- randomExponentialProcess_ :: MonadDES m => Double -> Process m ()
- randomErlangProcess :: MonadDES m => Double -> Int -> Process m Double
- randomErlangProcess_ :: MonadDES m => Double -> Int -> Process m ()
- randomPoissonProcess :: MonadDES m => Double -> Process m Int
- randomPoissonProcess_ :: MonadDES m => Double -> Process m ()
- randomBinomialProcess :: MonadDES m => Double -> Int -> Process m Int
- randomBinomialProcess_ :: MonadDES m => Double -> Int -> Process m ()
- randomGammaProcess :: MonadDES m => Double -> Double -> Process m Double
- randomGammaProcess_ :: MonadDES m => Double -> Double -> Process m ()
- randomBetaProcess :: MonadDES m => Double -> Double -> Process m Double
- randomBetaProcess_ :: MonadDES m => Double -> Double -> Process m ()
- randomWeibullProcess :: MonadDES m => Double -> Double -> Process m Double
- randomWeibullProcess_ :: MonadDES m => Double -> Double -> Process m ()
- randomDiscreteProcess :: MonadDES m => DiscretePDF Double -> Process m Double
- randomDiscreteProcess_ :: MonadDES m => DiscretePDF Double -> Process m ()
Documentation
:: MonadDES m | |
=> Double | the minimum time interval |
-> Double | the maximum time interval |
-> Process m Double | a computation of the time interval for which the process was actually held |
Hold the process for a random time interval distributed uniformly.
randomUniformProcess_ Source #
Hold the process for a random time interval distributed uniformly.
randomUniformIntProcess Source #
:: MonadDES m | |
=> Int | the minimum time interval |
-> Int | the maximum time interval |
-> Process m Int | a computation of the time interval for which the process was actually held |
Hold the process for a random time interval distributed uniformly.
randomUniformIntProcess_ Source #
Hold the process for a random time interval distributed uniformly.
randomTriangularProcess Source #
:: MonadDES m | |
=> Double | the minimum time interval |
-> Double | a median of the time interval |
-> Double | the maximum time interval |
-> Process m Double | a computation of the time interval for which the process was actually held |
Hold the process for a random time interval having the triangular distribution.
randomTriangularProcess_ Source #
:: MonadDES m | |
=> Double | the minimum time interval |
-> Double | a median of the time interval |
-> Double | the maximum time interval |
-> Process m () |
Hold the process for a random time interval having the triangular distribution.
:: MonadDES m | |
=> Double | the mean time interval |
-> Double | the time interval deviation |
-> Process m Double | a computation of the time interval for which the process was actually held |
Hold the process for a random time interval distributed normally.
Hold the process for a random time interval distributed normally.
randomLogNormalProcess Source #
:: MonadDES m | |
=> Double | the mean for a normal distribution which this distribution is derived from |
-> Double | the deviation for a normal distribution which this distribution is derived from |
-> Process m Double | a computation of the time interval for which the process was actually held |
Hold the process for a random time interval having the lognormal distribution.
randomLogNormalProcess_ Source #
:: MonadDES m | |
=> Double | the mean for a normal distribution which this distribution is derived from |
-> Double | the deviation for a normal distribution which this distribution is derived from |
-> Process m () |
Hold the process for a random time interval having the lognormal distribution.
randomExponentialProcess Source #
:: MonadDES m | |
=> Double | the mean time interval (the reciprocal of the rate) |
-> Process m Double | a computation of the time interval for which the process was actually held |
Hold the process for a random time interval distributed exponentially with the specified mean (the reciprocal of the rate).
randomExponentialProcess_ Source #
Hold the process for a random time interval distributed exponentially with the specified mean (the reciprocal of the rate).
:: MonadDES m | |
=> Double | the scale (the reciprocal of the rate) |
-> Int | the shape |
-> Process m Double | a computation of the time interval for which the process was actually held |
Hold the process for a random time interval having the Erlang distribution with the specified scale (the reciprocal of the rate) and shape parameters.
Hold the process for a random time interval having the Erlang distribution with the specified scale (the reciprocal of the rate) and shape parameters.
:: MonadDES m | |
=> Double | the mean time interval |
-> Process m Int | a computation of the time interval for which the process was actually held |
Hold the process for a random time interval having the Poisson distribution with the specified mean.
randomPoissonProcess_ Source #
Hold the process for a random time interval having the Poisson distribution with the specified mean.
randomBinomialProcess Source #
:: MonadDES m | |
=> Double | the probability |
-> Int | the number of trials |
-> Process m Int | a computation of the time interval for which the process was actually held |
Hold the process for a random time interval having the binomial distribution with the specified probability and trials.
randomBinomialProcess_ Source #
Hold the process for a random time interval having the binomial distribution with the specified probability and trials.
:: MonadDES m | |
=> Double | the shape |
-> Double | the scale (a reciprocal of the rate) |
-> Process m Double | a computation of the time interval for which the process was actually held |
Hold the process for a random time interval having the Gamma distribution with the specified shape and scale.
Hold the process for a random time interval having the Gamma distribution with the specified shape and scale.
:: MonadDES m | |
=> Double | the shape (alpha) |
-> Double | the shape (beta) |
-> Process m Double | a computation of the time interval for which the process was actually held |
Hold the process for a random time interval having the Beta distribution with the specified shape parameters (alpha and beta).
Hold the process for a random time interval having the Beta distribution with the specified shape parameters (alpha and beta).
:: MonadDES m | |
=> Double | the shape |
-> Double | the scale |
-> Process m Double | a computation of the time interval for which the process was actually held |
Hold the process for a random time interval having the Weibull distribution with the specified shape and scale.
randomWeibullProcess_ Source #
Hold the process for a random time interval having the Weibull distribution with the specified shape and scale.
randomDiscreteProcess Source #
:: MonadDES m | |
=> DiscretePDF Double | the discrete probability density function |
-> Process m Double | a computation of the time interval for which the process was actually held |
Hold the process for a random time interval having the specified discrete distribution.
randomDiscreteProcess_ Source #
:: MonadDES m | |
=> DiscretePDF Double | the discrete probability density function |
-> Process m () |
Hold the process for a random time interval having the specified discrete distribution.