aivika-transformers-5.3: 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.Internal.Types

Description

Tested with: GHC 8.0.1

It defines the implementation details of some types. You should never use it in ordinary simulation models. The module is destined for those who will extend the library.

Synopsis

Documentation

data Specs m Source #

It defines the simulation specs.

Constructors

Specs 

Fields

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

data Run m Source #

It indentifies the simulation run.

Constructors

Run 

Fields

data Point m Source #

It defines the simulation point appended with the additional information.

Constructors

Point 

Fields

newtype Parameter m a Source #

The Parameter monad that allows specifying the model parameters. For example, they can be used when running the Monte-Carlo simulation.

In general, this monad is very useful for representing a computation which is external relative to the model itself.

Constructors

Parameter (Run m -> m a) 

Instances

Monad m => ParameterLift Parameter m Source # 
MonadDES m => ResultComputing Parameter m Source # 
(MonadDES m, ResultItemable (ResultValue [e])) => ResultProvider (Parameter m (Vector e)) m Source # 
(Ix i, Show i, MonadDES m, ResultItemable (ResultValue [e])) => ResultProvider (Parameter m (Array i e)) m Source # 
(MonadDES m, ResultItemable (ResultValue a), ResultItemable (ResultValue (TimingStats a))) => ResultProvider (Parameter m (TimingCounter a)) m Source # 
(MonadDES m, ResultItemable (ResultValue a), ResultItemable (ResultValue (SamplingStats a))) => ResultProvider (Parameter m (SamplingCounter a)) m Source # 
(MonadDES m, ResultItemable (ResultValue a)) => ResultProvider (Parameter m a) m Source # 

newtype Simulation m a Source #

A value in the Simulation monad represents a computation within the simulation run.

Constructors

Simulation (Run m -> m a) 

Instances

Monad m => SimulationLift Simulation m Source # 
MonadDES m => ResultComputing Simulation m Source # 
(MonadDES m, ResultItemable (ResultValue [e])) => ResultProvider (Simulation m (Vector e)) m Source # 
(Ix i, Show i, MonadDES m, ResultItemable (ResultValue [e])) => ResultProvider (Simulation m (Array i e)) m Source # 
(MonadDES m, ResultItemable (ResultValue a), ResultItemable (ResultValue (TimingStats a))) => ResultProvider (Simulation m (TimingCounter a)) m Source # 
(MonadDES m, ResultItemable (ResultValue a), ResultItemable (ResultValue (SamplingStats a))) => ResultProvider (Simulation m (SamplingCounter a)) m Source # 
(MonadDES m, ResultItemable (ResultValue a)) => ResultProvider (Simulation m a) m Source # 

newtype Dynamics m a Source #

A value in the Dynamics monad represents a polymorphic time varying function defined in the whole spectrum of time values as a single entity. It is ideal for numerical approximating integrals.

Constructors

Dynamics (Point m -> m a) 

Instances

Monad m => DynamicsLift Dynamics m Source # 

Methods

liftDynamics :: Dynamics m a -> Dynamics m a Source #

MonadDES m => ResultComputing Dynamics m Source # 
(MonadDES m, ResultItemable (ResultValue [e])) => ResultProvider (Dynamics m (Vector e)) m Source # 
(Ix i, Show i, MonadDES m, ResultItemable (ResultValue [e])) => ResultProvider (Dynamics m (Array i e)) m Source # 
(MonadDES m, ResultItemable (ResultValue a), ResultItemable (ResultValue (TimingStats a))) => ResultProvider (Dynamics m (TimingCounter a)) m Source # 
(MonadDES m, ResultItemable (ResultValue a), ResultItemable (ResultValue (SamplingStats a))) => ResultProvider (Dynamics m (SamplingCounter a)) m Source # 
(MonadDES m, ResultItemable (ResultValue a)) => ResultProvider (Dynamics m a) m Source # 

newtype Event m a Source #

A value in the Event monad transformer represents a polymorphic time varying function which is strongly synchronized with the event queue.

Constructors

Event (Point m -> m a) 

Instances

Monad m => EventLift Event m Source # 

Methods

liftEvent :: Event m a -> Event m a Source #

MonadDES m => ResultComputing Event m Source # 
(Monad m, MonadRef m) => Observable (Ref m) (Event m) Source # 

Methods

readObservable :: Ref m a -> Event m a Source #

(Monad m, MonadRef m) => Observable (Ref m) (Event m) Source # 

Methods

readObservable :: Ref m a -> Event m a Source #

(MonadDES m, ResultItemable (ResultValue [e])) => ResultProvider (Event m (Vector e)) m Source # 
(Ix i, Show i, MonadDES m, ResultItemable (ResultValue [e])) => ResultProvider (Event m (Array i e)) m Source # 
(MonadDES m, ResultItemable (ResultValue a), ResultItemable (ResultValue (TimingStats a))) => ResultProvider (Event m (TimingCounter a)) m Source # 
(MonadDES m, ResultItemable (ResultValue a), ResultItemable (ResultValue (SamplingStats a))) => ResultProvider (Event m (SamplingCounter a)) m Source # 
(MonadDES m, ResultItemable (ResultValue a)) => ResultProvider (Event m a) m Source # 

data EventProcessing Source #

Defines how the events are processed.

Constructors

CurrentEvents

either process all earlier and then current events, or raise an error if the current simulation time is less than the actual time of the event queue (safe within the Event computation as this is protected by the type system)

EarlierEvents

either process all earlier events not affecting the events at the current simulation time, or raise an error if the current simulation time is less than the actual time of the event queue (safe within the Event computation as this is protected by the type system)

CurrentEventsOrFromPast

either process all earlier and then current events, or do nothing if the current simulation time is less than the actual time of the event queue (do not use unless the documentation states the opposite)

EarlierEventsOrFromPast

either process all earlier events, or do nothing if the current simulation time is less than the actual time of the event queue (do not use unless the documentation states the opposite)

class EventQueueing m where Source #

A type class of monads that allow enqueueing the events.

Associated Types

data EventQueue m :: * Source #

It represents the event queue.

Methods

newEventQueue :: Specs m -> m (EventQueue m) Source #

Create a new event queue by the specified specs with simulation session.

enqueueEvent :: Double -> Event m () -> Event m () Source #

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

runEvent :: Event m a -> Dynamics m a Source #

Run the EventT computation in the current simulation time within the DynamicsT computation involving all pending CurrentEvents in the processing too.

runEventWith :: EventProcessing -> Event m a -> Dynamics m a Source #

Run the EventT computation in the current simulation time within the DynamicsT computation specifying what pending events should be involved in the processing.

eventQueueCount :: Event m Int Source #

Return the number of pending events that should be yet actuated.

invokeParameter :: Run m -> Parameter m a -> m a Source #

Invoke the Parameter computation.

invokeSimulation :: Run m -> Simulation m a -> m a Source #

Invoke the Simulation computation.

invokeDynamics :: Point m -> Dynamics m a -> m a Source #

Invoke the Dynamics computation.

invokeEvent :: Point m -> Event m a -> m a Source #

Invoke the Event computation.