| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Eff.Concurrent.Protocol.CallbackServer
Description
Build a Control.Eff.Concurrent.EffectfulServer from callbacks.
This module contains in instance of Server that delegates to
callback functions.
Since: 0.27.0
Synopsis
- start :: forall (tag :: Type) eLoop q e. (HasCallStack, TangibleCallbacks tag eLoop q, Server (Server tag eLoop q) (Processes q), FilteredLogging (Processes q), HasProcesses e q) => CallbacksEff tag eLoop q -> Eff e (Endpoint tag)
- startLink :: forall (tag :: Type) eLoop q e. (HasCallStack, TangibleCallbacks tag eLoop q, Server (Server tag eLoop q) (Processes q), FilteredLogging (Processes q), HasProcesses e q) => CallbacksEff tag eLoop q -> Eff e (Endpoint tag)
- data Server tag eLoop e
- newtype ServerId (tag :: Type) = MkServerId {}
- data Event a where
- OnCall :: forall a r. (Tangible r, TangiblePdu a (Synchronous r)) => ReplyTarget a r -> Pdu a (Synchronous r) -> Event a
- OnCast :: forall a. TangiblePdu a Asynchronous => Pdu a Asynchronous -> Event a
- OnInterrupt :: Interrupt Recoverable -> Event a
- OnDown :: ProcessDown -> Event a
- OnTimeOut :: TimerElapsed -> Event a
- OnMessage :: StrictDynamic -> Event a
- type TangibleCallbacks tag eLoop e = (HasProcesses eLoop e, Typeable e, Typeable eLoop, Typeable tag)
- type Callbacks tag e = CallbacksEff tag (Processes e) e
- callbacks :: forall tag q. (HasCallStack, TangibleCallbacks tag (Processes q) q, Server (Server tag (Processes q) q) (Processes q), FilteredLogging q) => (Endpoint tag -> Event tag -> Eff (Processes q) ()) -> ServerId tag -> Callbacks tag q
- onEvent :: forall tag q. (HasCallStack, TangibleCallbacks tag (Processes q) q, Server (Server tag (Processes q) q) (Processes q), FilteredLogging q) => (Event tag -> Eff (Processes q) ()) -> ServerId (tag :: Type) -> Callbacks tag q
- type CallbacksEff tag eLoop e = Init (Server tag eLoop e)
- callbacksEff :: forall tag eLoop q. (HasCallStack, TangibleCallbacks tag eLoop q, Server (Server tag eLoop q) (Processes q), FilteredLogging q) => (forall x. Endpoint tag -> Eff eLoop x -> Eff (Processes q) x) -> (Endpoint tag -> Event tag -> Eff eLoop ()) -> ServerId tag -> CallbacksEff tag eLoop q
- onEventEff :: (HasCallStack, TangibleCallbacks tag eLoop q, Server (Server tag eLoop q) (Processes q), FilteredLogging q) => (forall a. Eff eLoop a -> Eff (Processes q) a) -> (Event tag -> Eff eLoop ()) -> ServerId (tag :: Type) -> CallbacksEff tag eLoop q
Documentation
start :: forall (tag :: Type) eLoop q e. (HasCallStack, TangibleCallbacks tag eLoop q, Server (Server tag eLoop q) (Processes q), FilteredLogging (Processes q), HasProcesses e q) => CallbacksEff tag eLoop q -> Eff e (Endpoint tag) Source #
Execute the server loop, that dispatches incoming events
to either a set of Callbacks or CallbacksEff.
Since: 0.29.1
startLink :: forall (tag :: Type) eLoop q e. (HasCallStack, TangibleCallbacks tag eLoop q, Server (Server tag eLoop q) (Processes q), FilteredLogging (Processes q), HasProcesses e q) => CallbacksEff tag eLoop q -> Eff e (Endpoint tag) Source #
Execute the server loop, that dispatches incoming events
to either a set of Callbacks or CallbacksEff.
Since: 0.29.1
data Server tag eLoop e Source #
Phantom type to indicate a callback based Server instance.
Since: 0.27.0
Instances
newtype ServerId (tag :: Type) Source #
The name/id of a Server for logging purposes.
Since: 0.24.0
Constructors
| MkServerId | |
Fields | |
Instances
| Eq (ServerId tag) Source # | |
| Ord (ServerId tag) Source # | |
| Typeable tag => Show (ServerId tag) Source # | |
| IsString (ServerId tag) Source # | |
Defined in Control.Eff.Concurrent.Protocol.CallbackServer Methods fromString :: String -> ServerId tag # | |
| NFData (ServerId tag) Source # | |
This event sum-type is used to communicate incoming messages and other events to the
instances of Server.
Since: 0.24.0
Constructors
| OnCall :: forall a r. (Tangible r, TangiblePdu a (Synchronous r)) => ReplyTarget a r -> Pdu a (Synchronous r) -> Event a | A Since: 0.24.1 |
| OnCast :: forall a. TangiblePdu a Asynchronous => Pdu a Asynchronous -> Event a | |
| OnInterrupt :: Interrupt Recoverable -> Event a | |
| OnDown :: ProcessDown -> Event a | |
| OnTimeOut :: TimerElapsed -> Event a | |
| OnMessage :: StrictDynamic -> Event a |
type TangibleCallbacks tag eLoop e = (HasProcesses eLoop e, Typeable e, Typeable eLoop, Typeable tag) Source #
The constraints for a tangible Server instance.
Since: 0.27.0
type Callbacks tag e = CallbacksEff tag (Processes e) e Source #
A convenience type alias for callbacks that do not need a custom effect.
Since: 0.29.1
callbacks :: forall tag q. (HasCallStack, TangibleCallbacks tag (Processes q) q, Server (Server tag (Processes q) q) (Processes q), FilteredLogging q) => (Endpoint tag -> Event tag -> Eff (Processes q) ()) -> ServerId tag -> Callbacks tag q Source #
A smart constructor for Callbacks.
Since: 0.29.1
onEvent :: forall tag q. (HasCallStack, TangibleCallbacks tag (Processes q) q, Server (Server tag (Processes q) q) (Processes q), FilteredLogging q) => (Event tag -> Eff (Processes q) ()) -> ServerId (tag :: Type) -> Callbacks tag q Source #
A simple smart constructor for Callbacks.
Since: 0.29.1
type CallbacksEff tag eLoop e = Init (Server tag eLoop e) Source #
callbacksEff :: forall tag eLoop q. (HasCallStack, TangibleCallbacks tag eLoop q, Server (Server tag eLoop q) (Processes q), FilteredLogging q) => (forall x. Endpoint tag -> Eff eLoop x -> Eff (Processes q) x) -> (Endpoint tag -> Event tag -> Eff eLoop ()) -> ServerId tag -> CallbacksEff tag eLoop q Source #
A smart constructor for CallbacksEff.
Since: 0.29.1
onEventEff :: (HasCallStack, TangibleCallbacks tag eLoop q, Server (Server tag eLoop q) (Processes q), FilteredLogging q) => (forall a. Eff eLoop a -> Eff (Processes q) a) -> (Event tag -> Eff eLoop ()) -> ServerId (tag :: Type) -> CallbacksEff tag eLoop q Source #
A simple smart constructor for CallbacksEff.
Since: 0.29.1