| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Hercules.Agent.Producer
Synopsis
- data Producer p r = Producer {- producerQueueRead :: STM (Msg p r)
- producerThread :: ThreadId
 
- data ProducerCancelled = ProducerCancelled
- data Msg p r- = Payload p
- | Exception SomeException
- | Close r
 
- forkProducer :: forall m p r. MonadUnliftIO m => ((p -> m ()) -> m r) -> m (Producer p r)
- cancel :: MonadIO m => Producer p r -> m ()
- withProducer :: MonadUnliftIO m => ((p -> m ()) -> m r) -> (Producer p r -> m a) -> m a
- listen :: MonadIO m => Producer p r -> (p -> m a) -> (r -> m a) -> STM (m a)
- joinSTM :: MonadIO m => STM (m a) -> m a
- data Syncing a- = Syncable a
- | Syncer (Maybe SomeException -> STM ())
 
- withSync :: (MonadUnliftIO m, Traversable t) => t (Syncing a) -> (t (Maybe a) -> m b) -> m b
- withBoundedDelayBatchProducer :: MonadUnliftIO m => Int -> Int -> Producer p r -> (Producer [p] r -> m a) -> m a
- syncer :: MonadIO m => (Syncing a -> m ()) -> m ()
Documentation
A thread producing zero or more payloads and a final value. Handles exception propagation.
Constructors
| Producer | |
| Fields 
 | |
data ProducerCancelled Source #
Constructors
| ProducerCancelled | 
Instances
| Exception ProducerCancelled Source # | |
| Defined in Hercules.Agent.Producer Methods toException :: ProducerCancelled -> SomeException # | |
| Show ProducerCancelled Source # | |
| Defined in Hercules.Agent.Producer Methods showsPrec :: Int -> ProducerCancelled -> ShowS # show :: ProducerCancelled -> String # showList :: [ProducerCancelled] -> ShowS # | |
Constructors
| Payload p | One of possibly many payloads from the producer | 
| Exception SomeException | The producer stopped due to an exception | 
| Close r | The producer was done and produced a final value | 
forkProducer :: forall m p r. MonadUnliftIO m => ((p -> m ()) -> m r) -> m (Producer p r) Source #
forkProducer f produces a computation that forks a thread for f, which
 receives a function for returning payloads p.
f may produce a final result value r when it is done.
cancel :: MonadIO m => Producer p r -> m () Source #
Throws ProducerCancelled as an async exception to the producer thread.
 Blocks until exception is raised. See throwTo.
withProducer :: MonadUnliftIO m => ((p -> m ()) -> m r) -> (Producer p r -> m a) -> m a Source #
Perform an computation while withProducer takes care of forking and cleaning up.
withProducer (write -> write "a" >> write "b") $ producer -> consume producer
withSync :: (MonadUnliftIO m, Traversable t) => t (Syncing a) -> (t (Maybe a) -> m b) -> m b Source #
Sends sync notifications after the whole computation succeeds (or fails) Note: not exception safe in the presence of pure exceptions.
withBoundedDelayBatchProducer Source #
Arguments
| :: MonadUnliftIO m | |
| => Int | Max time before flushing in microseconds | 
| -> Int | Max number of items in batch | 
| -> Producer p r | |
| -> (Producer [p] r -> m a) | |
| -> m a |