aivika-transformers-5.3.1: Transformers for the Aivika simulation library

CopyrightCopyright (c) 2009-2017 David Sorokin <david.sorokin@gmail.com>
LicenseBSD3
MaintainerDavid Sorokin <david.sorokin@gmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Simulation.Aivika.Trans.SystemDynamics

Contents

Description

Tested with: GHC 8.0.1

This module defines integrals and other functions of System Dynamics.

Synopsis

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

integ Source #

Arguments

:: (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]

integEither Source #

Arguments

:: (MonadSD m, MonadFix m) 
=> Dynamics m (Either Double Double)

either set a new Left integral value, or use a Right derivative

-> Dynamics m Double

the initial value

-> Simulation m (Dynamics m Double) 

Like integ but allows either setting a new Left integral value, or integrating using the Right derivative directly within computation.

This function always uses Euler's method.

smoothI Source #

Arguments

:: (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

smooth Source #

Arguments

:: (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.

smooth3I Source #

Arguments

:: (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

smooth3 Source #

Arguments

:: (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.

smoothNI Source #

Arguments

:: (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.

smoothN Source #

Arguments

:: (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.

delay1I Source #

Arguments

:: (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

delay1 Source #

Arguments

:: (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.

delay3I Source #

Arguments

:: (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.

delay3 Source #

Arguments

:: (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.

delayNI Source #

Arguments

:: (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.

delayN Source #

Arguments

:: (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.

forecast Source #

Arguments

:: (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)

trend Source #

Arguments

:: (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

diffsum Source #

Arguments

:: (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.

diffsumEither Source #

Arguments

:: (MonadSD m, MonadFix m, MonadMemo m a, Num a) 
=> Dynamics m (Either a a)

either set the Left value for the sum, or add the Right difference to the sum

-> Dynamics m a

the initial value

-> Simulation m (Dynamics m a)

the sum

Like diffsum but allows either setting a new Left sum value, or adding the Right difference.

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

delay Source #

Arguments

:: 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.

delayI Source #

Arguments

:: 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.

step Source #

Arguments

:: Monad m 
=> Dynamics m Double

the height

-> Dynamics m Double

the step time

-> Dynamics m Double 

Computation that returns 0 until the step time and then returns the specified height.

pulse Source #

Arguments

:: 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.

pulseP Source #

Arguments

:: 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.

ramp Source #

Arguments

:: 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

npv Source #

Arguments

:: (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

npve Source #

Arguments

:: (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