event-0.1.0.2: Monoidal, monadic and first-class events

Copyright(C) 2015 Dimitri Sabadie
LicenseBSD3
MaintainerDimitri Sabadie <dimitri.sabadie@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Control.Concurrent.Event

Contents

Description

An Event a is an object representing an event of type a. You can register actions through it – see the on function – and detach them later on.

An Event has many purposes. The one in mind when writing that package was to interface over C callback-based reactive system. Consider the following Haskell wrapper function, which is based on imperative style:

  -- Create a new button and register an action to launch when the button’s
  -- state changes.
  createButton :: (ButtonState -> IO ()) -> IO Button
  createButton callback = do
    -- create the button
    button <- ...
    forkIO . forever $ do
      -- launch a thread in which we can test whether the state has changed
      when stateHasChanged $ callback newState
    pure button

We can enhance that by representing the action of registering to the event and detaching from it by immediately returning a value:

  createButton :: IO (Button,Event ButtonState)
  createButton = do
    -- create the button
    button <- ...
    -- create an Event
    (ev,t) <- newEvent
    forkIO . forever $
      -- check the new state
      when stateHasChanged $ trigger t newState
    pure (button,ev)

The Trigger can also be returned to manually invoke the Event.

Synopsis

Events

data Event a Source

An Event a is a value of type a with no direct representation. It lives in the future. It’s possible to register actions with on to execute when data becomes available, and to detach those actions with the resulting Detach object by calling detach on it.

Events can be triggered with the trigger function and the associated type Trigger.

newtype Detach Source

Detach is used to detach an action from an Event.

Constructors

Detach 

Fields

detach :: IO ()
 

on :: MonadIO m => Event a -> (a -> IO ()) -> m Detach Source

Register an action.

newEvent :: MonadIO m => m (Event a, Trigger a) Source

Create a new Event a along with a Trigger a.

Triggering events

data Trigger a Source

Trigger a is used to trigger an Event a.

trigger :: MonadIO m => Trigger a -> a -> m () Source

Use a Trigger.