Copyright | Copyright (c) 2009-2017 David Sorokin <david.sorokin@gmail.com> |
---|---|
License | BSD3 |
Maintainer | David Sorokin <david.sorokin@gmail.com> |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- newtype Event m a = Event (Point m -> m a)
- class EventLift t m where
- data EventProcessing
- invokeEvent :: Point m -> Event m a -> m a
- runEventInStartTime :: MonadDES m => Event m a -> Simulation m a
- runEventInStopTime :: MonadDES m => Event m a -> Simulation m a
- type EventPriority = Int
- class EventQueueing m where
- data EventQueue m :: *
- newEventQueue :: Specs m -> m (EventQueue m)
- enqueueEventWithPriority :: Double -> EventPriority -> Event m () -> Event m ()
- enqueueEvent :: Double -> Event m () -> Event m ()
- runEvent :: Event m a -> Dynamics m a
- runEventWith :: EventProcessing -> Event m a -> Dynamics m a
- eventQueueCount :: Event m Int
- enqueueEventWithCancellation :: MonadDES m => Double -> Event m () -> Event m (EventCancellation m)
- enqueueEventWithStartTime :: MonadDES m => Event m () -> Event m ()
- enqueueEventWithStopTime :: MonadDES m => Event m () -> Event m ()
- enqueueEventWithTimes :: MonadDES m => [Double] -> Event m () -> Event m ()
- enqueueEventWithPoints :: MonadDES m => [Point m] -> Event m () -> Event m ()
- enqueueEventWithIntegTimes :: MonadDES m => Event m () -> Event m ()
- yieldEvent :: MonadDES m => Event m () -> Event m ()
- eventPriority :: MonadDES m => Event m EventPriority
- data EventCancellation m
- cancelEvent :: EventCancellation m -> Event m ()
- eventCancelled :: EventCancellation m -> Event m Bool
- eventFinished :: EventCancellation m -> Event m Bool
- catchEvent :: (MonadException m, Exception e) => Event m a -> (e -> Event m a) -> Event m a
- finallyEvent :: MonadException m => Event m a -> Event m b -> Event m a
- throwEvent :: (MonadException m, Exception e) => e -> Event m a
- memoEvent :: MonadDES m => Event m a -> Simulation m (Event m a)
- memoEventInTime :: MonadDES m => Event m a -> Simulation m (Event m a)
- newtype DisposableEvent m = DisposableEvent {
- disposeEvent :: Event m ()
- retryEvent :: MonadException m => String -> Event m a
- class (EventQueueing m, MonadIO (Event m)) => EventIOQueueing m where
- enqueueEventIO :: Double -> Event m () -> Event m ()
- enqueueEventIOWithStartTime :: (MonadDES m, EventIOQueueing m) => Event m () -> Event m ()
- enqueueEventIOWithStopTime :: (MonadDES m, EventIOQueueing m) => Event m () -> Event m ()
- enqueueEventIOWithTimes :: (MonadDES m, EventIOQueueing m) => [Double] -> Event m () -> Event m ()
- enqueueEventIOWithPoints :: (MonadDES m, EventIOQueueing m) => [Point m] -> Event m () -> Event m ()
- enqueueEventIOWithIntegTimes :: (MonadDES m, EventIOQueueing m) => Event m () -> Event m ()
- traceEvent :: MonadDES m => String -> Event m a -> Event m a
Event Monad
A value in the Event
monad transformer represents a polymorphic time varying
function which is strongly synchronized with the event queue.
Instances
class EventLift t m where Source #
A type class to lift the Event
computations into other computations.
liftEvent :: Event m a -> t m a Source #
Lift the specified Event
computation into another computation.
data EventProcessing Source #
Defines how the events are processed.
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 |
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 |
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) |
Instances
Show EventProcessing Source # | |
Defined in Simulation.Aivika.Trans.Internal.Types showsPrec :: Int -> EventProcessing -> ShowS # show :: EventProcessing -> String # showList :: [EventProcessing] -> ShowS # | |
Eq EventProcessing Source # | |
Defined in Simulation.Aivika.Trans.Internal.Types (==) :: EventProcessing -> EventProcessing -> Bool # (/=) :: EventProcessing -> EventProcessing -> Bool # | |
Ord EventProcessing Source # | |
Defined in Simulation.Aivika.Trans.Internal.Types compare :: EventProcessing -> EventProcessing -> Ordering # (<) :: EventProcessing -> EventProcessing -> Bool # (<=) :: EventProcessing -> EventProcessing -> Bool # (>) :: EventProcessing -> EventProcessing -> Bool # (>=) :: EventProcessing -> EventProcessing -> Bool # max :: EventProcessing -> EventProcessing -> EventProcessing # min :: EventProcessing -> EventProcessing -> EventProcessing # |
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
type EventPriority = Int Source #
The event priority (greater is higher).
class EventQueueing m where Source #
A type class of monads that allow enqueueing the events.
data EventQueue m :: * Source #
It represents the event queue.
newEventQueue :: Specs m -> m (EventQueue m) Source #
Create a new event queue by the specified specs with simulation session.
enqueueEventWithPriority :: Double -> EventPriority -> Event m () -> Event m () Source #
Enqueue the event which must be actuated at the specified time given the priority.
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.
Instances
EventQueueing IO Source # | An implementation of the |
Defined in Simulation.Aivika.IO.Event data EventQueue IO Source # newEventQueue :: Specs IO -> IO (EventQueue IO) Source # enqueueEventWithPriority :: Double -> EventPriority -> Event IO () -> Event IO () Source # enqueueEvent :: Double -> Event IO () -> Event IO () Source # runEvent :: Event IO a -> Dynamics IO a Source # runEventWith :: EventProcessing -> Event IO a -> Dynamics IO a Source # |
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.
eventPriority :: MonadDES m => Event m EventPriority Source #
Return the current event priority.
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.
DisposableEvent | |
|
Instances
Monad m => Monoid (DisposableEvent m) Source # | |
Defined in Simulation.Aivika.Trans.Internal.Event mempty :: DisposableEvent m # mappend :: DisposableEvent m -> DisposableEvent m -> DisposableEvent m # mconcat :: [DisposableEvent m] -> DisposableEvent m # | |
Monad m => Semigroup (DisposableEvent m) Source # | |
Defined in Simulation.Aivika.Trans.Internal.Event (<>) :: DisposableEvent m -> DisposableEvent m -> DisposableEvent m # sconcat :: NonEmpty (DisposableEvent m) -> DisposableEvent m # stimes :: Integral b => b -> DisposableEvent m -> DisposableEvent m # |
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.
enqueueEventIO :: Double -> Event m () -> Event m () Source #
Like enqueueEvent
but synchronizes the global modeling time before
calling the specified event handler.
Instances
EventIOQueueing IO Source # | An implementation of the |
Defined in Simulation.Aivika.IO.Event |
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.