event-monad-0.0.3: Event-graph simulation monad transformer

Control.Monad.EventT

Synopsis

Documentation

data EventT t m a Source

A monad transformer which adds an event queue and related operations to an underlying monad. The "t" parameter specifies the type of the simulation time.

Several hooks are provided to allow special handling of various events, such as the progression of time, the scheduling or canceling or dispatch of an event, etc.

Instances

MonadError e m => MonadError e (EventT t m) 
MonadReader r m => MonadReader r (EventT t m) 
MonadState s m => MonadState s (EventT t m) 
MonadWriter w m => MonadWriter w (EventT t m) 
MonadTrans (EventT t) 
Monad m => Monad (EventT t m) 
Functor m => Functor (EventT t m) 
(Typeable t, Typeable1 m) => Typeable1 (EventT t m) 
MonadFix m => MonadFix (EventT t m) 
MonadPlus m => MonadPlus (EventT t m) 
MonadIO m => MonadIO (EventT t m) 
MonadCont m => MonadCont (EventT t m) 
Monad m => MonadSimControl (EventT t m) 
Monad m => MonadTime (EventT t m) t 
(Monad m, Ord t) => MonadEventQueueInfo (EventT t m) t 
Monad m => RetryEvent (EventT t m) t 
Monad m => GetCurrentEvent (EventT t m) t 
(Monad m, Ord t) => CancelEvent (EventT t m) t 
(Monad m, Ord t, MonadEvent (EventT t m) e) => ScheduleEvent (EventT t m) t e 
(Monad m, Show t, Typeable t, Typeable1 m) => MonadEvent (EventT t m) (EventDescriptor (EventT t m) t) 
(Monad m, Typeable (EventT t m a)) => MonadEvent (EventT t m) (EventT t m a) 

runEventT :: Monad m => EventT t m a -> EventT_RState t m -> EventT_RWState t m -> m (a, EventT_RWState t m)Source

Run an EventT wrapped action. This is a "raw" action - there is no interaction with the state (including event graph) except whatever the action itself does.

runEventGraph :: (Monad m, MonadEvent (EventT t m) e, Ord t, Num t, Show t, Typeable t, Typeable1 m) => e -> m (EventT_RState t m, EventT_RWState t m)Source

Initialize the event queue and other stuff, enqueue the provided "start event", and run the queue until it's empty or until the simulation is paused.

runEventGraphWithState :: (Monad m, Ord t, Show t, Typeable t, Typeable1 m) => EventT_RState t m -> EventT_RWState t m -> m (EventT_RWState t m)Source

Repeatedly pull and run the next event in the queue until it's empty or until the simulation is paused using pauseSimulation or something equivalent.

newEventT_RState :: EventT_RState t mSource

A new instance of the read-only portion of the EventT internal state.

newEventT_RWState :: (Monad m, Ord t) => t -> EventT_RWState t mSource

A new instance of the read/write portion of the EventT internal state. The parameter is the initial time value.

type HandlerAccessor t m a b = (EventTHandlers t m -> HandlerSet (EventT t m) a b, HandlerSet (EventT t m) a b -> EventTHandlers t m -> EventTHandlers t m)Source

onClockChanged :: HandlerAccessor t m (t, t) ()Source

Fires whenever the clock changes, and is passed a tuple containing (old time, new time)

onEventDispatch :: HandlerAccessor t m (EventDescriptor (EventT t m) t) ()Source

Fires just before an event is dispatched. Is passed an EventDescriptor describing the event about to be run.

onEventComplete :: HandlerAccessor t m (EventDescriptor (EventT t m) t) ()Source

Fires after an event returns. Is passed an EventDescriptor for the event that just finished.

onEventSchedule :: HandlerAccessor t m (EventDescriptor (EventT t m) t) ()Source

Fires after an event is scheduled. Is passed an EventDescriptor for the event.

onEventCancel :: HandlerAccessor t m (Either EventID (EventDescriptor (EventT t m) t)) ()Source

Fires after an event is canceled. Is passed either an EventID (if the cancellation failed) or an EventDescriptor for the event that was canceled.

addHandler :: Monad m => HandlerAccessor t m a b -> (a -> EventT t m b) -> EventT t m HandlerIDSource

Add an event handler to be called when the specified event happens.

removeHandler :: Monad m => HandlerAccessor t m a b -> HandlerID -> EventT t m (Maybe (a -> EventT t m b))Source

Remove an event handler given its ID, and return it if it was in the set.