extensible-effects-concurrent-0.21.1: Message passing concurrency as extensible-effect

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.Api.Observer

Description

Observer Effects

This module supports the implementation of observers and observables. Expected use case is event propagation.

Since: 0.16.0

Synopsis

Documentation

data Observer o where Source #

Describes a process that observes another via Asynchronous Api messages.

An observer consists of a filter and a process id. The filter converts an observation to a message understood by the observer process, and the ProcessId is used to send the message.

Since: 0.16.0

Constructors

Observer :: (Show (Server p), Typeable p, Typeable o) => (o -> Maybe (Api p Asynchronous)) -> Server p -> Observer o 
Instances
Eq (Observer o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Observer

Methods

(==) :: Observer o -> Observer o -> Bool #

(/=) :: Observer o -> Observer o -> Bool #

Ord (Observer o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Observer

Methods

compare :: Observer o -> Observer o -> Ordering #

(<) :: Observer o -> Observer o -> Bool #

(<=) :: Observer o -> Observer o -> Bool #

(>) :: Observer o -> Observer o -> Bool #

(>=) :: Observer o -> Observer o -> Bool #

max :: Observer o -> Observer o -> Observer o #

min :: Observer o -> Observer o -> Observer o #

Show (Observer o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Observer

Methods

showsPrec :: Int -> Observer o -> ShowS #

show :: Observer o -> String #

showList :: [Observer o] -> ShowS #

data Api (Observer o) r Source #

A minimal Api for handling observations. This is one simple way of receiving observations - of course users can use any other Asynchronous Api message type for receiving observations.

Since: 0.16.0

Instance details

Defined in Control.Eff.Concurrent.Api.Observer

data Api (Observer o) r where

data family Api (api :: Type) (reply :: Synchronicity) Source #

This data family defines an API, a communication interface description between at least two processes. The processes act as servers or client(s) regarding a specific instance of this type.

The first parameter is usually a user defined phantom type that identifies the Api instance.

The second parameter specifies if a specific constructor of an (GADT-like) Api instance is Synchronous, i.e. returns a result and blocks the caller or if it is Asynchronous

Example:

data BookShop deriving Typeable

data instance Api BookShop r where
  RentBook  :: BookId   -> Api BookShop ('Synchronous (Either RentalError RentalId))
  BringBack :: RentalId -> Api BookShop 'Asynchronous

type BookId = Int
type RentalId = Int
type RentalError = String
Instances
data Api (Observer o) r Source #

A minimal Api for handling observations. This is one simple way of receiving observations - of course users can use any other Asynchronous Api message type for receiving observations.

Since: 0.16.0

Instance details

Defined in Control.Eff.Concurrent.Api.Observer

data Api (Observer o) r where
data Api (ObserverRegistry o) r Source #

Api for managing observers. This can be added to any server for any number of different observation types. The functions manageObservers and handleObserverRegistration are used to include observer handling;

Since: 0.16.0

Instance details

Defined in Control.Eff.Concurrent.Api.Observer

data Api (ObserverRegistry o) r where

registerObserver :: (SetMember Process (Process q) r, HasCallStack, Member Interrupts r, Typeable o) => Observer o -> Server (ObserverRegistry o) -> Eff r () Source #

And an Observer to the set of recipients for all observations reported by observed. Note that the observers are keyed by the observing process, i.e. a previous entry for the process contained in the Observer is overwritten. If you want multiple entries for a single process, just combine several filter functions.

Since: 0.16.0

handleObservations :: (HasCallStack, Typeable o, SetMember Process (Process q) r) => (o -> Eff r CallbackResult) -> MessageCallback (Observer o) r Source #

Based on the Api instance for Observer this simplified writing a callback handler for observations. In order to register to and ObserverRegistry use toObserver.

Since: 0.16.0

toObserver :: Typeable o => Server (Observer o) -> Observer o Source #

Use a Server as an Observer for handleObservations.

Since: 0.16.0

toObserverFor :: (Typeable a, Typeable o) => (o -> Api a Asynchronous) -> Server a -> Observer o Source #

Create an Observer that conditionally accepts all observations of the given type and applies the given function to them; the function takes an observation and returns an Api cast that the observer server is compatible to.

Since: 0.16.0

data ObserverRegistry o Source #

An Api for managing Observers, encompassing registration and de-registration of Observers.

Since: 0.16.0

Instances
data Api (ObserverRegistry o) r Source #

Api for managing observers. This can be added to any server for any number of different observation types. The functions manageObservers and handleObserverRegistration are used to include observer handling;

Since: 0.16.0

Instance details

Defined in Control.Eff.Concurrent.Api.Observer

data Api (ObserverRegistry o) r where

type ObserverState o = State (Observers o) Source #

Alias for the effect that contains the observers managed by manageObservers

handleObserverRegistration :: forall o q r. (HasCallStack, Typeable o, SetMember Process (Process q) r, Member (ObserverState o) r) => MessageCallback (ObserverRegistry o) r Source #

Provide the implementation for the ObserverRegistry Api, this handled RegisterObserver and ForgetObserver messages. It also adds the ObserverState constraint to the effect list.

Since: 0.16.0

manageObservers :: Eff (ObserverState o ': r) a -> Eff r a Source #

Keep track of registered Observers.

Handle the ObserverState introduced by handleObserverRegistration.

Since: 0.16.0

observed :: forall o r q. (SetMember Process (Process q) r, Member (ObserverState o) r, Member Interrupts r) => o -> Eff r () Source #

Report an observation to all observers. The process needs to manageObservers and to handleObserverRegistration.

Since: 0.16.0