Safe Haskell | None |
---|---|
Language | GHC2021 |
Polysemy.Conc.Events
Description
Synopsis
- subscribeGated :: forall e (r :: EffectRow). Members '[EventConsumer e, Gate] r => InterpreterFor (Consume e) r
- subscribeAsync :: forall e (r :: EffectRow) a. Members '[EventConsumer e, Scoped_ Gate, Resource, Race, Async] r => Sem (Consume e ': r) () -> Sem r a -> Sem r a
- consumeWhile :: forall e (r :: EffectRow). Member (Consume e) r => (e -> Sem r Bool) -> Sem r ()
- subscribeWhile :: forall e (r :: EffectRow). Member (EventConsumer e) r => (e -> Sem r Bool) -> Sem r ()
- subscribeWhileGated :: forall e (r :: EffectRow). Members '[EventConsumer e, Gate] r => (e -> Sem r Bool) -> Sem r ()
- subscribeWhileAsync :: forall e (r :: EffectRow) a. Members '[EventConsumer e, Gates, Resource, Race, Async] r => (e -> Sem (Consume e ': r) Bool) -> Sem r a -> Sem r a
- consumeLoop :: forall e (r :: EffectRow). Member (Consume e) r => (e -> Sem r ()) -> Sem r ()
- subscribeLoop :: forall e (r :: EffectRow). Member (EventConsumer e) r => (e -> Sem r ()) -> Sem r ()
- subscribeLoopGated :: forall e (r :: EffectRow). Members '[EventConsumer e, Gate] r => (e -> Sem r ()) -> Sem r ()
- subscribeLoopAsync :: forall e (r :: EffectRow) a. Members '[EventConsumer e, Gates, Resource, Race, Async] r => (e -> Sem (Consume e ': r) ()) -> Sem r a -> Sem r a
- consumeFind :: forall e (r :: EffectRow). Member (Consume e) r => (e -> Sem r Bool) -> Sem r e
- subscribeFind :: forall e (r :: EffectRow). Member (EventConsumer e) r => (e -> Sem (Consume e ': r) Bool) -> Sem r e
- consumeFirstJust :: forall e a (r :: EffectRow). Member (Consume e) r => (e -> Sem r (Maybe a)) -> Sem r a
- subscribeFirstJust :: forall e a (r :: EffectRow). Member (EventConsumer e) r => (e -> Sem (Consume e ': r) (Maybe a)) -> Sem r a
- consumeElem :: forall e (r :: EffectRow). (Eq e, Member (Consume e) r) => e -> Sem r ()
- subscribeElem :: forall e (r :: EffectRow). (Eq e, Member (EventConsumer e) r) => e -> Sem r ()
Documentation
subscribeGated :: forall e (r :: EffectRow). Members '[EventConsumer e, Gate] r => InterpreterFor (Consume e) r Source #
subscribeAsync :: forall e (r :: EffectRow) a. Members '[EventConsumer e, Scoped_ Gate, Resource, Race, Async] r => Sem (Consume e ': r) () -> Sem r a -> Sem r a Source #
consumeWhile :: forall e (r :: EffectRow). Member (Consume e) r => (e -> Sem r Bool) -> Sem r () Source #
Pull repeatedly from Consume
, passing the event to the supplied callback.
Stop when the action returns False
.
subscribeWhile :: forall e (r :: EffectRow). Member (EventConsumer e) r => (e -> Sem r Bool) -> Sem r () Source #
Pull repeatedly from the Events
channel, passing the event to the supplied callback.
Stop when the action returns False
.
subscribeWhileGated :: forall e (r :: EffectRow). Members '[EventConsumer e, Gate] r => (e -> Sem r Bool) -> Sem r () Source #
subscribeWhileAsync :: forall e (r :: EffectRow) a. Members '[EventConsumer e, Gates, Resource, Race, Async] r => (e -> Sem (Consume e ': r) Bool) -> Sem r a -> Sem r a Source #
Start a new thread that pulls repeatedly from the Events
channel, passing the event to the supplied
callback and stops when the action returns False
.
consumeLoop :: forall e (r :: EffectRow). Member (Consume e) r => (e -> Sem r ()) -> Sem r () Source #
Pull repeatedly from Consume
, passing the event to the supplied callback.
subscribeLoop :: forall e (r :: EffectRow). Member (EventConsumer e) r => (e -> Sem r ()) -> Sem r () Source #
Pull repeatedly from the Events
channel, passing the event to the supplied callback.
subscribeLoopGated :: forall e (r :: EffectRow). Members '[EventConsumer e, Gate] r => (e -> Sem r ()) -> Sem r () Source #
subscribeLoopAsync :: forall e (r :: EffectRow) a. Members '[EventConsumer e, Gates, Resource, Race, Async] r => (e -> Sem (Consume e ': r) ()) -> Sem r a -> Sem r a Source #
Start a new thread that pulls repeatedly from the Events
channel, passing the event to the supplied
callback.
consumeFind :: forall e (r :: EffectRow). Member (Consume e) r => (e -> Sem r Bool) -> Sem r e Source #
Block until a value matching the predicate has been returned by Consume
.
subscribeFind :: forall e (r :: EffectRow). Member (EventConsumer e) r => (e -> Sem (Consume e ': r) Bool) -> Sem r e Source #
Block until a value matching the predicate has been published to the Events
channel.
consumeFirstJust :: forall e a (r :: EffectRow). Member (Consume e) r => (e -> Sem r (Maybe a)) -> Sem r a Source #
subscribeFirstJust :: forall e a (r :: EffectRow). Member (EventConsumer e) r => (e -> Sem (Consume e ': r) (Maybe a)) -> Sem r a Source #
consumeElem :: forall e (r :: EffectRow). (Eq e, Member (Consume e) r) => e -> Sem r () Source #
Block until the specified value has been returned by Consume
.
subscribeElem :: forall e (r :: EffectRow). (Eq e, Member (EventConsumer e) r) => e -> Sem r () Source #
Block until the specified value has been published to the Events
channel.