polysemy-conc-0.12.1.0: Polysemy effects for concurrency
Safe HaskellSafe-Inferred
LanguageHaskell2010

Polysemy.Conc.Events

Description

 
Synopsis

Documentation

subscribeGated :: forall e r. Members [EventConsumer e, Gate] r => InterpreterFor (Consume e) r Source #

Create a new scope for Events, causing the nested program to get its own copy of the event stream.

Calls signal before running the argument to ensure that subscribe has finished creating a channel, for use with asynchronous execution.

subscribeAsync :: forall e r a. Members [EventConsumer e, Scoped_ Gate, Resource, Race, Async] r => Sem (Consume e ': r) () -> Sem r a -> Sem r a Source #

Create a new scope for Events, causing the nested program to get its own copy of the event stream.

Executes in a new thread, ensuring that the main thread blocks until subscribe has finished creating a channel.

consumeWhile :: 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. 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. Members [EventConsumer e, Gate] 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.

Signals the caller that the channel was successfully subscribed to using the Gate effect.

subscribeWhileAsync :: forall e r 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 :: 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. 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. Members [EventConsumer e, Gate] r => (e -> Sem r ()) -> Sem r () Source #

Pull repeatedly from the Events channel, passing the event to the supplied callback.

Signals the caller that the channel was successfully subscribed to using the Gate effect.

subscribeLoopAsync :: forall e r 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. 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. 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. Member (Consume e) r => (e -> Sem r (Maybe a)) -> Sem r a Source #

Return the first value returned by Consume for which the function produces Just.

subscribeFirstJust :: forall e a r. Member (EventConsumer e) r => (e -> Sem (Consume e ': r) (Maybe a)) -> Sem r a Source #

Return the first value published to the Events channel for which the function produces Just.

consumeElem :: forall e r. Eq e => Member (Consume e) r => e -> Sem r () Source #

Block until the specified value has been returned by Consume.

subscribeElem :: forall e r. Eq e => Member (EventConsumer e) r => e -> Sem r () Source #

Block until the specified value has been published to the Events channel.