-- | -- Module : Simulation.Aivika.Dynamics.Random -- Copyright : Copyright (c) 2009-2014, David Sorokin -- License : BSD3 -- Maintainer : David Sorokin -- Stability : experimental -- Tested with: GHC 7.8.3 -- -- This module defines the random functions that always return the same values -- in the integration time points within a single simulation run. The values -- for another simulation run will be regenerated anew. -- -- For example, the computations returned by these functions can be used in -- the equations of System Dynamics. -- -- Also it is worth noting that the values are generated in a strong order starting -- from 'starttime' with step 'dt'. This is how the 'memo0Dynamics' function -- actually works. -- module Simulation.Aivika.Dynamics.Random (memoRandomUniformDynamics, memoRandomUniformIntDynamics, memoRandomNormalDynamics, memoRandomExponentialDynamics, memoRandomErlangDynamics, memoRandomPoissonDynamics, memoRandomBinomialDynamics) where import System.Random import Control.Monad.Trans import Simulation.Aivika.Generator import Simulation.Aivika.Internal.Specs import Simulation.Aivika.Internal.Parameter import Simulation.Aivika.Internal.Simulation import Simulation.Aivika.Internal.Dynamics import Simulation.Aivika.Dynamics.Memo.Unboxed -- | Computation that generates random numbers distributed uniformly and -- memoizes them in the integration time points. memoRandomUniformDynamics :: Dynamics Double -- ^ minimum -> Dynamics Double -- ^ maximum -> Simulation (Dynamics Double) memoRandomUniformDynamics min max = memo0Dynamics $ Dynamics $ \p -> do let g = runGenerator $ pointRun p min' <- invokeDynamics p min max' <- invokeDynamics p max generateUniform g min' max' -- | Computation that generates random integer numbers distributed uniformly and -- memoizes them in the integration time points. memoRandomUniformIntDynamics :: Dynamics Int -- ^ minimum -> Dynamics Int -- ^ maximum -> Simulation (Dynamics Int) memoRandomUniformIntDynamics min max = memo0Dynamics $ Dynamics $ \p -> do let g = runGenerator $ pointRun p min' <- invokeDynamics p min max' <- invokeDynamics p max generateUniformInt g min' max' -- | Computation that generates random numbers distributed normally and -- memoizes them in the integration time points. memoRandomNormalDynamics :: Dynamics Double -- ^ mean -> Dynamics Double -- ^ deviation -> Simulation (Dynamics Double) memoRandomNormalDynamics mu nu = memo0Dynamics $ Dynamics $ \p -> do let g = runGenerator $ pointRun p mu' <- invokeDynamics p mu nu' <- invokeDynamics p nu generateNormal g mu' nu' -- | Computation that generates exponential random numbers with the specified mean -- (the reciprocal of the rate) and memoizes them in the integration time points. memoRandomExponentialDynamics :: Dynamics Double -- ^ the mean (the reciprocal of the rate) -> Simulation (Dynamics Double) memoRandomExponentialDynamics mu = memo0Dynamics $ Dynamics $ \p -> do let g = runGenerator $ pointRun p mu' <- invokeDynamics p mu generateExponential g mu' -- | Computation that generates the Erlang random numbers with the specified scale -- (the reciprocal of the rate) and integer shape but memoizes them in the integration -- time points. memoRandomErlangDynamics :: Dynamics Double -- ^ the scale (the reciprocal of the rate) -> Dynamics Int -- ^ the shape -> Simulation (Dynamics Double) memoRandomErlangDynamics beta m = memo0Dynamics $ Dynamics $ \p -> do let g = runGenerator $ pointRun p beta' <- invokeDynamics p beta m' <- invokeDynamics p m generateErlang g beta' m' -- | Computation that generats the Poisson random numbers with the specified mean -- and memoizes them in the integration time points. memoRandomPoissonDynamics :: Dynamics Double -- ^ the mean -> Simulation (Dynamics Int) memoRandomPoissonDynamics mu = memo0Dynamics $ Dynamics $ \p -> do let g = runGenerator $ pointRun p mu' <- invokeDynamics p mu generatePoisson g mu' -- | Computation that generates binomial random numbers with the specified -- probability and trials but memoizes them in the integration time points. memoRandomBinomialDynamics :: Dynamics Double -- ^ the probability -> Dynamics Int -- ^ the number of trials -> Simulation (Dynamics Int) memoRandomBinomialDynamics prob trials = memo0Dynamics $ Dynamics $ \p -> do let g = runGenerator $ pointRun p prob' <- invokeDynamics p prob trials' <- invokeDynamics p trials generateBinomial g prob' trials'