module Simulation.Aivika.Activity.Random
(newRandomUniformActivity,
newRandomUniformIntActivity,
newRandomTriangularActivity,
newRandomNormalActivity,
newRandomLogNormalActivity,
newRandomExponentialActivity,
newRandomErlangActivity,
newRandomPoissonActivity,
newRandomBinomialActivity,
newRandomGammaActivity,
newRandomBetaActivity,
newRandomWeibullActivity,
newRandomDiscreteActivity,
newPreemptibleRandomUniformActivity,
newPreemptibleRandomUniformIntActivity,
newPreemptibleRandomTriangularActivity,
newPreemptibleRandomNormalActivity,
newPreemptibleRandomLogNormalActivity,
newPreemptibleRandomExponentialActivity,
newPreemptibleRandomErlangActivity,
newPreemptibleRandomPoissonActivity,
newPreemptibleRandomBinomialActivity,
newPreemptibleRandomGammaActivity,
newPreemptibleRandomBetaActivity,
newPreemptibleRandomWeibullActivity,
newPreemptibleRandomDiscreteActivity) where
import Simulation.Aivika.Generator
import Simulation.Aivika.Simulation
import Simulation.Aivika.Process
import Simulation.Aivika.Process.Random
import Simulation.Aivika.Activity
newRandomUniformActivity :: Double
-> Double
-> Simulation (Activity () a a)
newRandomUniformActivity :: forall a. Double -> Double -> Simulation (Activity () a a)
newRandomUniformActivity =
forall a. Bool -> Double -> Double -> Simulation (Activity () a a)
newPreemptibleRandomUniformActivity Bool
False
newRandomUniformIntActivity :: Int
-> Int
-> Simulation (Activity () a a)
newRandomUniformIntActivity :: forall a. Int -> Int -> Simulation (Activity () a a)
newRandomUniformIntActivity =
forall a. Bool -> Int -> Int -> Simulation (Activity () a a)
newPreemptibleRandomUniformIntActivity Bool
False
newRandomTriangularActivity :: Double
-> Double
-> Double
-> Simulation (Activity () a a)
newRandomTriangularActivity :: forall a.
Double -> Double -> Double -> Simulation (Activity () a a)
newRandomTriangularActivity =
forall a.
Bool -> Double -> Double -> Double -> Simulation (Activity () a a)
newPreemptibleRandomTriangularActivity Bool
False
newRandomNormalActivity :: Double
-> Double
-> Simulation (Activity () a a)
newRandomNormalActivity :: forall a. Double -> Double -> Simulation (Activity () a a)
newRandomNormalActivity =
forall a. Bool -> Double -> Double -> Simulation (Activity () a a)
newPreemptibleRandomNormalActivity Bool
False
newRandomLogNormalActivity :: Double
-> Double
-> Simulation (Activity () a a)
newRandomLogNormalActivity :: forall a. Double -> Double -> Simulation (Activity () a a)
newRandomLogNormalActivity =
forall a. Bool -> Double -> Double -> Simulation (Activity () a a)
newPreemptibleRandomLogNormalActivity Bool
False
newRandomExponentialActivity :: Double
-> Simulation (Activity () a a)
newRandomExponentialActivity :: forall a. Double -> Simulation (Activity () a a)
newRandomExponentialActivity =
forall a. Bool -> Double -> Simulation (Activity () a a)
newPreemptibleRandomExponentialActivity Bool
False
newRandomErlangActivity :: Double
-> Int
-> Simulation (Activity () a a)
newRandomErlangActivity :: forall a. Double -> Int -> Simulation (Activity () a a)
newRandomErlangActivity =
forall a. Bool -> Double -> Int -> Simulation (Activity () a a)
newPreemptibleRandomErlangActivity Bool
False
newRandomPoissonActivity :: Double
-> Simulation (Activity () a a)
newRandomPoissonActivity :: forall a. Double -> Simulation (Activity () a a)
newRandomPoissonActivity =
forall a. Bool -> Double -> Simulation (Activity () a a)
newPreemptibleRandomPoissonActivity Bool
False
newRandomBinomialActivity :: Double
-> Int
-> Simulation (Activity () a a)
newRandomBinomialActivity :: forall a. Double -> Int -> Simulation (Activity () a a)
newRandomBinomialActivity =
forall a. Bool -> Double -> Int -> Simulation (Activity () a a)
newPreemptibleRandomBinomialActivity Bool
False
newRandomGammaActivity :: Double
-> Double
-> Simulation (Activity () a a)
newRandomGammaActivity :: forall a. Double -> Double -> Simulation (Activity () a a)
newRandomGammaActivity =
forall a. Bool -> Double -> Double -> Simulation (Activity () a a)
newPreemptibleRandomGammaActivity Bool
False
newRandomBetaActivity :: Double
-> Double
-> Simulation (Activity () a a)
newRandomBetaActivity :: forall a. Double -> Double -> Simulation (Activity () a a)
newRandomBetaActivity =
forall a. Bool -> Double -> Double -> Simulation (Activity () a a)
newPreemptibleRandomBetaActivity Bool
False
newRandomWeibullActivity :: Double
-> Double
-> Simulation (Activity () a a)
newRandomWeibullActivity :: forall a. Double -> Double -> Simulation (Activity () a a)
newRandomWeibullActivity =
forall a. Bool -> Double -> Double -> Simulation (Activity () a a)
newPreemptibleRandomWeibullActivity Bool
False
newRandomDiscreteActivity :: DiscretePDF Double
-> Simulation (Activity () a a)
newRandomDiscreteActivity :: forall a. DiscretePDF Double -> Simulation (Activity () a a)
newRandomDiscreteActivity =
forall a.
Bool -> DiscretePDF Double -> Simulation (Activity () a a)
newPreemptibleRandomDiscreteActivity Bool
False
newPreemptibleRandomUniformActivity :: Bool
-> Double
-> Double
-> Simulation (Activity () a a)
newPreemptibleRandomUniformActivity :: forall a. Bool -> Double -> Double -> Simulation (Activity () a a)
newPreemptibleRandomUniformActivity Bool
preemptible Double
min Double
max =
forall a b.
Bool -> (a -> Process b) -> Simulation (Activity () a b)
newPreemptibleActivity Bool
preemptible forall a b. (a -> b) -> a -> b
$ \a
a ->
do Double -> Double -> Process ()
randomUniformProcess_ Double
min Double
max
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
newPreemptibleRandomUniformIntActivity :: Bool
-> Int
-> Int
-> Simulation (Activity () a a)
newPreemptibleRandomUniformIntActivity :: forall a. Bool -> Int -> Int -> Simulation (Activity () a a)
newPreemptibleRandomUniformIntActivity Bool
preemptible Int
min Int
max =
forall a b.
Bool -> (a -> Process b) -> Simulation (Activity () a b)
newPreemptibleActivity Bool
preemptible forall a b. (a -> b) -> a -> b
$ \a
a ->
do Int -> Int -> Process ()
randomUniformIntProcess_ Int
min Int
max
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
newPreemptibleRandomTriangularActivity :: Bool
-> Double
-> Double
-> Double
-> Simulation (Activity () a a)
newPreemptibleRandomTriangularActivity :: forall a.
Bool -> Double -> Double -> Double -> Simulation (Activity () a a)
newPreemptibleRandomTriangularActivity Bool
preemptible Double
min Double
median Double
max =
forall a b.
Bool -> (a -> Process b) -> Simulation (Activity () a b)
newPreemptibleActivity Bool
preemptible forall a b. (a -> b) -> a -> b
$ \a
a ->
do Double -> Double -> Double -> Process ()
randomTriangularProcess_ Double
min Double
median Double
max
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
newPreemptibleRandomNormalActivity :: Bool
-> Double
-> Double
-> Simulation (Activity () a a)
newPreemptibleRandomNormalActivity :: forall a. Bool -> Double -> Double -> Simulation (Activity () a a)
newPreemptibleRandomNormalActivity Bool
preemptible Double
mu Double
nu =
forall a b.
Bool -> (a -> Process b) -> Simulation (Activity () a b)
newPreemptibleActivity Bool
preemptible forall a b. (a -> b) -> a -> b
$ \a
a ->
do Double -> Double -> Process ()
randomNormalProcess_ Double
mu Double
nu
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
newPreemptibleRandomLogNormalActivity :: Bool
-> Double
-> Double
-> Simulation (Activity () a a)
newPreemptibleRandomLogNormalActivity :: forall a. Bool -> Double -> Double -> Simulation (Activity () a a)
newPreemptibleRandomLogNormalActivity Bool
preemptible Double
mu Double
nu =
forall a b.
Bool -> (a -> Process b) -> Simulation (Activity () a b)
newPreemptibleActivity Bool
preemptible forall a b. (a -> b) -> a -> b
$ \a
a ->
do Double -> Double -> Process ()
randomLogNormalProcess_ Double
mu Double
nu
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
newPreemptibleRandomExponentialActivity :: Bool
-> Double
-> Simulation (Activity () a a)
newPreemptibleRandomExponentialActivity :: forall a. Bool -> Double -> Simulation (Activity () a a)
newPreemptibleRandomExponentialActivity Bool
preemptible Double
mu =
forall a b.
Bool -> (a -> Process b) -> Simulation (Activity () a b)
newPreemptibleActivity Bool
preemptible forall a b. (a -> b) -> a -> b
$ \a
a ->
do Double -> Process ()
randomExponentialProcess_ Double
mu
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
newPreemptibleRandomErlangActivity :: Bool
-> Double
-> Int
-> Simulation (Activity () a a)
newPreemptibleRandomErlangActivity :: forall a. Bool -> Double -> Int -> Simulation (Activity () a a)
newPreemptibleRandomErlangActivity Bool
preemptible Double
beta Int
m =
forall a b.
Bool -> (a -> Process b) -> Simulation (Activity () a b)
newPreemptibleActivity Bool
preemptible forall a b. (a -> b) -> a -> b
$ \a
a ->
do Double -> Int -> Process ()
randomErlangProcess_ Double
beta Int
m
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
newPreemptibleRandomPoissonActivity :: Bool
-> Double
-> Simulation (Activity () a a)
newPreemptibleRandomPoissonActivity :: forall a. Bool -> Double -> Simulation (Activity () a a)
newPreemptibleRandomPoissonActivity Bool
preemptible Double
mu =
forall a b.
Bool -> (a -> Process b) -> Simulation (Activity () a b)
newPreemptibleActivity Bool
preemptible forall a b. (a -> b) -> a -> b
$ \a
a ->
do Double -> Process ()
randomPoissonProcess_ Double
mu
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
newPreemptibleRandomBinomialActivity :: Bool
-> Double
-> Int
-> Simulation (Activity () a a)
newPreemptibleRandomBinomialActivity :: forall a. Bool -> Double -> Int -> Simulation (Activity () a a)
newPreemptibleRandomBinomialActivity Bool
preemptible Double
prob Int
trials =
forall a b.
Bool -> (a -> Process b) -> Simulation (Activity () a b)
newPreemptibleActivity Bool
preemptible forall a b. (a -> b) -> a -> b
$ \a
a ->
do Double -> Int -> Process ()
randomBinomialProcess_ Double
prob Int
trials
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
newPreemptibleRandomGammaActivity :: Bool
-> Double
-> Double
-> Simulation (Activity () a a)
newPreemptibleRandomGammaActivity :: forall a. Bool -> Double -> Double -> Simulation (Activity () a a)
newPreemptibleRandomGammaActivity Bool
preemptible Double
kappa Double
theta =
forall a b.
Bool -> (a -> Process b) -> Simulation (Activity () a b)
newPreemptibleActivity Bool
preemptible forall a b. (a -> b) -> a -> b
$ \a
a ->
do Double -> Double -> Process ()
randomGammaProcess_ Double
kappa Double
theta
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
newPreemptibleRandomBetaActivity :: Bool
-> Double
-> Double
-> Simulation (Activity () a a)
newPreemptibleRandomBetaActivity :: forall a. Bool -> Double -> Double -> Simulation (Activity () a a)
newPreemptibleRandomBetaActivity Bool
preemptible Double
alpha Double
beta =
forall a b.
Bool -> (a -> Process b) -> Simulation (Activity () a b)
newPreemptibleActivity Bool
preemptible forall a b. (a -> b) -> a -> b
$ \a
a ->
do Double -> Double -> Process ()
randomBetaProcess_ Double
alpha Double
beta
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
newPreemptibleRandomWeibullActivity :: Bool
-> Double
-> Double
-> Simulation (Activity () a a)
newPreemptibleRandomWeibullActivity :: forall a. Bool -> Double -> Double -> Simulation (Activity () a a)
newPreemptibleRandomWeibullActivity Bool
preemptible Double
alpha Double
beta =
forall a b.
Bool -> (a -> Process b) -> Simulation (Activity () a b)
newPreemptibleActivity Bool
preemptible forall a b. (a -> b) -> a -> b
$ \a
a ->
do Double -> Double -> Process ()
randomWeibullProcess_ Double
alpha Double
beta
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
newPreemptibleRandomDiscreteActivity :: Bool
-> DiscretePDF Double
-> Simulation (Activity () a a)
newPreemptibleRandomDiscreteActivity :: forall a.
Bool -> DiscretePDF Double -> Simulation (Activity () a a)
newPreemptibleRandomDiscreteActivity Bool
preemptible DiscretePDF Double
dpdf =
forall a b.
Bool -> (a -> Process b) -> Simulation (Activity () a b)
newPreemptibleActivity Bool
preemptible forall a b. (a -> b) -> a -> b
$ \a
a ->
do DiscretePDF Double -> Process ()
randomDiscreteProcess_ DiscretePDF Double
dpdf
forall (m :: * -> *) a. Monad m => a -> m a
return a
a