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

Control.Monad.EventM

Synopsis

Documentation

data EventIO t a Source

Instances

Monad (EventIO t) 
Functor (EventIO t) 
MonadFix (EventIO t) 
MonadIO (EventIO t) 
HasRef (EventIO t)

A monad which extends IO with an event queue and related operations. 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.

MonadSimControl (EventIO t) 
MonadTime (EventIO t) t 
MonadEventQueueInfo (EventIO t) t 
RetryEvent (EventIO t) t 
GetCurrentEvent (EventIO t) t 
CancelEvent (EventIO t) t 
MonadEvent (EventIO t) e => ScheduleEvent (EventIO t) t e 
MonadEvent (EventIO t) (IO a) 
Show t => MonadEvent (EventIO t) (EventDescriptor (EventIO t) t) 
MonadEvent (EventIO t) (EventIO t a) 
NewRef (Ref (EventIO t) a) IO a 
WriteRef (Ref IO a) (EventIO t) a 
ReadRef (Ref IO a) (EventIO t) a 
ModifyRef (Ref IO a) (EventIO t) a 
NewRef (Ref IO a) (EventIO t) a 

runEventIO :: EventIO t a -> EventIOState t -> IO aSource

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 :: (MonadEvent (EventIO t) e, Ord t, Num t, Show t) => e -> IO (EventIOState t)Source

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

runEventGraphWithState :: (Ord t, Show t) => EventIOState t -> IO ()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.

newEventIOState :: Ord t => t -> IO (EventIOState t)Source

onClockChanged :: EventIOHandlers t -> Ref IO (HandlerSet (EventIO t) (t, t) ())Source

onEventDispatch :: EventIOHandlers t -> Ref IO (HandlerSet (EventIO t) (EventDescriptor (EventIO t) t) ())Source

onEventComplete :: EventIOHandlers t -> Ref IO (HandlerSet (EventIO t) (EventDescriptor (EventIO t) t) ())Source

onEventSchedule :: EventIOHandlers t -> Ref IO (HandlerSet (EventIO t) (EventDescriptor (EventIO t) t) ())Source

addHandler :: HandlerAccessor t a b -> (a -> EventIO t b) -> EventIO t HandlerIDSource

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

removeHandler :: HandlerAccessor t a b -> HandlerID -> EventIO t (Maybe (a -> EventIO t b))Source

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