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

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.Protocol.Observer

Description

Observer Effects

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

The observable event sources and the observers are usually server processes for a protocol that embeds the ObserverRegistry and Observer Pdus respectively.

A generic FIFO queue based observer can be found in Control.Eff.Concurrent.Protocol.Observer.Queue.

Since: 0.16.0

Synopsis

Documentation

newtype Observer event Source #

A protocol to communicate Observed events from a sources to many sinks.

A sink is any process that serves a protocol with a Pdu instance that embeds the Observer Pdu via an HasPduPrism instance.

This type has dual use, for one it serves as type-index for Pdu, i.e. HasPdu respectively, and secondly it contains an ObservationSink and a MonitorReference.

The ObservationSink is used to serialize and send the Observed events, while the ProcessId serves as key for internal maps.

Since: 0.28.0

Constructors

MkObserver (Arg ProcessId (ObservationSink event)) 
Instances
Typeable child => HasPduPrism (Watchdog child) (Observer (ChildEvent child)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Methods

embeddedPdu :: Prism' (Pdu (Watchdog child) result) (Pdu (Observer (ChildEvent child)) result) Source #

embedPdu :: Pdu (Observer (ChildEvent child)) result -> Pdu (Watchdog child) result Source #

fromPdu :: Pdu (Watchdog child) result -> Maybe (Pdu (Observer (ChildEvent child)) result) Source #

Eq (Observer event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

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

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

Ord (Observer event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

compare :: Observer event -> Observer event -> Ordering #

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

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

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

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

max :: Observer event -> Observer event -> Observer event #

min :: Observer event -> Observer event -> Observer event #

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

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

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

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

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

Typeable event => Show (Observer event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

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

show :: Observer event -> String #

showList :: [Observer event] -> ShowS #

NFData event => NFData (Pdu (Observer event) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Pdu (Observer event) r -> () #

NFData (Observer event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Observer event -> () #

Tangible event => HasPdu (Observer event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Associated Types

type EmbeddedPduList (Observer event) :: [Type] Source #

data Pdu (Observer event) reply :: Type Source #

type ToPretty (Observer event :: Type) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

type ToPretty (Observer event :: Type) = PrettyParens ("observing" <:> ToPretty event)
type EmbeddedPduList (Observer event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

type EmbeddedPduList (Observer event) = ([] :: [Type])
data Pdu (Observer event) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

data Pdu (Observer event) r where

data ObservationSink event Source #

The Information necessary to wrap an Observed event to a process specific message, e.g. the embedded Observer Pdu instance, and the MonitorReference of the destination process.

Since: 0.28.0

Instances
Generic (ObservationSink event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Associated Types

type Rep (ObservationSink event) :: Type -> Type #

Methods

from :: ObservationSink event -> Rep (ObservationSink event) x #

to :: Rep (ObservationSink event) x -> ObservationSink event #

NFData (ObservationSink event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: ObservationSink event -> () #

type Rep (ObservationSink event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

type Rep (ObservationSink event) = D1 (MetaData "ObservationSink" "Control.Eff.Concurrent.Protocol.Observer" "extensible-effects-concurrent-0.32.0-GimAdtHOovq4dulPgeQPe9" False) (C1 (MetaCons "MkObservationSink" PrefixI True) (S1 (MetaSel (Just "_observerSerializer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Serializer (Pdu (Observer event) Asynchronous))) :*: S1 (MetaSel (Just "_observerMonitorReference") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MonitorReference)))

type IsObservable eventSource event = (Tangible event, Embeds eventSource (ObserverRegistry event), HasPdu eventSource) Source #

Convenience type alias.

Since: 0.28.0

type CanObserve eventSink event = (Tangible event, Embeds eventSink (Observer event), HasPdu eventSink) Source #

Convenience type alias.

Since: 0.28.0

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

The protocol data unit type for the given protocol.

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 #

Typeable event => Show (Pdu (ObserverRegistry event) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

showsPrec :: Int -> Pdu (ObserverRegistry event) r -> ShowS #

show :: Pdu (ObserverRegistry event) r -> String #

showList :: [Pdu (ObserverRegistry event) r] -> ShowS #

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

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

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

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

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

(Typeable p, Show (ChildId p)) => Show (Pdu (Broker p) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Methods

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

show :: Pdu (Broker p) r -> String #

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

(Show (ChildId child), Typeable child, Typeable (ServerPdu child)) => Show (Pdu (Watchdog child) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Methods

showsPrec :: Int -> Pdu (Watchdog child) r -> ShowS #

show :: Pdu (Watchdog child) r -> String #

showList :: [Pdu (Watchdog child) 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 -> () #

(Typeable 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 (Pdu (ObserverRegistry event) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

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

NFData event => NFData (Pdu (Observer event) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Pdu (Observer event) r -> () #

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

Defined in Control.Eff.Concurrent.Protocol.Broker

Methods

rnf :: Pdu (Broker p) r -> () #

NFData (ChildId child) => NFData (Pdu (Watchdog child) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Methods

rnf :: Pdu (Watchdog child) r -> () #

data Pdu (ObserverRegistry event) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

data Pdu (Broker p) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

data Pdu (Broker p) r where
data Pdu (Watchdog child) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

data Pdu (Watchdog child) 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) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

data Pdu (a1, a2) r
data Pdu (Observer event) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

data Pdu (Observer event) r where
data Pdu (a1, a2, a3) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

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

Defined in Control.Eff.Concurrent.Protocol

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

Defined in Control.Eff.Concurrent.Protocol

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

registerObserver :: forall event eventSink eventSource r q. (HasCallStack, HasProcesses r q, IsObservable eventSource event, Tangible (Pdu eventSource Asynchronous), Tangible (Pdu eventSink Asynchronous), CanObserve eventSink event) => Endpoint eventSource -> Endpoint eventSink -> Eff r () Source #

And an Observer to the set of recipients for all observations reported by observerRegistryNotify. Note that the observerRegistry 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

forgetObserver :: forall event eventSink eventSource r q. (HasProcesses r q, HasCallStack, Tangible (Pdu eventSource Asynchronous), Tangible (Pdu eventSink Asynchronous), IsObservable eventSource event, CanObserve eventSink event) => Endpoint eventSource -> Endpoint eventSink -> Eff r () Source #

Send the ForgetObserver message

Since: 0.16.0

forgetObserverUnsafe :: forall event eventSource r q. (HasProcesses r q, HasCallStack, Tangible (Pdu eventSource Asynchronous), IsObservable eventSource event) => Endpoint eventSource -> ProcessId -> Eff r () Source #

Send the ForgetObserver message, use a raw ProcessId as parameter.

Since: 0.28.0

data ObserverRegistry (event :: Type) Source #

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

Since: 0.28.0

Instances
Tangible event => HasPdu (ObserverRegistry event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Associated Types

type EmbeddedPduList (ObserverRegistry event) :: [Type] Source #

data Pdu (ObserverRegistry event) reply :: Type Source #

Typeable p => HasPduPrism (Broker p) (ObserverRegistry (ChildEvent p)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Methods

embeddedPdu :: Prism' (Pdu (Broker p) result) (Pdu (ObserverRegistry (ChildEvent p)) result) Source #

embedPdu :: Pdu (ObserverRegistry (ChildEvent p)) result -> Pdu (Broker p) result Source #

fromPdu :: Pdu (Broker p) result -> Maybe (Pdu (ObserverRegistry (ChildEvent p)) result) Source #

Typeable event => Show (Pdu (ObserverRegistry event) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

showsPrec :: Int -> Pdu (ObserverRegistry event) r -> ShowS #

show :: Pdu (ObserverRegistry event) r -> String #

showList :: [Pdu (ObserverRegistry event) r] -> ShowS #

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

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

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

type EmbeddedPduList (ObserverRegistry event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

type EmbeddedPduList (ObserverRegistry event) = ([] :: [Type])
data Pdu (ObserverRegistry event) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

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

Defined in Control.Eff.Concurrent.Protocol.Observer

type ToPretty (ObserverRegistry event :: Type) = PrettyParens ("observer registry" <:> ToPretty event)

type ObserverRegistryState event = State (ObserverRegistry event) Source #

Alias for the effect that contains the observers managed by evalObserverRegistryState

observerRegistryNotify :: forall event r q. (HasProcesses r q, Member (ObserverRegistryState event) r, Tangible event, HasCallStack) => event -> Eff r () Source #

Report an observation to all observers. The process needs to evalObserverRegistryState and to observerRegistryHandlePdu.

Since: 0.28.0

evalObserverRegistryState :: HasCallStack => Eff (ObserverRegistryState event ': r) a -> Eff r a Source #

Keep track of registered Observers.

Handle the ObserverRegistryState effect, i.e. run evalState on an emptyObserverRegistry.

Since: 0.28.0

observerRegistryHandlePdu :: forall event q r. (HasCallStack, Typeable event, HasProcesses r q, Member (ObserverRegistryState event) r, Member Logs r) => Pdu (ObserverRegistry event) Asynchronous -> Eff r () Source #

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

Since: 0.28.0

observerRegistryRemoveProcess :: forall event q r. (HasCallStack, Typeable event, HasProcesses r q, Member (ObserverRegistryState event) r, Member Logs r) => ProcessId -> Eff r Bool Source #

Remove the entry in the ObserverRegistry for the ProcessId and return True if there was an entry, False otherwise.

Since: 0.28.0