event-monad-0.0.1.0: Event-graph simulation monad transformerSource codeContentsIndex
Control.Monad.Event.Classes
Synopsis
class Monad m => MonadTime m t | m -> t where
getCurrentTime :: m t
class Monad m => MonadSimControl m where
resumeSimulation :: m ()
pauseSimulation :: m ()
isSimulationRunning :: m Bool
class Monad m => MonadEvent m e | e -> m where
describeEvent :: e -> m Doc
runEvent :: e -> m ()
class (MonadEvent m e, MonadTime m t) => ScheduleEvent m t e | m -> t where
scheduleEventAt :: t -> e -> m EventID
doNext :: e -> m ()
scheduleEventIn :: (ScheduleEvent m t e, Num t) => t -> e -> m EventID
class MonadTime m t => CancelEvent m t | m -> t where
cancelEvent :: EventID -> m (Maybe (EventDescriptor m t))
class MonadTime m t => GetCurrentEvent m t | m -> t where
getCurrentEvent :: m (Maybe (EventDescriptor m t))
class MonadTime m t => RetryEvent m t | m -> t where
retryEventAt :: t -> m EventID
retryEventIn :: (RetryEvent m t, Num t) => t -> m EventID
class MonadTime m t => MonadEventQueueInfo m t | m -> t where
eventQueueSize :: m Int
eventQueueContents :: m [EventDescriptor m t]
Documentation
class Monad m => MonadTime m t | m -> t whereSource
A type-class for monads with a concept of time. That concept need not necessarily meet any prior conditions - not even an Eq instance.
Methods
getCurrentTime :: m tSource
show/hide Instances
class Monad m => MonadSimControl m whereSource
A monad in which there is a concept of running and not-running and unrestricted operations for switching between them.
Methods
resumeSimulation :: m ()Source
pauseSimulation :: m ()Source
isSimulationRunning :: m BoolSource
show/hide Instances
class Monad m => MonadEvent m e | e -> m whereSource
A monad in which there is a concept of an "event" - an action with a sort of a special status, which can be described for humans and can be otherwise manipulated in monads implementing the classes to follow.
Methods
describeEvent :: e -> m DocSource
runEvent :: e -> m ()Source
show/hide Instances
class (MonadEvent m e, MonadTime m t) => ScheduleEvent m t e | m -> t whereSource
A monad which can schedule events for later execution. For obvious reasons, such a monad must also have a concept of events (covering the event that the user is trying to schedule) and a concept of time.
Methods
scheduleEventAt :: t -> e -> m EventIDSource

Schedule an event for execution at a time. The meaning of "time" is left entirely up to the implementor, however it will generally be the case that time is an instance of Num and/or is totally ordered in the usual way.

Returns an EventID that can be used to identify the event if needed later (for example, to cancel it).

doNext :: e -> m ()Source

schedule an event to run at the current time. This does not constitute a promise to execute immediately or in any particular order relative to other events that have been or will be scheduled for the current time.

If an implementor has a time type which is an instance of Num, then doNext should be equivalent to scheduleEventIn 0 - unless the monad's documentation clearly warns to the contrary in a really big typeface. ; ) Note that this clause may change to also strongly suggest that doNext put its event at the very front of the queue (ie, before any other events already scheduled for the current time).

show/hide Instances
MonadEvent (EventIO t) e => ScheduleEvent (EventIO t) t e
(Monad m, Ord t, MonadEvent (EventT t m) e) => ScheduleEvent (EventT t m) t e
scheduleEventIn :: (ScheduleEvent m t e, Num t) => t -> e -> m EventIDSource
schedule an event at an absolute time (see scheduleEventIn)
class MonadTime m t => CancelEvent m t | m -> t whereSource
A monad in which an event (presumably one previously scheduled) can be canceled.
Methods
cancelEvent :: EventID -> m (Maybe (EventDescriptor m t))Source
Cancel an event given its EventID. If successful (and if the monad's implementation allows it), an EventDescriptor (an existential wrapper describing an event, its ID, and the time at which it would have run) containing the canceled event is returned.
show/hide Instances
class MonadTime m t => GetCurrentEvent m t | m -> t whereSource
A monad in which an EventDescriptor for the currently-executing event, if any, can be obtained.
Methods
getCurrentEvent :: m (Maybe (EventDescriptor m t))Source
show/hide Instances
class MonadTime m t => RetryEvent m t | m -> t whereSource
A monad in which the currently executing event can be rescheduled. Note that calling retryEventAt does not terminate the currently executing event - although perhaps it should. Until a more permanent decision is made, it's probably best to make retryEventAt the last action of an event when it is used, to minimize impact of future changes.
Methods
retryEventAt :: t -> m EventIDSource
show/hide Instances
retryEventIn :: (RetryEvent m t, Num t) => t -> m EventIDSource
retry the currently-executing event at an absolute time (see retryEventIn)
class MonadTime m t => MonadEventQueueInfo m t | m -> t whereSource
A monad in which information about the event queue can be retrieved.
Methods
eventQueueSize :: m IntSource
Return the number of events currently scheduled.
eventQueueContents :: m [EventDescriptor m t]Source
Return a list of (some or all of) the events coming up. There is no obligation on the part of the monad to provide anything at all.
show/hide Instances
Produced by Haddock version 2.4.2