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 |
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
- data Event a
- class EventLift m where
- data EventProcessing
- runEvent :: Event a -> Dynamics a
- runEventWith :: EventProcessing -> Event a -> Dynamics a
- runEventInStartTime :: Event a -> Simulation a
- runEventInStopTime :: Event a -> Simulation a
- type EventPriority = Int
- enqueueEvent :: Double -> Event () -> Event ()
- enqueueEventWithPriority :: Double -> EventPriority -> Event () -> Event ()
- enqueueEventWithCancellation :: Double -> Event () -> Event EventCancellation
- enqueueEventWithStartTime :: Event () -> Event ()
- enqueueEventWithStopTime :: Event () -> Event ()
- enqueueEventWithTimes :: [Double] -> Event () -> Event ()
- enqueueEventWithIntegTimes :: Event () -> Event ()
- yieldEvent :: Event () -> Event ()
- eventQueueCount :: Event Int
- eventPriority :: Event EventPriority
- data EventCancellation
- cancelEvent :: EventCancellation -> Event ()
- eventCancelled :: EventCancellation -> Event Bool
- eventFinished :: EventCancellation -> Event Bool
- catchEvent :: Exception e => Event a -> (e -> Event a) -> Event a
- finallyEvent :: Event a -> Event b -> Event a
- throwEvent :: Exception e => e -> Event a
- memoEvent :: Event a -> Simulation (Event a)
- memoEventInTime :: Event a -> Simulation (Event a)
- newtype DisposableEvent = DisposableEvent {
- disposeEvent :: Event ()
- retryEvent :: String -> Event a
- traceEvent :: String -> Event a -> Event a
Event Monad
A value in the Event
monad represents a polymorphic time varying function
which is strongly synchronized with the event queue.
Instances
class EventLift m where Source #
A type class to lift the Event
computation to 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) |
Instances
Show EventProcessing Source # | |
Defined in Simulation.Aivika.Internal.Event showsPrec :: Int -> EventProcessing -> ShowS # show :: EventProcessing -> String # showList :: [EventProcessing] -> ShowS # | |
Eq EventProcessing Source # | |
Defined in Simulation.Aivika.Internal.Event (==) :: EventProcessing -> EventProcessing -> Bool # (/=) :: EventProcessing -> EventProcessing -> Bool # | |
Ord EventProcessing Source # | |
Defined in Simulation.Aivika.Internal.Event compare :: EventProcessing -> EventProcessing -> Ordering # (<) :: EventProcessing -> EventProcessing -> Bool # (<=) :: EventProcessing -> EventProcessing -> Bool # (>) :: EventProcessing -> EventProcessing -> Bool # (>=) :: EventProcessing -> EventProcessing -> Bool # max :: EventProcessing -> EventProcessing -> EventProcessing # min :: EventProcessing -> EventProcessing -> EventProcessing # |
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 #
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
type EventPriority = Int Source #
The event priority (greater is higher).
enqueueEvent :: Double -> Event () -> Event () Source #
Enqueue the event which must be actuated at the specified time.
enqueueEventWithPriority :: Double -> EventPriority -> Event () -> Event () Source #
Enqueue the event which must be actuated at the specified time given the priority.
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.
eventPriority :: Event EventPriority Source #
Return the current event priority.
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.
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.
DisposableEvent | |
|
Instances
Monoid DisposableEvent Source # | |
Defined in Simulation.Aivika.Internal.Event mappend :: DisposableEvent -> DisposableEvent -> DisposableEvent # mconcat :: [DisposableEvent] -> DisposableEvent # | |
Semigroup DisposableEvent Source # | |
Defined in Simulation.Aivika.Internal.Event (<>) :: DisposableEvent -> DisposableEvent -> DisposableEvent # sconcat :: NonEmpty DisposableEvent -> DisposableEvent # stimes :: Integral b => b -> DisposableEvent -> DisposableEvent # |
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.