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 integrals and other functions of System Dynamics.
Synopsis
- (.==.) :: (Monad m, Eq a) => Dynamics m a -> Dynamics m a -> Dynamics m Bool
- (./=.) :: (Monad m, Eq a) => Dynamics m a -> Dynamics m a -> Dynamics m Bool
- (.<.) :: (Monad m, Ord a) => Dynamics m a -> Dynamics m a -> Dynamics m Bool
- (.>=.) :: (Monad m, Ord a) => Dynamics m a -> Dynamics m a -> Dynamics m Bool
- (.>.) :: (Monad m, Ord a) => Dynamics m a -> Dynamics m a -> Dynamics m Bool
- (.<=.) :: (Monad m, Ord a) => Dynamics m a -> Dynamics m a -> Dynamics m Bool
- maxDynamics :: (Monad m, Ord a) => Dynamics m a -> Dynamics m a -> Dynamics m a
- minDynamics :: (Monad m, Ord a) => Dynamics m a -> Dynamics m a -> Dynamics m a
- ifDynamics :: Monad m => Dynamics m Bool -> Dynamics m a -> Dynamics m a -> Dynamics m a
- integ :: (MonadSD m, MonadFix m) => Dynamics m Double -> Dynamics m Double -> Simulation m (Dynamics m Double)
- integEither :: (MonadSD m, MonadFix m) => Dynamics m (Either Double Double) -> Dynamics m Double -> Simulation m (Dynamics m Double)
- smoothI :: (MonadSD m, MonadFix m) => Dynamics m Double -> Dynamics m Double -> Dynamics m Double -> Simulation m (Dynamics m Double)
- smooth :: (MonadSD m, MonadFix m) => Dynamics m Double -> Dynamics m Double -> Simulation m (Dynamics m Double)
- smooth3I :: (MonadSD m, MonadFix m) => Dynamics m Double -> Dynamics m Double -> Dynamics m Double -> Simulation m (Dynamics m Double)
- smooth3 :: (MonadSD m, MonadFix m) => Dynamics m Double -> Dynamics m Double -> Simulation m (Dynamics m Double)
- smoothNI :: (MonadSD m, MonadFix m) => Dynamics m Double -> Dynamics m Double -> Int -> Dynamics m Double -> Simulation m (Dynamics m Double)
- smoothN :: (MonadSD m, MonadFix m) => Dynamics m Double -> Dynamics m Double -> Int -> Simulation m (Dynamics m Double)
- delay1I :: (MonadSD m, MonadFix m) => Dynamics m Double -> Dynamics m Double -> Dynamics m Double -> Simulation m (Dynamics m Double)
- delay1 :: (MonadSD m, MonadFix m) => Dynamics m Double -> Dynamics m Double -> Simulation m (Dynamics m Double)
- delay3I :: (MonadSD m, MonadFix m) => Dynamics m Double -> Dynamics m Double -> Dynamics m Double -> Simulation m (Dynamics m Double)
- delay3 :: (MonadSD m, MonadFix m) => Dynamics m Double -> Dynamics m Double -> Simulation m (Dynamics m Double)
- delayNI :: (MonadSD m, MonadFix m) => Dynamics m Double -> Dynamics m Double -> Int -> Dynamics m Double -> Simulation m (Dynamics m Double)
- delayN :: (MonadSD m, MonadFix m) => Dynamics m Double -> Dynamics m Double -> Int -> Simulation m (Dynamics m Double)
- forecast :: (MonadSD m, MonadFix m) => Dynamics m Double -> Dynamics m Double -> Dynamics m Double -> Simulation m (Dynamics m Double)
- trend :: (MonadSD m, MonadFix m) => Dynamics m Double -> Dynamics m Double -> Dynamics m Double -> Simulation m (Dynamics m Double)
- diffsum :: (MonadSD m, MonadFix m, MonadMemo m a, Num a) => Dynamics m a -> Dynamics m a -> Simulation m (Dynamics m a)
- diffsumEither :: (MonadSD m, MonadFix m, MonadMemo m a, Num a) => Dynamics m (Either a a) -> Dynamics m a -> Simulation m (Dynamics m a)
- lookupDynamics :: Monad m => Dynamics m Double -> Array Int (Double, Double) -> Dynamics m Double
- lookupStepwiseDynamics :: Monad m => Dynamics m Double -> Array Int (Double, Double) -> Dynamics m Double
- delay :: Monad m => Dynamics m a -> Dynamics m Double -> Dynamics m a
- delayI :: MonadSD m => Dynamics m a -> Dynamics m Double -> Dynamics m a -> Simulation m (Dynamics m a)
- delayByDT :: Monad m => Dynamics m a -> Dynamics m Int -> Dynamics m a
- delayIByDT :: MonadSD m => Dynamics m a -> Dynamics m Int -> Dynamics m a -> Simulation m (Dynamics m a)
- step :: Monad m => Dynamics m Double -> Dynamics m Double -> Dynamics m Double
- pulse :: Monad m => Dynamics m Double -> Dynamics m Double -> Dynamics m Double
- pulseP :: Monad m => Dynamics m Double -> Dynamics m Double -> Dynamics m Double -> Dynamics m Double
- ramp :: Monad m => Dynamics m Double -> Dynamics m Double -> Dynamics m Double -> Dynamics m Double
- npv :: (MonadSD m, MonadFix m) => Dynamics m Double -> Dynamics m Double -> Dynamics m Double -> Dynamics m Double -> Simulation m (Dynamics m Double)
- npve :: (MonadSD m, MonadFix m) => Dynamics m Double -> Dynamics m Double -> Dynamics m Double -> Dynamics m Double -> Simulation m (Dynamics m Double)
Equality and Ordering
(.==.) :: (Monad m, Eq a) => Dynamics m a -> Dynamics m a -> Dynamics m Bool Source #
Compare for equality.
(./=.) :: (Monad m, Eq a) => Dynamics m a -> Dynamics m a -> Dynamics m Bool Source #
Compare for inequality.
(.<.) :: (Monad m, Ord a) => Dynamics m a -> Dynamics m a -> Dynamics m Bool Source #
Compare for ordering.
(.>=.) :: (Monad m, Ord a) => Dynamics m a -> Dynamics m a -> Dynamics m Bool Source #
Compare for ordering.
(.>.) :: (Monad m, Ord a) => Dynamics m a -> Dynamics m a -> Dynamics m Bool Source #
Compare for ordering.
(.<=.) :: (Monad m, Ord a) => Dynamics m a -> Dynamics m a -> Dynamics m Bool Source #
Compare for ordering.
maxDynamics :: (Monad m, Ord a) => Dynamics m a -> Dynamics m a -> Dynamics m a Source #
Return the maximum.
minDynamics :: (Monad m, Ord a) => Dynamics m a -> Dynamics m a -> Dynamics m a Source #
Return the minimum.
ifDynamics :: Monad m => Dynamics m Bool -> Dynamics m a -> Dynamics m a -> Dynamics m a Source #
Implement the if-then-else operator.
Ordinary Differential Equations
:: (MonadSD m, MonadFix m) | |
=> Dynamics m Double | the derivative |
-> Dynamics m Double | the initial value |
-> Simulation m (Dynamics m Double) | the integral |
Return an integral with the specified derivative and initial value.
To create a loopback, you should use the recursive do-notation. It allows defining the differential equations unordered as in mathematics:
model = mdo a <- integ (- ka * a) 100 b <- integ (ka * a - kb * b) 0 c <- integ (kb * b) 0 let ka = 1 kb = 1 runDynamicsInStopTime $ sequence [a, b, c]
:: (MonadSD m, MonadFix m) | |
=> Dynamics m Double | the value to smooth over time |
-> Dynamics m Double | time |
-> Dynamics m Double | the initial value |
-> Simulation m (Dynamics m Double) | the first order exponential smooth |
Return the first order exponential smooth.
To create a loopback, you should use the recursive do-notation with help of which the function itself is defined:
smoothI x t i = mdo y <- integ ((x - y) / t) i return y
:: (MonadSD m, MonadFix m) | |
=> Dynamics m Double | the value to smooth over time |
-> Dynamics m Double | time |
-> Simulation m (Dynamics m Double) | the first order exponential smooth |
Return the first order exponential smooth.
This is a simplified version of the smoothI
function
without specifing the initial value.
:: (MonadSD m, MonadFix m) | |
=> Dynamics m Double | the value to smooth over time |
-> Dynamics m Double | time |
-> Dynamics m Double | the initial value |
-> Simulation m (Dynamics m Double) | the third order exponential smooth |
Return the third order exponential smooth.
To create a loopback, you should use the recursive do-notation with help of which the function itself is defined:
smooth3I x t i = mdo y <- integ ((s2 - y) / t') i s2 <- integ ((s1 - s2) / t') i s1 <- integ ((x - s1) / t') i let t' = t / 3.0 return y
:: (MonadSD m, MonadFix m) | |
=> Dynamics m Double | the value to smooth over time |
-> Dynamics m Double | time |
-> Simulation m (Dynamics m Double) | the third order exponential smooth |
Return the third order exponential smooth.
This is a simplified version of the smooth3I
function
without specifying the initial value.
:: (MonadSD m, MonadFix m) | |
=> Dynamics m Double | the value to smooth over time |
-> Dynamics m Double | time |
-> Int | the order |
-> Dynamics m Double | the initial value |
-> Simulation m (Dynamics m Double) | the n'th order exponential smooth |
Return the n'th order exponential smooth.
The result is not discrete in that sense that it may change within the integration time
interval depending on the integration method used. Probably, you should apply
the discreteDynamics
function to the result if you want to achieve an effect when
the value is not changed within the time interval, which is used sometimes.
:: (MonadSD m, MonadFix m) | |
=> Dynamics m Double | the value to smooth over time |
-> Dynamics m Double | time |
-> Int | the order |
-> Simulation m (Dynamics m Double) | the n'th order exponential smooth |
Return the n'th order exponential smooth.
This is a simplified version of the smoothNI
function
without specifying the initial value.
:: (MonadSD m, MonadFix m) | |
=> Dynamics m Double | the value to conserve |
-> Dynamics m Double | time |
-> Dynamics m Double | the initial value |
-> Simulation m (Dynamics m Double) | the first order exponential delay |
Return the first order exponential delay.
To create a loopback, you should use the recursive do-notation with help of which the function itself is defined:
delay1I x t i = mdo y <- integ (x - y / t) (i * t) return $ y / t
:: (MonadSD m, MonadFix m) | |
=> Dynamics m Double | the value to conserve |
-> Dynamics m Double | time |
-> Simulation m (Dynamics m Double) | the first order exponential delay |
Return the first order exponential delay.
This is a simplified version of the delay1I
function
without specifying the initial value.
:: (MonadSD m, MonadFix m) | |
=> Dynamics m Double | the value to conserve |
-> Dynamics m Double | time |
-> Dynamics m Double | the initial value |
-> Simulation m (Dynamics m Double) | the third order exponential delay |
Return the third order exponential delay.
:: (MonadSD m, MonadFix m) | |
=> Dynamics m Double | the value to conserve |
-> Dynamics m Double | time |
-> Simulation m (Dynamics m Double) | the third order exponential delay |
Return the third order exponential delay.
This is a simplified version of the delay3I
function
without specifying the initial value.
:: (MonadSD m, MonadFix m) | |
=> Dynamics m Double | the value to conserve |
-> Dynamics m Double | time |
-> Int | the order |
-> Dynamics m Double | the initial value |
-> Simulation m (Dynamics m Double) | the n'th order exponential delay |
Return the n'th order exponential delay.
:: (MonadSD m, MonadFix m) | |
=> Dynamics m Double | the value to conserve |
-> Dynamics m Double | time |
-> Int | the order |
-> Simulation m (Dynamics m Double) | the n'th order exponential delay |
Return the n'th order exponential delay.
This is a simplified version of the delayNI
function
without specifying the initial value.
:: (MonadSD m, MonadFix m) | |
=> Dynamics m Double | the value to forecast |
-> Dynamics m Double | the average time |
-> Dynamics m Double | the time horizon |
-> Simulation m (Dynamics m Double) | the forecast |
Return the forecast.
The function has the following definition:
forecast x at hz = do y <- smooth x at return $ x * (1.0 + (x / y - 1.0) / at * hz)
:: (MonadSD m, MonadFix m) | |
=> Dynamics m Double | the value for which the trend is calculated |
-> Dynamics m Double | the average time |
-> Dynamics m Double | the initial value |
-> Simulation m (Dynamics m Double) | the fractional change rate |
Return the trend.
The function has the following definition:
trend x at i = do y <- smoothI x at (x / (1.0 + i * at)) return $ (x / y - 1.0) / at
Difference Equations
:: (MonadSD m, MonadFix m, MonadMemo m a, Num a) | |
=> Dynamics m a | the difference |
-> Dynamics m a | the initial value |
-> Simulation m (Dynamics m a) | the sum |
Retun the sum for the difference equation.
It is like an integral returned by the integ
function, only now
the difference is used instead of derivative.
As usual, to create a loopback, you should use the recursive do-notation.
Table Functions
lookupDynamics :: Monad m => Dynamics m Double -> Array Int (Double, Double) -> Dynamics m Double Source #
Lookup x
in a table of pairs (x, y)
using linear interpolation.
lookupStepwiseDynamics :: Monad m => Dynamics m Double -> Array Int (Double, Double) -> Dynamics m Double Source #
Lookup x
in a table of pairs (x, y)
using stepwise function.
Discrete Functions
:: Monad m | |
=> Dynamics m a | the value to delay |
-> Dynamics m Double | the lag time |
-> Dynamics m a | the delayed value |
Return the delayed value using the specified lag time.
This function is less accurate than delayByDT
.
:: MonadSD m | |
=> Dynamics m a | the value to delay |
-> Dynamics m Double | the lag time |
-> Dynamics m a | the initial value |
-> Simulation m (Dynamics m a) | the delayed value |
Return the delayed value using the specified lag time and initial value.
Because of the latter, it allows creating a loop back.
This function is less accurate than delayIByDT
.
:: Monad m | |
=> Dynamics m a | the value to delay |
-> Dynamics m Int | the delay as a multiplication of the corresponding number and the integration time step |
-> Dynamics m a | the delayed value |
Return the delayed value by the specified positive number of integration time steps used for calculating the lag time.
:: MonadSD m | |
=> Dynamics m a | the value to delay |
-> Dynamics m Int | the delay as a multiplication of the corresponding number and the integration time step |
-> Dynamics m a | the initial value |
-> Simulation m (Dynamics m a) | the delayed value |
Return the delayed value by the specified initial value and a positive number of integration time steps used for calculating the lag time. It allows creating a loop back.
Computation that returns 0 until the step time and then returns the specified height.
:: Monad m | |
=> Dynamics m Double | the time start |
-> Dynamics m Double | the interval width |
-> Dynamics m Double |
Computation that returns 1, starting at the time start, and lasting for the interval width; 0 is returned at all other times.
:: Monad m | |
=> Dynamics m Double | the time start |
-> Dynamics m Double | the interval width |
-> Dynamics m Double | the time period |
-> Dynamics m Double |
Computation that returns 1, starting at the time start, and lasting for the interval width and then repeats this pattern with the specified period; 0 is returned at all other times.
:: Monad m | |
=> Dynamics m Double | the slope parameter |
-> Dynamics m Double | the time start |
-> Dynamics m Double | the end time |
-> Dynamics m Double |
Computation that returns 0 until the specified time start and then slopes upward until the end time and then holds constant.
Financial Functions
:: (MonadSD m, MonadFix m) | |
=> Dynamics m Double | the stream |
-> Dynamics m Double | the discount rate |
-> Dynamics m Double | the initial value |
-> Dynamics m Double | factor |
-> Simulation m (Dynamics m Double) | the Net Present Value (NPV) |
Return the Net Present Value (NPV) of the stream computed using the specified discount rate, the initial value and some factor (usually 1).
It is defined in the following way:
npv stream rate init factor = mdo let dt' = liftParameter dt df <- integ (- df * rate) 1 accum <- integ (stream * df) init return $ (accum + dt' * stream * df) * factor
:: (MonadSD m, MonadFix m) | |
=> Dynamics m Double | the stream |
-> Dynamics m Double | the discount rate |
-> Dynamics m Double | the initial value |
-> Dynamics m Double | factor |
-> Simulation m (Dynamics m Double) | the Net Present Value End (NPVE) |
Return the Net Present Value End of period (NPVE) of the stream computed using the specified discount rate, the initial value and some factor.
It is defined in the following way:
npve stream rate init factor = mdo let dt' = liftParameter dt df <- integ (- df * rate / (1 + rate * dt')) (1 / (1 + rate * dt')) accum <- integ (stream * df) init return $ (accum + dt' * stream * df) * factor