eve-0.1.2: An extensible event framework

Safe HaskellNone
LanguageHaskell2010

Eve

Contents

Synopsis

Running your App

eve :: (MonadIO m, Typeable m) => AppT AppState m () -> m AppState Source #

This runs your application. It accepts an initialization block (which is the same as any other App or Action block, which registers event listeners and event providers. Note that nothing in this block should use dispatchEvent since it is possible that not all listeners have yet been registered. You can use the afterInit trigger to dispatch any events you'd like to run at start-up.

It is polymorphic in the Monad it operates over, so you may use it with any custom base monad which implements MonadIO.

If you don't need this functionality; the easiest way to get started is to simply cally it like so:

import Eve

initialize = App ()
initialize = do
  addListener ...
  ...

startApp :: IO ()
startApp = eve_ initialize

Working with Actions

type App a = AppT AppState IO a Source #

An App is a base level monad which operates over your main application state. You may call runAction inside an app to run Actions over other states. need to specify your own custom base state.

type Action state a = ActionT AppState state IO a Source #

An Action is a monad over some zoomed in state, they are run inside App using runAction. For example an Action which operates over a String somewhere in your app state would be written as:

alterString :: Action String ()

type AppT s m a = ActionT s s m a Source #

An App has the same base and zoomed values.

data ActionT base zoomed m a Source #

Base Action type. Allows paramaterization over application state, zoomed state and underlying monad.

Instances

Monad m => MonadState zoomed (ActionT base zoomed m) Source # 

Methods

get :: ActionT base zoomed m zoomed #

put :: zoomed -> ActionT base zoomed m () #

state :: (zoomed -> (a, zoomed)) -> ActionT base zoomed m a #

MonadTrans (ActionT base zoomed) Source # 

Methods

lift :: Monad m => m a -> ActionT base zoomed m a #

Monad n => MonadFree (AppF base n) (ActionT base zoomed n) Source # 

Methods

wrap :: AppF base n (ActionT base zoomed n a) -> ActionT base zoomed n a #

Monad m => Monad (ActionT base zoomed m) Source # 

Methods

(>>=) :: ActionT base zoomed m a -> (a -> ActionT base zoomed m b) -> ActionT base zoomed m b #

(>>) :: ActionT base zoomed m a -> ActionT base zoomed m b -> ActionT base zoomed m b #

return :: a -> ActionT base zoomed m a #

fail :: String -> ActionT base zoomed m a #

Monad m => Functor (ActionT base zoomed m) Source # 

Methods

fmap :: (a -> b) -> ActionT base zoomed m a -> ActionT base zoomed m b #

(<$) :: a -> ActionT base zoomed m b -> ActionT base zoomed m a #

Monad m => Applicative (ActionT base zoomed m) Source # 

Methods

pure :: a -> ActionT base zoomed m a #

(<*>) :: ActionT base zoomed m (a -> b) -> ActionT base zoomed m a -> ActionT base zoomed m b #

(*>) :: ActionT base zoomed m a -> ActionT base zoomed m b -> ActionT base zoomed m b #

(<*) :: ActionT base zoomed m a -> ActionT base zoomed m b -> ActionT base zoomed m a #

MonadIO m => MonadIO (ActionT base zoomed m) Source # 

Methods

liftIO :: IO a -> ActionT base zoomed m a #

Monad m => Zoom (ActionT base s m) (ActionT base t m) s t Source # 

Methods

zoom :: LensLike' (Zoomed (ActionT base s m) c) t s -> ActionT base s m c -> ActionT base t m c #

type Zoomed (ActionT base zoomed m) Source # 
type Zoomed (ActionT base zoomed m) = Zoomed (FreeT (AppF base m) (StateT zoomed m))

liftApp :: Monad m => AppT base m a -> ActionT base zoomed m a Source #

Allows you to run an App or AppM inside of an Action or ActionM

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

Given a Lens or Traversal or something similar from Control.Lens which focuses the state (t) of an Action from a base state (s), this will convert Action t a -> Action s a.

Given a lens HasStates s => Lens' s t it can also convert Action t a -> App a

exit :: (Monad m, HasStates s) => ActionT s zoomed m () Source #

Tells the application to quit. This triggers onExit listeners following the current event loop.

Dispatching Events

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

Given an Event of any type, this runs any listeners registered for that event type with the provided event. Events may also contain data pertaining to the event and it will be passed to the listeners.

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 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.

dispatchActionAsync :: (MonadIO m, HasStates base, Typeable m, Typeable base) => IO (AppT base m ()) -> ActionT base zoomed m () Source #

Dispatch an action which is generated by some IO. Note that state of the application may have changed between calling dispatchActionAsync and running the resulting Action

Event Listeners

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 #

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 s. (MonadState s m, HasEvents s, Typeable m, Typeable eventType, Typeable result, Monoid result) => (eventType -> m result) -> m () Source #

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

Unregisters a listener referred to by the provided ListenerId

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.

Asynchronous Helpers

asyncActionProvider :: (MonadIO m, HasStates base, Typeable m, Typeable base) => ((AppT base m () -> IO ()) -> IO ()) -> ActionT base zoomed m () Source #

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

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

Let's break it down:

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

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

asyncEventProvider :: (HasEvents base, MonadIO m, Typeable m) => (Dispatcher -> 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 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

myInit :: App ()
myInit = asyncEventProvider myTimer

type Dispatcher = 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.

Built-in Event Listeners

afterInit :: forall base zoomed m a. (Monad m, HasEvents zoomed, Typeable m, Typeable base) => ActionT base zoomed m a -> ActionT base zoomed 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 zoomed, Typeable m, Typeable base) => ActionT base zoomed 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 zoomed, Typeable m, Typeable base) => ActionT base zoomed m a -> ActionT base zoomed m () Source #

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

Registers an action to be performed AFTER each event phase.

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

onExit :: forall base zoomed m a. (HasEvents zoomed, Typeable m, Typeable base, Monad m) => ActionT base zoomed 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.

Working with State

All application-provided states are stored in the same Map; keyed by their TypeRep. This means that if more than one state uses the same type then they'll conflict and overwrite each-other (this is less of a problem than you're probably thinking). This is easily solved by simply using a newtype around any types you haven't defined yourself. For example if your application stores a counter as an Int, wrap it in your own custom Counter newtype when storing it. If you wish to store multiple copies of a given state simply store them in a list or map, then store that container as your state.

Because states are stored by their TypeRep, they must define an instance of Typeable, luckily GHC can derive this for you with deriving Typeable.

It is also required for all states to define an instance of Default, this is because accessing an extension which has not yet been stored will result in the default value.

If there's no default value that makes sense for your type, you can define a default of Nothing and pattern-match on its value when you access it.

Stored states are accessed by using the stateLens lens, this lens is polymorphic and can return ANY type. GHC infers the needed type and the lens will retrieve the state that you want from the store of states. It seems a bit complicated, but it all works fine in practice.

To avoid confusion it's best to rename a version of stateLens with a more restrictive type for each different state type that you store. This helps prevent strange errors and makes your code much easier to read. For example:

data MyState = MyState String
myState :: HasStates s => Lens' s MyState
myState = stateLens

myAction = do
  MyState str <- use stateLens

If GHC has trouble inferring the type, rename it and restrict the type as above.

class HasStates s where Source #

Represents a state which can itself store more states. states is a lens which points to a given state's States map.

Minimal complete definition

states

Methods

states :: Lens' s States Source #

type States = Map TypeRep StateWrapper Source #

A map of state types to their current value.

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.

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

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

data AppState Source #

A basic default state which underlies App Contains only a map of States.