eve-0.1.0: An extensible event framework

Safe HaskellNone
LanguageHaskell2010

Eve

Synopsis

Documentation

data Action zoomed a Source #

Instances

MonadState zoomed (Action zoomed) Source # 

Methods

get :: Action zoomed zoomed #

put :: zoomed -> Action zoomed () #

state :: (zoomed -> (a, zoomed)) -> Action zoomed a #

MonadFree ActionF (Action zoomed) Source # 

Methods

wrap :: ActionF (Action zoomed a) -> Action zoomed a #

Monad (Action zoomed) Source # 

Methods

(>>=) :: Action zoomed a -> (a -> Action zoomed b) -> Action zoomed b #

(>>) :: Action zoomed a -> Action zoomed b -> Action zoomed b #

return :: a -> Action zoomed a #

fail :: String -> Action zoomed a #

Functor (Action zoomed) Source # 

Methods

fmap :: (a -> b) -> Action zoomed a -> Action zoomed b #

(<$) :: a -> Action zoomed b -> Action zoomed a #

Applicative (Action zoomed) Source # 

Methods

pure :: a -> Action zoomed a #

(<*>) :: Action zoomed (a -> b) -> Action zoomed a -> Action zoomed b #

(*>) :: Action zoomed a -> Action zoomed b -> Action zoomed b #

(<*) :: Action zoomed a -> Action zoomed b -> Action zoomed a #

MonadIO (Action zoomed) Source # 

Methods

liftIO :: IO a -> Action zoomed a #

Zoom (Action s) (Action t) s t Source # 

Methods

zoom :: LensLike' (Zoomed (Action s) c) t s -> Action s c -> Action t c #

type Zoomed (Action s) Source # 

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

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

dispatchEventAsync :: Typeable event => IO event -> App () Source #

This function takes an IO which results in some event, it runs the IO asynchronously and dispatches the event. Note that any listeners which are registered for the resulting event will still be run syncronously, only the code which generates the event is asynchronous.

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

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

onInit :: App result -> App () Source #

Registers an action to be performed during the Initialization phase.

This phase occurs exactly ONCE when the app starts up. Though arbitrary actions may be performed in the configuration block; it's recommended to embed such actions in the onInit event listener so that all event listeners are registered before any dispatches occur.

afterInit :: App a -> App () Source #

beforeEvent :: App a -> App ListenerId Source #

Registers an action to be performed BEFORE each event phase.

afterEvent :: App a -> App ListenerId Source #

Registers an action to be performed BEFORE each event phase.

onExit :: App a -> App () Source #

asyncActionProvider :: ((App () -> IO ()) -> IO ()) -> App () Source #

asyncEventProvider :: (Dispatcher -> IO ()) -> App () Source #

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

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

Let's break it down:

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

This type as a whole represents a function which accepts a Dispatcher 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 :: Dispatcher -> IO ()
myTimer dispatch = forever $ dispatch Timer >> threadDelay 1000000

myAction :: Action s ()
myAction = onInit $ asyncEventProvider myTimer

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.

class HasExts s where Source #

Represents a state which can be extended. exts is a Lens' which points to the state's Exts

Minimal complete definition

exts

Methods

exts :: Lens' s Exts Source #

type Exts = Map TypeRep Ext Source #

A map of extension types to their current value.

class (Typeable s, HasExts 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.

ext :: forall a e. (Show a, Typeable a, Default a, HasExts e) => Lens' e a Source #

A polymorphic lens which accesses extensions in the extension state. It returns the default value (def) if a state has not yet been set.

runAction :: Zoom m n s t => LensLike' (Zoomed m c) t s -> m c -> n c Source #