aivika-0.1: A multi-paradigm simulation library

Stabilityexperimental
MaintainerDavid Sorokin <david.sorokin@gmail.com>

Simulation.Aivika.Dynamics

Contents

Description

Tested with: GHC 6.12.1

Aivika is a multi-paradigm simulation library. It allows us to integrate a system of ordinary differential equations. Also it can be applied to the Discrete Event Simulation. It supports the event-oriented, process-oriented and activity-oriented paradigms. Aivika also supports the Agent-based Modeling. Finally, it can be applied to System Dynamics.

Synopsis

Dynamics

data Dynamics a Source

A value in the Dynamics monad represents a dynamic process, i.e. a polymorphic time varying function.

class DynamicsTrans m whereSource

The DynamicsTrans class defines a type which the Dynamics computation can be lifted to.

Methods

liftD :: Dynamics a -> m aSource

Lift the computation.

Instances

data Specs Source

It defines the simulation specs.

Constructors

Specs 

Fields

spcStartTime :: Double

the start time

spcStopTime :: Double

the stop time

spcDT :: Double

the integration time step

spcMethod :: Method

the integration method

Instances

data Method Source

It defines the integration method.

Constructors

Euler

Euler's method

RungeKutta2

the 2nd order Runge-Kutta method

RungeKutta4

the 4th order Runge-Kutta method

Instances

runDynamics1 :: Dynamics (Dynamics a) -> Specs -> IO aSource

Run the simulation and return the result in the last time point using the specified simulation specs.

runDynamics :: Dynamics (Dynamics a) -> Specs -> IO [a]Source

Run the simulation and return the results in all integration time points using the specified simulation specs.

runDynamicsIO :: Dynamics (Dynamics a) -> Specs -> IO [IO a]Source

Run the simulation and return the results in all integration time points using the specified simulation specs.

Time parameters

starttime :: Dynamics DoubleSource

Return the start simulation time.

stoptime :: Dynamics DoubleSource

Return the stop simulation time.

dt :: Dynamics DoubleSource

Return the integration time step.

time :: Dynamics DoubleSource

Return the current simulation time.

Maximum and Minimum

maxD :: Ord a => Dynamics a -> Dynamics a -> Dynamics aSource

Return the maximum.

minD :: Ord a => Dynamics a -> Dynamics a -> Dynamics aSource

Return the minimum.

Integrals

data Integ Source

The Integ type represents an integral.

newInteg :: Dynamics Double -> Dynamics IntegSource

Create a new integral with the specified initial value.

integInit :: Integ -> Dynamics DoubleSource

The initial value.

integValue :: Integ -> Dynamics DoubleSource

Return the integral's value.

integDiff :: Integ -> Dynamics Double -> Dynamics ()Source

Set the derivative for the integral.

Table Functions

lookupD :: Dynamics Double -> Array Int (Double, Double) -> Dynamics DoubleSource

Lookup x in a table of pairs (x, y) using linear interpolation.

lookupStepwiseD :: Dynamics Double -> Array Int (Double, Double) -> Dynamics DoubleSource

Lookup x in a table of pairs (x, y) using stepwise function.

Interpolation

initD :: Dynamics a -> Dynamics aSource

Return the initial value.

discrete :: Dynamics a -> Dynamics aSource

Discretize the computation in the integration time points.

interpolate :: Dynamics Double -> Dynamics DoubleSource

Interpolate the computation based on the integration time points only.

Memoization and Sequential Calculations

class MArray IOArray e IO => Memo e Source

The Memo class specifies a type for which an array can be created.

Instances

Memo e 

class MArray IOUArray e IO => UMemo e Source

The UMemo class specifies a type for which an unboxed array exists.

Instances

memo :: Memo e => (Dynamics e -> Dynamics e) -> Dynamics e -> Dynamics (Dynamics e)Source

Memoize and order the computation in the integration time points using the specified interpolation and being aware of the Runge-Kutta method.

umemo :: UMemo e => (Dynamics e -> Dynamics e) -> Dynamics e -> Dynamics (Dynamics e)Source

Memoize and order the computation in the integration time points using the specified interpolation and being aware of the Runge-Kutta method.

memo0 :: Memo e => (Dynamics e -> Dynamics e) -> Dynamics e -> Dynamics (Dynamics e)Source

Memoize and order the computation in the integration time points using the specified interpolation and without knowledge of the Runge-Kutta method.

umemo0 :: UMemo e => (Dynamics e -> Dynamics e) -> Dynamics e -> Dynamics (Dynamics e)Source

Memoize and order the computation in the integration time points using the specified interpolation and without knowledge of the Runge-Kutta method.

Utility

once :: Dynamics a -> Dynamics (Dynamics a)Source

Call the computation only once.

Event Queue

data DynamicsQueue Source

The DynamicsQueue type represents the event queue.

newQueue :: Dynamics DynamicsQueueSource

Create a new event queue.

enqueueDC :: DynamicsQueue -> Dynamics Double -> Dynamics (() -> IO ()) -> Dynamics ()Source

Enqueue the event which must be actuated at the specified time.

