Copyright | Copyright (c) 2009-2015, David Sorokin <david.sorokin@gmail.com> |
---|---|
License | BSD3 |
Maintainer | David Sorokin <david.sorokin@gmail.com> |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
- data Event m a
- class EventLift t m where
- data EventProcessing
- runEventInStartTime :: MonadDES m => Event m a -> Simulation m a
- runEventInStopTime :: MonadDES m => Event m a -> Simulation m a
- class EventQueueing m where
- data EventQueue m :: *
- newEventQueue :: Specs m -> m (EventQueue 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)
- enqueueEventWithTimes :: MonadDES m => [Double] -> Event m () -> Event m ()
- enqueueEventWithIntegTimes :: MonadDES m => Event m () -> Event m ()
- yieldEvent :: MonadDES m => Event m () -> Event m ()
- 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 ()
- 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.
class EventLift t m where Source
A type class to lift the Event
computations into other computations.
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) |
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.
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.
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.
enqueueEventWithTimes :: MonadDES m => [Double] -> 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.
DisposableEvent | |
|
Monad m => Monoid (DisposableEvent m) Source |