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

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.Protocol.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 Pdu 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 :: (Tangible o, TangiblePdu p Asynchronous, Tangible (Endpoint p), Typeable p) => (o -> Maybe (Pdu p Asynchronous)) -> Endpoint p -> Observer o 
Instances
Eq (Observer o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

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

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

Ord (Observer o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.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.Protocol.Observer

Methods

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

show :: Observer o -> String #

showList :: [Observer o] -> ShowS #

NFData o => NFData (Observer o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Observer o -> () #

Show o => Show (Pdu (Observer o) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

showsPrec :: Int -> Pdu (Observer o) r -> ShowS #

show :: Pdu (Observer o) r -> String #

showList :: [Pdu (Observer o) r] -> ShowS #

NFData o => NFData (Pdu (Observer o) Asynchronous) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Pdu (Observer o) Asynchronous -> () #

data Pdu (Observer o) r Source #

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

Since: 0.16.0

Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

data Pdu (Observer o) r where
type ToPretty (Observer o :: Type) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

type ToPretty (Observer o :: Type) = PrettyParens ("observing" <:> ToPretty o)

type TangibleObserver o = (Tangible o, TangiblePdu (Observer o) Asynchronous) Source #

The constraints on the type parameters to an Observer

Since: 0.24.0

data family Pdu (protocol :: Type) (reply :: Synchronicity) Source #

This data family defines the **protocol data units**(PDU) of a protocol.

A Protocol in the sense of a communication interface description between processes.

The first parameter is usually a user defined type that identifies the protocol that uses the Pdus are. It maybe a phantom type.

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

Example:

data BookShop deriving Typeable

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

type BookId = Int
type RentalId = Int
type RentalError = String
Instances
(Show (Pdu a1 r), Show (Pdu a2 r)) => Show (Pdu (a1, a2) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

showsPrec :: Int -> Pdu (a1, a2) r -> ShowS #

show :: Pdu (a1, a2) r -> String #

showList :: [Pdu (a1, a2) r] -> ShowS #

(Show (Pdu a1 r), Show (Pdu a2 r), Show (Pdu a3 r)) => Show (Pdu (a1, a2, a3) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

showsPrec :: Int -> Pdu (a1, a2, a3) r -> ShowS #

show :: Pdu (a1, a2, a3) r -> String #

showList :: [Pdu (a1, a2, a3) r] -> ShowS #

(Show (Pdu a1 r), Show (Pdu a2 r), Show (Pdu a3 r), Show (Pdu a4 r)) => Show (Pdu (a1, a2, a3, a4) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

showsPrec :: Int -> Pdu (a1, a2, a3, a4) r -> ShowS #

show :: Pdu (a1, a2, a3, a4) r -> String #

showList :: [Pdu (a1, a2, a3, a4) r] -> ShowS #

(Show (Pdu a1 r), Show (Pdu a2 r), Show (Pdu a3 r), Show (Pdu a4 r), Show (Pdu a5 r)) => Show (Pdu (a1, a2, a3, a4, a5) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

showsPrec :: Int -> Pdu (a1, a2, a3, a4, a5) r -> ShowS #

show :: Pdu (a1, a2, a3, a4, a5) r -> String #

showList :: [Pdu (a1, a2, a3, a4, a5) r] -> ShowS #

Show (ChildId p) => Show (Pdu (Sup p) (Synchronous r)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

Methods

showsPrec :: Int -> Pdu (Sup p) (Synchronous r) -> ShowS #

show :: Pdu (Sup p) (Synchronous r) -> String #

showList :: [Pdu (Sup p) (Synchronous r)] -> ShowS #

Show (Pdu (ObserverRegistry o) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Show o => Show (Pdu (Observer o) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

showsPrec :: Int -> Pdu (Observer o) r -> ShowS #

show :: Pdu (Observer o) r -> String #

showList :: [Pdu (Observer o) r] -> ShowS #

(NFData (Pdu a1 r), NFData (Pdu a2 r)) => NFData (Pdu (a1, a2) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

rnf :: Pdu (a1, a2) r -> () #

(NFData (Pdu a1 r), NFData (Pdu a2 r), NFData (Pdu a3 r)) => NFData (Pdu (a1, a2, a3) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

rnf :: Pdu (a1, a2, a3) r -> () #

(NFData (Pdu a1 r), NFData (Pdu a2 r), NFData (Pdu a3 r), NFData (Pdu a4 r)) => NFData (Pdu (a1, a2, a3, a4) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

rnf :: Pdu (a1, a2, a3, a4) r -> () #

(NFData (Pdu a1 r), NFData (Pdu a2 r), NFData (Pdu a3 r), NFData (Pdu a4 r), NFData (Pdu a5 r)) => NFData (Pdu (a1, a2, a3, a4, a5) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

rnf :: Pdu (a1, a2, a3, a4, a5) r -> () #

NFData (ChildId p) => NFData (Pdu (Sup p) (Synchronous r)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

Methods

rnf :: Pdu (Sup p) (Synchronous r) -> () #

NFData (Pdu (ObserverRegistry o) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Pdu (ObserverRegistry o) r -> () #

NFData o => NFData (Pdu (Observer o) Asynchronous) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Pdu (Observer o) Asynchronous -> () #

data Pdu (Observer o) r Source #

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

Since: 0.16.0

Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

data Pdu (Observer o) r where
type ToPretty (Pdu x y :: Type) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

type ToPretty (Pdu x y :: Type) = PrettySurrounded (PutStr "<") (PutStr ">") (("protocol" <:> ToPretty x) <+> ToPretty y)
data Pdu (a1, a2) x Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

data Pdu (a1, a2) x
data Pdu (Sup p) r Source #

The Pdu instance contains methods to start, stop and lookup a child process, as well as a diagnostic callback.

Since: 0.23.0

Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

data Pdu (Sup p) r where
data Pdu (ObserverRegistry o) r Source #

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

data Pdu (ObserverRegistry o) r where
data Pdu (a1, a2, a3) x Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

data Pdu (a1, a2, a3) x
data Pdu (a1, a2, a3, a4) x Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

data Pdu (a1, a2, a3, a4) x
data Pdu (a1, a2, a3, a4, a5) x Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

data Pdu (a1, a2, a3, a4, a5) x

registerObserver :: (SetMember Process (Process q) r, HasCallStack, Member Interrupts r, TangibleObserver o, EmbedProtocol x (ObserverRegistry o), TangiblePdu x Asynchronous) => Observer o -> Endpoint x -> 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, NFData (Observer o)) => (o -> Eff r ()) -> Pdu (Observer o) Asynchronous -> Eff r () Source #

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

Since: 0.16.0

toObserverFor :: (TangibleObserver o, Typeable a, TangiblePdu a Asynchronous) => (o -> Pdu a Asynchronous) -> Endpoint 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 Pdu cast that the observer server is compatible to.

Since: 0.16.0

data ObserverRegistry o Source #

A protocol for managing Observers, encompassing registration and de-registration of Observers.

Since: 0.16.0

Instances
Show (Pdu (ObserverRegistry o) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

NFData (Pdu (ObserverRegistry o) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Pdu (ObserverRegistry o) r -> () #

type ToPretty (ObserverRegistry o :: Type) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

type ToPretty (ObserverRegistry o :: Type) = PrettyParens ("observer registry" <:> ToPretty o)
data Pdu (ObserverRegistry o) r Source #

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

data Pdu (ObserverRegistry o) r where

type ObserverState o = State (Observers o) Source #

Alias for the effect that contains the observers managed by manageObservers

data Observers o Source #

Internal state for manageObservers

Instances
Eq (Observers o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

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

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

Ord (Observers o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Show (Observers o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

NFData o => NFData (Observers o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Observers o -> () #

emptyObservers :: Observers o Source #

The empty ObserverState

Since: 0.24.0

handleObserverRegistration :: forall o q r. (HasCallStack, Typeable o, SetMember Process (Process q) r, Member (ObserverState o) r, Member Logs r) => Pdu (ObserverRegistry o) Asynchronous -> Eff r () Source #

Provide the implementation for the ObserverRegistry Protocol, 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, TangibleObserver o) => o -> Eff r () Source #

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

Since: 0.16.0