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

Contents

Description

Tested with: GHC 8.0.1

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

Synopsis

Event Monad

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 # 

class EventLift t m where Source #

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

Minimal complete definition

liftEvent

Methods

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

Lift the specified Event computation into another computation.

Instances

Monad m => EventLift Event m Source # 

Methods

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

Monad m => EventLift Composite m Source # 

Methods

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

MonadDES m => EventLift Cont m Source # 

Methods

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

MonadDES m => EventLift Process m Source # 

Methods

liftEvent :: Event m a -> Process m a 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)

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

Invoke the Event computation.

runEventInStartTime :: MonadDES m => Event m a -> Simulation m a Source #

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

runEventInStopTime :: MonadDES m => Event m a -> Simulation m a Source #

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

Event Queue

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.

enqueueEventWithCancellation :: MonadDES m => Double -> Event m () -> Event m (EventCancellation m) Source #

Enqueue the event with an ability to cancel it.

enqueueEventWithStartTime :: MonadDES m => Event m () -> Event m () Source #

Actuate the event handler in the start time point.

enqueueEventWithStopTime :: MonadDES m => Event m () -> Event m () Source #

Actuate the event handler in the final time point.

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

Actuate the event handler in the specified time points.

enqueueEventWithPoints :: MonadDES m => [Point m] -> Event m () -> Event m () Source #

Actuate the event handler in the specified time points.

enqueueEventWithIntegTimes :: MonadDES m => Event m () -> Event m () Source #

Actuate the event handler in the integration time points.

yieldEvent :: MonadDES m => Event m () -> Event m () Source #

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

Cancelling Event

data EventCancellation m Source #

It allows cancelling the event.

cancelEvent :: EventCancellation m -> Event m () Source #

Cancel the event.

eventCancelled :: EventCancellation m -> Event m Bool Source #

Test whether the event was cancelled.

eventFinished :: EventCancellation m -> Event m Bool Source #

Test whether the event was processed and finished.

Error Handling

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

Exception handling within Event computations.

finallyEvent :: MonadException m => Event m a -> Event m b -> Event m a Source #

A computation with finalization part like the finally function.

throwEvent :: (MonadException m, Exception e) => e -> Event m a Source #

Like the standard throw function.

Memoization

memoEvent :: MonadDES m => Event m a -> Simulation m (Event m a) Source #

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

memoEventInTime :: MonadDES m => Event m a -> Simulation m (Event m 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 m Source #

Defines a computation disposing some entity.

Constructors

DisposableEvent 

Fields

Retrying Computation

retryEvent :: MonadException m => String -> Event m a Source #

Retry the current computation as possible, using the specified argument as a SimulationRetry exception message in case of failure. It makes sense for parallel distributed simulation, when we have to make a rollback, awaiting for incoming messages.

Synchronizing IO Actions

class (EventQueueing m, MonadIO (Event m)) => EventIOQueueing m where Source #

A type class of monads that allows synchronizing the global modeling time before calling the event handler so that it is rather safe to perform IO actions within such a handler. It is mainly destined for parallel distributed simulation, but it should be supported in other cases too.

Minimal complete definition

enqueueEventIO

Methods

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

Like enqueueEvent but synchronizes the global modeling time before calling the specified event handler.

enqueueEventIOWithStartTime :: (MonadDES m, EventIOQueueing m) => Event m () -> Event m () Source #

Like enqueueEventWithStartTime but synchronizes the global modeling time before calling the specified event handler.

enqueueEventIOWithStopTime :: (MonadDES m, EventIOQueueing m) => Event m () -> Event m () Source #

Like enqueueEventWithStopTime but synchronizes the global modeling time before calling the specified event handler.

enqueueEventIOWithTimes :: (MonadDES m, EventIOQueueing m) => [Double] -> Event m () -> Event m () Source #

Like enqueueEventWithTimes but synchronizes the global modeling time before calling the specified event handler.

enqueueEventIOWithPoints :: (MonadDES m, EventIOQueueing m) => [Point m] -> Event m () -> Event m () Source #

Like enqueueEventWithPoints but synchronizes the global modeling time before calling the specified event handler.

enqueueEventIOWithIntegTimes :: (MonadDES m, EventIOQueueing m) => Event m () -> Event m () Source #

Like enqueueEventWithIntegTimes but synchronizes the global modeling time before calling the specified event handler.

Debugging

traceEvent :: MonadDES m => String -> Event m a -> Event m a Source #

Show the debug message with the current simulation time.

Orphan instances

MonadTrans Event Source # 

Methods

lift :: Monad m => m a -> Event m a #

Monad m => MonadCompTrans Event m Source # 

Methods

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

Monad m => ParameterLift Event m Source # 

Methods

liftParameter :: Parameter m a -> Event m a Source #

Monad m => SimulationLift Event m Source # 

Methods

liftSimulation :: Simulation m a -> Event m a Source #

Monad m => DynamicsLift Event m Source # 

Methods

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

Monad m => Monad (Event m) Source # 

Methods

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

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

return :: a -> Event m a #

fail :: String -> Event m a #

Functor m => Functor (Event m) Source # 

Methods

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

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

MonadFix m => MonadFix (Event m) Source # 

Methods

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

Applicative m => Applicative (Event m) Source # 

Methods

pure :: a -> Event m a #

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

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

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

MonadIO m => MonadIO (Event m) Source # 

Methods

liftIO :: IO a -> Event m a #