eve-0.1.9.0: An extensible event framework

Safe HaskellNone
LanguageHaskell2010

Eve.Internal.Listeners

Synopsis

Documentation

class (Typeable s, HasStates s) => HasEvents s Source #

A typeclass to ensure people don't dispatch events to states which shouldn't accept them.

To allow dispatching events in an action over your state simply define the empty instance:

instance HasEvents MyState where
-- Don't need anything here.
Instances
HasEvents AppState Source # 
Instance details

Defined in Eve.Internal.AppState

dispatchEvent :: forall result eventType m base zoomed. (HasEvents base, Monoid result, Monad m, Typeable m, Typeable eventType, Typeable result) => eventType -> ActionT base zoomed m result Source #

Runs any listeners registered for the provided event with the provided event;

You can also query listeners and receive a (Monoidal) result.

data RequestNames = GetFirstName | GetLastName
provideName1, provideName2 :: RequestNames -> App [String]
provideName1 GetFirstNames = return ["Bob"]
provideName1 GetLastNames = return ["Smith"]
provideName2 GetFirstNames = return ["Sally"]
provideName2 GetLastNames = return ["Jenkins"]

-- Note that if we registered an action of type 'GetFirstName -> ()' it would NOT
-- be run in response to the following 'dispatchEvent', since it's type doesn't match.

greetNames :: App [String]
greetNames = do
  addListener_ provideName1
  addListener_ provideName2
  firstNames <- dispatchEvent GetFirstName
  lastNames <- dispatchEvent GetLastName
  liftIO $ print firstNames
  -- ["Bob", "Sally"]
  liftIO $ print lastNames
  -- ["Smith", "Jenkins"]

dispatchEvent_ :: forall eventType m base zoomed. (HasEvents base, Monad m, Typeable m, Typeable eventType) => eventType -> ActionT base zoomed m () Source #

dispatchLocalEvent :: forall result eventType m s. (MonadState s m, HasEvents s, Monoid result, Typeable m, Typeable eventType, Typeable result) => eventType -> m result Source #

A local version of dispatchEvent. The local version dispatches the event in the context of the current Action, If you don't know what this means, you probably want dispatchEvent instead

dispatchLocalEvent_ :: forall eventType m s. (MonadState s m, HasEvents s, Typeable m, Typeable eventType) => eventType -> m () Source #

dispatchEventAsync :: (Typeable event, MonadIO m, Typeable m, HasEvents base) => IO event -> ActionT base zoomed m () Source #

This function takes an IO which results in some event, it runs the IO asynchronously, THEN dispatches the event. Note that only the code which generates the event is asynchronous, not any responses to the event itself.

addListener :: forall result eventType m base zoomed. (HasEvents base, Monad m, Typeable m, Typeable eventType, Typeable result, Monoid result) => (eventType -> AppT base m result) -> ActionT base zoomed m ListenerId Source #

Registers an Action or App to respond to an event.

For a given use: addListener myListener, myListener might have the type MyEvent -> App a it will register the function myListener to be run in response to a dispatchEvent (MyEvent eventInfo) and will be provided (MyEvent eventInfo) as an argument.

This returns a ListenerId which corresponds to the registered listener for use with removeListener

addListener_ :: forall result eventType m base zoomed. (HasEvents base, Monad m, Typeable m, Typeable eventType, Typeable result, Monoid result) => (eventType -> AppT base m result) -> ActionT base zoomed m () Source #

addLocalListener :: forall result eventType m s. (MonadState s m, HasEvents s, Typeable m, Typeable eventType, Typeable result, Monoid result) => (eventType -> m result) -> m ListenerId Source #

The local version of addListener. It will register a listener within an Actions local event context. If you don't know what this means you probably want addListener instead.

addLocalListener_ :: forall result eventType m s. (MonadState s m, HasEvents s, Typeable m, Typeable eventType, Typeable result, Monoid result) => (eventType -> m result) -> m () Source #

removeListener :: (HasEvents base, Monad m) => ListenerId -> ActionT base zoomed m () Source #

Unregisters a listener referred to by the provided ListenerId

removeLocalListener :: (MonadState s m, HasEvents s) => ListenerId -> m () Source #

The local version of removeListener. This removes a listener from an Actions event context. If you don't know what this means you probably want removeListener instead.

asyncEventProvider :: (HasEvents base, MonadIO m, Typeable m) => (EventDispatcher -> IO ()) -> ActionT base zoomed m () Source #

This allows long-running IO processes to provide Events to the application asyncronously.

Don't let the type signature confuse you; it's much simpler than it seems.

Let's break it down:

Using the EventDispatcher type with asyncEventProvider requires the RankNTypes language pragma.

This type as a whole represents a function which accepts an EventDispatcher and returns an IO; the dispatcher itself accepts data of ANY Typeable type and emits it as an event.

When you call asyncEventProvider you pass it a function which accepts a dispatch function as an argument and then calls it with various events within the resulting IO.

Note that this function calls forkIO internally, so there's no need to do that yourself.

Here's an example which fires a Timer event every second.

{-# language RankNTypes #-}
data Timer = Timer
myTimer :: EventDispatcher -> IO ()
myTimer dispatch = forever $ dispatch Timer >> threadDelay 1000000

myInit :: App ()
myInit = asyncEventProvider myTimer

afterInit :: forall base m a. (Monad m, HasEvents base, Typeable m) => AppT base m a -> AppT base m () Source #

Registers an action to be performed directly following the Initialization phase.

At this point any listeners in the initialization block have run, so you may dispatchEvents here.

beforeEvent :: forall base zoomed m a. (Monad m, HasEvents base, Typeable m) => AppT base m a -> ActionT base zoomed m ListenerId Source #

Registers an action to be performed BEFORE each async event is processed phase.

beforeEvent_ :: (Monad m, HasEvents base, Typeable m) => AppT base m a -> ActionT base zoomed m () Source #

afterEvent :: forall base zoomed m a. (Monad m, HasEvents base, Typeable m) => AppT base m a -> ActionT base zoomed m ListenerId Source #

Registers an action to be performed AFTER each event phase.

afterEvent_ :: (Monad m, HasEvents base, Typeable m) => AppT base m a -> ActionT base zoomed m () Source #

onExit :: forall base zoomed m a. (HasEvents base, Typeable m, Monad m) => AppT base m a -> ActionT base zoomed m () Source #

Registers an action to be run before shutdown. Any asynchronous combinators used in this block will NOT be run.

data Listener Source #

A wrapper around event listeners so they can be stored in Listeners.

data ListenerId Source #

An opaque reverence to a specific registered event-listener. A ListenerId is used only to remove listeners later with removeListener.

Instances
Eq ListenerId Source # 
Instance details

Defined in Eve.Internal.Listeners

type EventDispatcher = forall event. Typeable event => event -> IO () Source #

This is a type alias to make defining your functions for use with asyncEventProvider easier; It represents the function your event provider function will be passed to allow dispatching events. Using this type requires the RankNTypes language pragma.