enqueueD :: DynamicsQueue -> Dynamics Double -> Dynamics () -> Dynamics ()Source

Enqueue the event which must be actuated at the specified time.

runQueue :: DynamicsQueue -> Dynamics ()Source

Run the event queue processing its events.

References

data DynamicsRef a Source

The DynamicsRef type represents a mutable variable similar to the IORef variable but only bound to some event queue, which makes the variable coordinated with that queue.

newRef :: DynamicsQueue -> a -> Dynamics (DynamicsRef a)Source

Create a new reference bound to the specified event queue.

refQueue :: DynamicsRef a -> DynamicsQueueSource

Return the bound event queue.

readRef :: DynamicsRef a -> Dynamics aSource

Read the value of a reference, forcing the bound event queue to raise the events in case of need.

writeRef :: DynamicsRef a -> a -> Dynamics ()Source

Write a new value into the reference.

writeRef' :: DynamicsRef a -> a -> Dynamics ()Source

A strict version of the writeRef function.

modifyRef :: DynamicsRef a -> (a -> a) -> Dynamics ()Source

Mutate the contents of the reference, forcing the bound event queue to raise all pending events in case of need.

modifyRef' :: DynamicsRef a -> (a -> a) -> Dynamics ()Source

A strict version of the modifyRef function.

Discontinuous Processes

data DynamicsPID Source

Represents a process handler, its PID.

Instances

data DynamicsProc a Source

Specifies a discontinuous process that can be suspended at any time and then resumed later.

newPID :: DynamicsQueue -> Dynamics DynamicsPIDSource

Create a new process PID.

pidQueue :: DynamicsPID -> DynamicsQueueSource

Return the bound event queue.

holdProcD :: Dynamics Double -> DynamicsProc ()Source

Hold the process for the specified time period.

holdProc :: Double -> DynamicsProc ()Source

Hold the process for the specified time period.

passivateProc :: DynamicsProc ()Source

Passivate the process.

procPassive :: DynamicsPID -> DynamicsProc BoolSource

Test whether the process with the specified PID is passivated.

reactivateProc :: DynamicsPID -> DynamicsProc ()Source

Reactivate a process with the specified PID.

procPID :: DynamicsProc DynamicsPIDSource

Return the current process PID.

runProc :: DynamicsProc () -> DynamicsPID -> Dynamics Double -> Dynamics ()Source

Start the process with the specified PID at the desired time.

Resources

data DynamicsResource Source

Represents a limited resource.

Instances

newResource :: DynamicsQueue -> Int -> Dynamics DynamicsResourceSource

Create a new resource with the specified initial count.

resourceQueue :: DynamicsResource -> DynamicsQueueSource

Return the bound event queue.

resourceInitCount :: DynamicsResource -> IntSource

Return the initial count of the resource.

resourceCount :: DynamicsResource -> DynamicsProc IntSource

Return the current count of the resource.

requestResource :: DynamicsResource -> DynamicsProc ()Source

Request for the resource decreasing its count in case of success, otherwise suspending the discontinuous process until some other process releases the resource.

releaseResource :: DynamicsResource -> DynamicsProc ()Source

Release the resource increasing its count and resuming one of the previously suspended processes as possible.

Agent-based Modeling

data Agent Source

Represents an agent.

Instances

data AgentState Source

Represents the agent state.

Instances

newAgent :: DynamicsQueue -> Dynamics AgentSource

Create an agent bound with the specified event queue.

newState :: Agent -> Dynamics AgentStateSource

Create a new state.

newSubstate :: AgentState -> Dynamics AgentStateSource

Create a child state.

agentQueue :: Agent -> DynamicsQueueSource

Return the bound event queue.

agentState :: Agent -> Dynamics (Maybe AgentState)Source

Return the selected downmost active state.

activateState :: AgentState -> Dynamics ()Source

Select the next downmost active state.

initState :: AgentState -> Dynamics ()Source

Activate the child state during the direct activation of the parent state. This call is ignored in other cases.

stateAgent :: AgentState -> AgentSource

Return the corresponded agent.

stateParent :: AgentState -> Maybe AgentStateSource

Return the parent state or Nothing.

addTimeoutD :: AgentState -> Dynamics Double -> Dynamics () -> Dynamics ()Source

Add to the state a timeout handler that will be actuated in the specified time period, while the state remains active.

addTimeout :: AgentState -> Double -> Dynamics () -> Dynamics ()Source

Add to the state a timeout handler that will be actuated in the specified time period, while the state remains active.

addTimerD :: AgentState -> Dynamics Double -> Dynamics () -> Dynamics ()Source

Add to the state a timer handler that will be actuated in the specified time period and then repeated again many times, while the state remains active.

addTimer :: AgentState -> Double -> Dynamics () -> Dynamics ()Source

Add to the state a timer handler that will be actuated in the specified time period and then repeated again many times, while the state remains active.

stateActivation :: AgentState -> Dynamics () -> Dynamics ()Source

Set the activation computation for the specified state.

stateDeactivation :: AgentState -> Dynamics () -> Dynamics ()Source

Set the deactivation computation for the specified state.