aivika-5.3.1: A multi-method 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.Event

Contents

Description

Tested with: GHC 8.0.1

The module defines the Event monad which is very similar to the Dynamics monad but only now the computation is strongly synchronized with the event queue.

The Dynamics computation is defined in all time points simultaneously, while the Event computation can be described in every time point differently and can change in discrete steps. Therefore, the former is destined for differential and difference equations of System Dynamics, while the latter is destined for discrete event simulation, being its core actually.

Synopsis

Event Monad

data Event a Source #

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

Instances

Monad Event Source # 

Methods

(>>=) :: Event a -> (a -> Event b) -> Event b #

(>>) :: Event a -> Event b -> Event b #

return :: a -> Event a #

fail :: String -> Event a #

Functor Event Source # 

Methods

fmap :: (a -> b) -> Event a -> Event b #

(<$) :: a -> Event b -> Event a #

MonadFix Event Source # 

Methods

mfix :: (a -> Event a) -> Event a #

Applicative Event Source # 

Methods

pure :: a -> Event a #

(<*>) :: Event (a -> b) -> Event a -> Event b #

(*>) :: Event a -> Event b -> Event b #

(<*) :: Event a -> Event b -> Event a #

MonadIO Event Source # 

Methods

liftIO :: IO a -> Event a #

ParameterLift Event Source # 
SimulationLift Event Source # 
DynamicsLift Event Source # 
EventLift Event Source # 

Methods

liftEvent :: Event a -> Event a Source #

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

class EventLift m where Source #

A type class to lift the Event computation to other computations.

Minimal complete definition

liftEvent

Methods

liftEvent :: Event a -> m a Source #

Lift the specified Event computation to another computation.

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)

runEvent :: Event a -> Dynamics a Source #

Run the Event computation in the current simulation time within the Dynamics computation involving all pending CurrentEvents in the processing too.

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

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

runEventInStartTime :: Event a -> Simulation a Source #

Run the Event computation in the start time involving all pending CurrentEvents in the processing too.

runEventInStopTime :: Event a -> Simulation a Source #

Run the Event computation in the stop time involving all pending CurrentEvents in the processing too.

Event Queue

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

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

enqueueEventWithCancellation :: Double -> Event () -> Event EventCancellation Source #

Enqueue the event with an ability to cancel it.

enqueueEventWithStartTime :: Event () -> Event () Source #

Actuate the event handler in the start time point.

enqueueEventWithStopTime :: Event () -> Event () Source #

Actuate the event handler in the final time point.

enqueueEventWithTimes :: [Double] -> Event () -> Event () Source #

Actuate the event handler in the specified time points.

enqueueEventWithIntegTimes :: Event () -> Event () Source #

Actuate the event handler in the integration time points.

yieldEvent :: Event () -> Event () Source #

Enqueue the event which must be actuated with the current modeling time but later.

eventQueueCount :: Event Int Source #

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

Cancelling Event

data EventCancellation Source #

It allows cancelling the event.

cancelEvent :: EventCancellation -> Event () Source #

Cancel the event.

eventCancelled :: EventCancellation -> Event Bool Source #

Test whether the event was cancelled.

eventFinished :: EventCancellation -> Event Bool Source #

Test whether the event was processed and finished.

Error Handling

catchEvent :: Exception e => Event a -> (e -> Event a) -> Event a Source #

Exception handling within Event computations.

finallyEvent :: Event a -> Event b -> Event a Source #

A computation with finalization part like the finally function.

throwEvent :: Exception e => e -> Event a Source #

Like the standard throw function.

Memoization

memoEvent :: Event a -> Simulation (Event a) Source #

Memoize the Event computation, always returning the same value within a simulation run.

memoEventInTime :: Event a -> Simulation (Event a) Source #

Memoize the Event computation, always returning the same value in the same modeling time. After the time changes, the value is recalculated by demand.

It is possible to implement this function efficiently, for the Event computation is always synchronized with the event queue which time flows in one direction only. This synchronization is a key difference between the Event and Dynamics computations.

Disposable

newtype DisposableEvent Source #

Defines a computation disposing some entity.

Constructors

DisposableEvent 

Fields

Retrying Computation

retryEvent :: String -> Event a Source #

Retry the current computation as possible, using the specified argument as a SimulationRetry exception message in case of failure.

Debugging

traceEvent :: String -> Event a -> Event a Source #

Show the debug message with the current simulation time.