Safe Haskell | None |
---|---|
Language | Haskell98 |
- Introduction
Contain combinators for concurrently joining conduits, such that the producing side may continue to produce (up to the queue size) as the consumer is concurrently consuming.
- data CConduit i o m r
- data CFConduit i o m r
- ($=&) :: CCatable c1 c2 c3 => c1 i x m () -> c2 x o m r -> c3 i o m r
- (=$&) :: CCatable c1 c2 c3 => c1 i x m () -> c2 x o m r -> c3 i o m r
- (=$=&) :: CCatable c1 c2 c3 => c1 i x m () -> c2 x o m r -> c3 i o m r
- ($$&) :: (CCatable c1 c2 c3, CRunnable c3, RunConstraints c3 m) => c1 () x m () -> c2 x Void m r -> m r
- buffer :: (CCatable c1 c2 c3, CRunnable c3, RunConstraints c3 m) => Int -> c1 () x m () -> c2 x Void m r -> m r
- buffer' :: CCatable c1 c2 c3 => Int -> c1 i x m () -> c2 x o m r -> c3 i o m r
- bufferToFile :: (CFConduitLike c1, CFConduitLike c2, Serialize x, MonadUnliftIO m, MonadResource m, MonadThrow m) => Int -> Maybe Int -> FilePath -> c1 () x m () -> c2 x Void m r -> m r
- bufferToFile' :: (CFConduitLike c1, CFConduitLike c2, Serialize x) => Int -> Maybe Int -> FilePath -> c1 i x m () -> c2 x o m r -> CFConduit i o m r
- runCConduit :: (CRunnable c, RunConstraints c m) => c () Void m r -> m r
- gatherFrom :: (MonadIO m, MonadUnliftIO m) => Int -> (TBQueue o -> m ()) -> ConduitT () o m ()
- drainTo :: (MonadIO m, MonadUnliftIO m) => Int -> (TBQueue (Maybe i) -> m r) -> ConduitT i Void m r
Documentation
data CConduit i o m r Source #
A "concurrent conduit", in which the stages run in parallel with a buffering queue between them.
data CFConduit i o m r Source #
A "concurrent conduit", in which the stages run in parallel with a buffering queue and possibly a disk file between them.
(=$=&) :: CCatable c1 c2 c3 => c1 i x m () -> c2 x o m r -> c3 i o m r infixr 2 Source #
An operator form of buffer'
. In general you should be able to replace
any use of =$=
with =$=&
and $$
either with $$&
or =$=
and runCConduit
and suddenly reap the benefit of concurrency, if
your conduits were spending time waiting on each other.
>>>
runCConduit $ CL.sourceList [1,2,3] =$=& CL.consume
[1,2,3]
($$&) :: (CCatable c1 c2 c3, CRunnable c3, RunConstraints c3 m) => c1 () x m () -> c2 x Void m r -> m r infixr 0 Source #
An operator form of buffer
. In general you should be able to replace
any use of $$
with $$&
and suddenly reap the benefit of
concurrency, if your conduits were spending time waiting on each other.
The underlying monad must always be an instance of
'MonadBaseControl IO'. If at least one of the two conduits is a
CFConduit
, it must additionally be a in instance of
MonadResource
.
>>>
CL.sourceList [1,2,3] $$& CL.consume
[1,2,3]
It can be combined with $=&
and $=
. This creates two threads;
the first thread produces the list and the second thread does the
map and the consume:
>>>
CL.sourceList [1,2,3] $$& mapC (*2) $= CL.consume
[2,4,6]
This creates three threads. The three conduits all run in their own threads:
>>>
CL.sourceList [1,2,3] $$& mapC (*2) $=& CL.consume
[2,4,6]
>>>
CL.sourceList [1,2,3] $$& (mapC (*2) $= mapC (+1)) $=& CL.consume
[3,5,7]
:: (CCatable c1 c2 c3, CRunnable c3, RunConstraints c3 m) | |
=> Int | Size of the bounded queue in memory. |
-> c1 () x m () | |
-> c2 x Void m r | |
-> m r |
Concurrently join the producer and consumer, using a bounded queue of the given size. The producer will block when the queue is full, if it is producing faster than the consumers is taking from it. Likewise, if the consumer races ahead, it will block until more input is available.
Exceptions are properly managed and propagated between the two sides, so the net effect should be equivalent to not using buffer at all, save for the concurrent interleaving of effects.
The underlying monad must always be an instance of
'MonadBaseControl IO'. If at least one of the two conduits is a
CFConduit
, it must additionally be a in instance of
MonadResource
.
This function is similar to $$
; for one more like =$=
, see
buffer'
.
>>>
buffer 1 (CL.sourceList [1,2,3]) CL.consume
[1,2,3]
:: CCatable c1 c2 c3 | |
=> Int | Size of the bounded queue in memory |
-> c1 i x m () | |
-> c2 x o m r | |
-> c3 i o m r |
Concurrently join the producer and consumer, using a bounded queue of the given size. The producer will block when the queue is full, if it is producing faster than the consumers is taking from it. Likewise, if the consumer races ahead, it will block until more input is available.
Exceptions are properly managed and propagated between the two sides, so the net effect should be equivalent to not using buffer at all, save for the concurrent interleaving of effects.
This function is similar to =$=
; for one more like $$
, see
buffer
.
>>>
runCConduit $ buffer' 1 (CL.sourceList [1,2,3]) CL.consume
[1,2,3]
:: (CFConduitLike c1, CFConduitLike c2, Serialize x, MonadUnliftIO m, MonadResource m, MonadThrow m) | |
=> Int | Size of the bounded queue in memory |
-> Maybe Int | Max elements to keep on disk at one time |
-> FilePath | Directory to write temp files to |
-> c1 () x m () | |
-> c2 x Void m r | |
-> m r |
Like buffer
, except that when the bounded queue is overflowed, the
excess is cached in a local file so that consumption from upstream may
continue. When the queue becomes exhausted by yielding, it is filled
from the cache until all elements have been yielded.
Note that the maximum amount of memory consumed is equal to (2 * memorySize + 1), so take this into account when picking a chunking size.
This function is similar to $$
; for one more like =$=
, see
bufferToFile'
.
>>>
runResourceT $ bufferToFile 1 Nothing "/tmp" (CL.sourceList [1,2,3]) CL.consume
[1,2,3]
:: (CFConduitLike c1, CFConduitLike c2, Serialize x) | |
=> Int | Size of the bounded queue in memory |
-> Maybe Int | Max elements to keep on disk at one time |
-> FilePath | Directory to write temp files to |
-> c1 i x m () | |
-> c2 x o m r | |
-> CFConduit i o m r |
Like buffer'
, except that when the bounded queue is overflowed, the
excess is cached in a local file so that consumption from upstream may
continue. When the queue becomes exhausted by yielding, it is filled
from the cache until all elements have been yielded.
Note that the maximum amount of memory consumed is equal to (2 * memorySize + 1), so take this into account when picking a chunking size.
This function is similar to =$=
; for one more like $$
, see
bufferToFile
.
>>>
runResourceT $ runCConduit $ bufferToFile' 1 Nothing "/tmp" (CL.sourceList [1,2,3]) CL.consume
[1,2,3]
It is frequently convenient to define local function to use this in operator form:
>>>
:{
runResourceT $ do let buf c = bufferToFile' 10 Nothing "/tmp" c -- eta-conversion to avoid monomorphism restriction runCConduit $ CL.sourceList [0x30, 0x31, 0x32] `buf` mapC (toEnum :: Int -> Char) `buf` CL.consume :} "012"
runCConduit :: (CRunnable c, RunConstraints c m) => c () Void m r -> m r Source #
Execute a conduit concurrently. This is the concurrent
equivalent of runConduit
.
The underlying monad must always be an instance of
MonadUnliftIO
. If the conduits is a CFConduit
, it must
additionally be a in instance of MonadResource
.
:: (MonadIO m, MonadUnliftIO m) | |
=> Int | Size of the queue to create |
-> (TBQueue o -> m ()) | Action that generates output values |
-> ConduitT () o m () |
Gather output values asynchronously from an action in the base monad and
then yield them downstream. This provides a means of working around the
restriction that ConduitM
cannot be an instance of MonadBaseControl
in order to, for example, yield values from within a Haskell callback
function called from a C library.