| Copyright | (C) 2014-2018 Merijn Verstraaten |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Merijn Verstraaten <merijn@inconsistent.nl> |
| Stability | experimental |
| Portability | haha |
| Safe Haskell | Safe |
| Language | Haskell2010 |
BroadcastChan.Conduit
Description
This module is identical to BroadcastChan, but replaces the parallel processing operations with functions for creating conduits and sinks that process in parallel.
Synopsis
- data Action
- data Handler (m :: Type -> Type) a
- = Simple Action
- | Handle (a -> SomeException -> m Action)
- parMapM :: (MonadResource m, MonadUnliftIO m) => Handler m a -> Int -> (a -> m b) -> ConduitM a b m ()
- parMapM_ :: (MonadResource m, MonadUnliftIO m) => Handler m a -> Int -> (a -> m ()) -> ConduitM a Void m ()
- data BroadcastChan (dir :: Direction) a
- data Direction
- type In = In
- type Out = Out
- newBroadcastChan :: MonadIO m => m (BroadcastChan In a)
- newBChanListener :: MonadIO m => BroadcastChan dir a -> m (BroadcastChan Out a)
- closeBChan :: MonadIO m => BroadcastChan In a -> m Bool
- isClosedBChan :: MonadIO m => BroadcastChan dir a -> m Bool
- getBChanContents :: BroadcastChan dir a -> IO [a]
- foldBChan :: (MonadIO m, MonadIO n) => (x -> a -> x) -> x -> (x -> b) -> BroadcastChan d a -> n (m b)
- foldBChanM :: (MonadIO m, MonadIO n) => (x -> a -> m x) -> m x -> (x -> m b) -> BroadcastChan d a -> n (m b)
Documentation
Action to take when an exception occurs while processing an element.
Arguments
| :: (MonadResource m, MonadUnliftIO m) | |
| => Handler m a | Exception handler |
| -> Int | Number of parallel threads to use |
| -> (a -> m b) | Function to run in parallel |
| -> ConduitM a b m () |
Create a conduit that processes inputs in parallel.
This function does NOT guarantee that input elements are processed or output in a deterministic order!
Arguments
| :: (MonadResource m, MonadUnliftIO m) | |
| => Handler m a | Exception handler |
| -> Int | Number of parallel threads to use |
| -> (a -> m ()) | Function to run in parallel |
| -> ConduitM a Void m () |
Create a conduit sink that consumes inputs in parallel.
This function does NOT guarantee that input elements are processed or output in a deterministic order!
Re-exports from BroadcastChan
Datatypes
data BroadcastChan (dir :: Direction) a #
The abstract type representing the read or write end of a BroadcastChan.
Instances
| Eq (BroadcastChan dir a) | |
Defined in BroadcastChan.Internal Methods (==) :: BroadcastChan dir a -> BroadcastChan dir a -> Bool # (/=) :: BroadcastChan dir a -> BroadcastChan dir a -> Bool # | |
Used with DataKinds as phantom type indicating whether a BroadcastChan
value is a read or write end.
Constructors
| In | Indicates a write |
| Out | Indicates a read |
Alias for the Direction type from the Direction kind, allows users to write
the type without enabling BroadcastChan Direction aDataKinds.
Alias for the Direction type from the Direction kind, allows users to write
the type without enabling BroadcastChan Direction aDataKinds.
Construction
newBroadcastChan :: MonadIO m => m (BroadcastChan In a) #
Creates a new BroadcastChan write end.
newBChanListener :: MonadIO m => BroadcastChan dir a -> m (BroadcastChan Out a) #
Create a new read end for a BroadcastChan.
BroadcastChanDirection:Will receive all messages written to the channel after this read end is created.
BroadcastChanDirection:Will receive all currently unread messages and all future messages.
Basic Operations
closeBChan :: MonadIO m => BroadcastChan In a -> m Bool #
Close a BroadcastChan, disallowing further writes. Returns True if the
BroadcastChan was closed. Returns False if the BroadcastChan was
already closed.
isClosedBChan :: MonadIO m => BroadcastChan dir a -> m Bool #
Check whether a BroadcastChan is closed. True meaning that future
read/write operations on the channel will always fail.
BroadcastChanDirection:Trueindicates the channel is closed and writes will always fail.Beware of TOC-TOU races: It is possible for a
BroadcastChanto be closed by another thread. If multiple threads use the same channel acloseBChanfrom another thread can result in the channel being closed right afterisClosedBChanreturns.BroadcastChanDirection:Trueindicates the channel is both closed and empty, meaning reads will always fail.
getBChanContents :: BroadcastChan dir a -> IO [a] #
Return a lazy list representing the messages written to the channel.
Uses unsafeInterleaveIO to defer the IO operations.
BroadcastChanDirection:The list contains every message written to the channel after this
IOaction completes.BroadcastChanDirection:The list contains every currently unread message and all future messages. It's safe to keep using the original channel in any thread.
Unlike
getChanContentsfrom Control.Concurrent, the list resulting from this function is not affected by reads on the input channel. Every message that is unread or written after theIOaction completes will end up in the result list.
Foldl combinators
Combinators for use with Tekmo's foldl package.
foldBChan :: (MonadIO m, MonadIO n) => (x -> a -> x) -> x -> (x -> b) -> BroadcastChan d a -> n (m b) #
Strict fold of the BroadcastChan's messages. Can be used with
Control.Foldl from Tekmo's foldl package:
Control.Foldl.purelyfoldBChan:: (MonadIOm,MonadIOn) =>Folda b ->BroadcastChand a -> n (m b)
The result of this function is a nested monadic value to give more fine-grained control/separation between the start of listening for messages and the start of processing. The inner action folds the actual messages and completes when the channel is closed and exhausted. The outer action controls from when on messages are received. Specifically:
BroadcastChanDirection:Will process all messages sent after the outer action completes.
BroadcastChanDirection:Will process all messages that are unread when the outer action completes, as well as all future messages.
After the outer action completes the fold is unaffected by other (concurrent) reads performed on the original channel. So it's safe to reuse the channel.
foldBChanM :: (MonadIO m, MonadIO n) => (x -> a -> m x) -> m x -> (x -> m b) -> BroadcastChan d a -> n (m b) #
Strict, monadic fold of the BroadcastChan's messages. Can be used with
Control.Foldl from Tekmo's foldl package:
Control.Foldl.impurelyfoldBChanM:: (MonadIOm,MonadIOn) =>FoldMm a b ->BroadcastChand a -> n (m b)
Has the same behaviour and guarantees as foldBChan.