| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
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
- data Observer o where
- Observer :: (Tangible o, TangiblePdu p Asynchronous, Tangible (Endpoint p), Typeable p) => (o -> Maybe (Pdu p Asynchronous)) -> Endpoint p -> Observer o
- type TangibleObserver o = (Tangible o, TangiblePdu (Observer o) Asynchronous)
- data family Pdu (protocol :: Type) (reply :: Synchronicity)
- 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 ()
- forgetObserver :: (SetMember Process (Process q) r, HasCallStack, Member Interrupts r, Typeable o, NFData o, EmbedProtocol x (ObserverRegistry o), TangiblePdu x Asynchronous) => Observer o -> Endpoint x -> Eff r ()
- handleObservations :: (HasCallStack, Typeable o, SetMember Process (Process q) r, NFData (Observer o)) => (o -> Eff r ()) -> Pdu (Observer o) Asynchronous -> Eff r ()
- toObserver :: TangibleObserver o => Endpoint (Observer o) -> Observer o
- toObserverFor :: (TangibleObserver o, Typeable a, TangiblePdu a Asynchronous) => (o -> Pdu a Asynchronous) -> Endpoint a -> Observer o
- data ObserverRegistry o
- type ObserverState o = State (Observers o)
- data Observers o
- emptyObservers :: Observers o
- 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 ()
- manageObservers :: Eff (ObserverState o ': r) a -> Eff r a
- observed :: forall o r q. (SetMember Process (Process q) r, Member (ObserverState o) r, Member Interrupts r, TangibleObserver o) => o -> Eff r ()
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 # | |
| Ord (Observer o) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Observer | |
| Show (Observer o) Source # | |
| NFData o => NFData (Observer o) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Observer | |
| Show o => Show (Pdu (Observer o) r) Source # | |
| NFData o => NFData (Pdu (Observer o) Asynchronous) Source # | |
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 Since: 0.16.0 |
Defined in Control.Eff.Concurrent.Protocol.Observer data Pdu (Observer o) r where
| |
| type ToPretty (Observer o :: Type) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Observer | |
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 # | |
| (Show (Pdu a1 r), Show (Pdu a2 r), Show (Pdu a3 r)) => Show (Pdu (a1, a2, a3) r) Source # | |
| (Show (Pdu a1 r), Show (Pdu a2 r), Show (Pdu a3 r), Show (Pdu a4 r)) => Show (Pdu (a1, a2, a3, a4) r) Source # | |
| (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 # | |
| Show (ChildId p) => Show (Pdu (Sup p) (Synchronous r)) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Supervisor | |
| Show (Pdu (ObserverRegistry o) r) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Observer | |
| Show o => Show (Pdu (Observer o) r) Source # | |
| (NFData (Pdu a1 r), NFData (Pdu a2 r)) => NFData (Pdu (a1, a2) r) Source # | |
Defined in Control.Eff.Concurrent.Protocol | |
| (NFData (Pdu a1 r), NFData (Pdu a2 r), NFData (Pdu a3 r)) => NFData (Pdu (a1, a2, a3) r) Source # | |
Defined in Control.Eff.Concurrent.Protocol | |
| (NFData (Pdu a1 r), NFData (Pdu a2 r), NFData (Pdu a3 r), NFData (Pdu a4 r)) => NFData (Pdu (a1, a2, a3, a4) r) Source # | |
Defined in Control.Eff.Concurrent.Protocol | |
| (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 # | |
Defined in Control.Eff.Concurrent.Protocol | |
| NFData (ChildId p) => NFData (Pdu (Sup p) (Synchronous r)) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Supervisor Methods rnf :: Pdu (Sup p) (Synchronous r) -> () # | |
| NFData (Pdu (ObserverRegistry o) r) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Observer Methods rnf :: Pdu (ObserverRegistry o) r -> () # | |
| NFData o => NFData (Pdu (Observer o) Asynchronous) Source # | |
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 Since: 0.16.0 |
Defined in Control.Eff.Concurrent.Protocol.Observer data Pdu (Observer o) r where
| |
| type ToPretty (Pdu x y :: Type) Source # | |
| data Pdu (a1, a2) x Source # | |
Defined in Control.Eff.Concurrent.Protocol | |
| data Pdu (Sup p) r Source # | The Since: 0.23.0 |
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 Since: 0.16.0 |
Defined in Control.Eff.Concurrent.Protocol.Observer data Pdu (ObserverRegistry o) r where
| |
| data Pdu (a1, a2, a3) x Source # | |
| data Pdu (a1, a2, a3, a4) x Source # | |
| data Pdu (a1, a2, a3, a4, a5) x Source # | |
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
forgetObserver :: (SetMember Process (Process q) r, HasCallStack, Member Interrupts r, Typeable o, NFData o, EmbedProtocol x (ObserverRegistry o), TangiblePdu x Asynchronous) => Observer o -> Endpoint x -> Eff r () Source #
Send the ForgetObserver message
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
toObserver :: TangibleObserver o => Endpoint (Observer o) -> Observer o Source #
Use a Endpoint as an Observer for handleObservations.
Since: 0.16.0
toObserverFor :: (TangibleObserver o, Typeable a, TangiblePdu a Asynchronous) => (o -> Pdu a Asynchronous) -> Endpoint a -> Observer o Source #
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 # | |
Defined in Control.Eff.Concurrent.Protocol.Observer | |
| NFData (Pdu (ObserverRegistry o) r) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Observer Methods rnf :: Pdu (ObserverRegistry o) r -> () # | |
| type ToPretty (ObserverRegistry o :: Type) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Observer | |
| 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 Since: 0.16.0 |
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
Internal state for manageObservers
Instances
| Eq (Observers o) Source # | |
| Ord (Observers o) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Observer | |
| Show (Observers o) Source # | |
| NFData o => NFData (Observers o) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Observer | |
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