Safe Haskell | Safe |
---|---|
Language | Haskell98 |
- data Pipe l i o u m r
- await :: Pipe l i o u m (Maybe i)
- awaitE :: Pipe l i o u m (Either u i)
- awaitForever :: Monad m => (i -> Pipe l i o r m r') -> Pipe l i o r m r
- yield :: Monad m => o -> Pipe l i o u m ()
- yieldM :: Monad m => m o -> Pipe l i o u m ()
- yieldOr :: Monad m => o -> m () -> Pipe l i o u m ()
- leftover :: l -> Pipe l i o u m ()
- bracketP :: MonadResource m => IO a -> (a -> IO ()) -> (a -> Pipe l i o u m r) -> Pipe l i o u m r
- addCleanup :: Monad m => (Bool -> m ()) -> Pipe l i o u m r -> Pipe l i o u m r
- idP :: Monad m => Pipe l a a r m r
- pipe :: Monad m => Pipe l a b r0 m r1 -> Pipe Void b c r1 m r2 -> Pipe l a c r0 m r2
- pipeL :: Monad m => Pipe l a b r0 m r1 -> Pipe b b c r1 m r2 -> Pipe l a c r0 m r2
- runPipe :: Monad m => Pipe Void () Void () m r -> m r
- injectLeftovers :: Monad m => Pipe i i o u m r -> Pipe l i o u m r
- (>+>) :: Monad m => Pipe l a b r0 m r1 -> Pipe Void b c r1 m r2 -> Pipe l a c r0 m r2
- (<+<) :: Monad m => Pipe Void b c r1 m r2 -> Pipe l a b r0 m r1 -> Pipe l a c r0 m r2
- catchP :: (MonadBaseControl IO m, Exception e) => Pipe l i o u m r -> (e -> Pipe l i o u m r) -> Pipe l i o u m r
- handleP :: (MonadBaseControl IO m, Exception e) => (e -> Pipe l i o u m r) -> Pipe l i o u m r -> Pipe l i o u m r
- tryP :: (MonadBaseControl IO m, Exception e) => Pipe l i o u m r -> Pipe l i o u m (Either e r)
- transPipe :: Monad m => (forall a. m a -> n a) -> Pipe l i o u m r -> Pipe l i o u n r
- mapOutput :: Monad m => (o1 -> o2) -> Pipe l i o1 u m r -> Pipe l i o2 u m r
- mapOutputMaybe :: Monad m => (o1 -> Maybe o2) -> Pipe l i o1 u m r -> Pipe l i o2 u m r
- mapInput :: Monad m => (i1 -> i2) -> (l2 -> Maybe l1) -> Pipe l2 i2 o u m r -> Pipe l1 i1 o u m r
- sourceList :: Monad m => [a] -> Pipe l i a u m ()
- withUpstream :: Monad m => Pipe l i o u m r -> Pipe l i o u m (u, r)
- enumFromTo :: (Enum o, Eq o, Monad m) => o -> o -> Pipe l i o u m ()
- generalizeUpstream :: Monad m => Pipe l i o () m r -> Pipe l i o u m r
- newtype ConduitM i o m r = ConduitM {
- unConduitM :: forall b. (r -> Pipe i i o () m b) -> Pipe i i o () m b
- type Source m o = ConduitM () o m ()
- type Producer m o = forall i. ConduitM i o m ()
- type Sink i = ConduitM i Void
- type Consumer i m r = forall o. ConduitM i o m r
- type Conduit i m o = ConduitM i o m ()
- data ResumableSource m o = ResumableSource (Pipe () () o () m ()) (m ())
- data ResumableConduit i m o = ResumableConduit (Pipe i i o () m ()) (m ())
- data Flush a
- newtype ZipSource m o = ZipSource {
- getZipSource :: Source m o
- newtype ZipSink i m r = ZipSink {
- getZipSink :: Sink i m r
- newtype ZipConduit i o m r = ZipConduit {
- getZipConduit :: ConduitM i o m r
- await :: Monad m => Consumer i m (Maybe i)
- awaitForever :: Monad m => (i -> ConduitM i o m r) -> ConduitM i o m ()
- yield :: Monad m => o -> ConduitM i o m ()
- yieldM :: Monad m => m o -> ConduitM i o m ()
- yieldOr :: Monad m => o -> m () -> ConduitM i o m ()
- leftover :: i -> ConduitM i o m ()
- runConduit :: Monad m => ConduitM () Void m r -> m r
- connectResume :: Monad m => ResumableSource m o -> Sink o m r -> m (ResumableSource m o, r)
- connectResumeConduit :: Monad m => ResumableConduit i m o -> Sink o m r -> Sink i m (ResumableConduit i m o, r)
- fuseLeftovers :: Monad m => ([b] -> [a]) -> ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
- fuseReturnLeftovers :: Monad m => ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m (r, [b])
- ($$+) :: Monad m => Source m a -> Sink a m b -> m (ResumableSource m a, b)
- ($$++) :: Monad m => ResumableSource m a -> Sink a m b -> m (ResumableSource m a, b)
- ($$+-) :: Monad m => ResumableSource m a -> Sink a m b -> m b
- ($=+) :: Monad m => ResumableSource m a -> Conduit a m b -> ResumableSource m b
- (=$$+) :: Monad m => Conduit a m b -> Sink b m r -> Sink a m (ResumableConduit a m b, r)
- (=$$++) :: Monad m => ResumableConduit i m o -> Sink o m r -> Sink i m (ResumableConduit i m o, r)
- (=$$+-) :: Monad m => ResumableConduit i m o -> Sink o m r -> Sink i m r
- ($$) :: Monad m => Source m a -> Sink a m b -> m b
- ($=) :: Monad m => Conduit a m b -> ConduitM b c m r -> ConduitM a c m r
- (=$) :: Monad m => Conduit a m b -> ConduitM b c m r -> ConduitM a c m r
- (=$=) :: Monad m => Conduit a m b -> ConduitM b c m r -> ConduitM a c m r
- sourceToPipe :: Monad m => Source m o -> Pipe l i o u m ()
- sinkToPipe :: Monad m => Sink i m r -> Pipe l i o u m r
- conduitToPipe :: Monad m => Conduit i m o -> Pipe l i o u m ()
- toProducer :: Monad m => Source m a -> Producer m a
- toConsumer :: Monad m => Sink a m b -> Consumer a m b
- bracketP :: MonadResource m => IO a -> (a -> IO ()) -> (a -> ConduitM i o m r) -> ConduitM i o m r
- addCleanup :: Monad m => (Bool -> m ()) -> ConduitM i o m r -> ConduitM i o m r
- catchC :: (MonadBaseControl IO m, Exception e) => ConduitM i o m r -> (e -> ConduitM i o m r) -> ConduitM i o m r
- handleC :: (MonadBaseControl IO m, Exception e) => (e -> ConduitM i o m r) -> ConduitM i o m r -> ConduitM i o m r
- tryC :: (MonadBaseControl IO m, Exception e) => ConduitM i o m r -> ConduitM i o m (Either e r)
- transPipe :: Monad m => (forall a. m a -> n a) -> ConduitM i o m r -> ConduitM i o n r
- mapOutput :: Monad m => (o1 -> o2) -> ConduitM i o1 m r -> ConduitM i o2 m r
- mapOutputMaybe :: Monad m => (o1 -> Maybe o2) -> ConduitM i o1 m r -> ConduitM i o2 m r
- mapInput :: Monad m => (i1 -> i2) -> (i2 -> Maybe i1) -> ConduitM i2 o m r -> ConduitM i1 o m r
- closeResumableSource :: Monad m => ResumableSource m a -> m ()
- unwrapResumable :: MonadIO m => ResumableSource m o -> m (Source m o, m ())
- unwrapResumableConduit :: MonadIO m => ResumableConduit i m o -> m (Conduit i m o, m ())
- newResumableSource :: Monad m => Source m o -> ResumableSource m o
- newResumableConduit :: Monad m => Conduit i m o -> ResumableConduit i m o
- zipSinks :: Monad m => Sink i m r -> Sink i m r' -> Sink i m (r, r')
- zipSources :: Monad m => Source m a -> Source m b -> Source m (a, b)
- zipSourcesApp :: Monad m => Source m (a -> b) -> Source m a -> Source m b
- zipConduitApp :: Monad m => ConduitM i o m (x -> y) -> ConduitM i o m x -> ConduitM i o m y
- mergeSource :: Monad m => Source m i -> Conduit a m (i, a)
- passthroughSink :: Monad m => Sink i m r -> (r -> m ()) -> Conduit i m i
- sourceToList :: Monad m => Source m a -> m [a]
- fuseBoth :: Monad m => ConduitM a b m r1 -> ConduitM b c m r2 -> ConduitM a c m (r1, r2)
- fuseBothMaybe :: Monad m => ConduitM a b m r1 -> ConduitM b c m r2 -> ConduitM a c m (Maybe r1, r2)
- fuseUpstream :: Monad m => ConduitM a b m r -> Conduit b m c -> ConduitM a c m r
- sequenceSources :: (Traversable f, Monad m) => f (Source m o) -> Source m (f o)
- sequenceSinks :: (Traversable f, Monad m) => f (Sink i m r) -> Sink i m (f r)
- sequenceConduits :: (Traversable f, Monad m) => f (ConduitM i o m r) -> ConduitM i o m (f r)
- module Data.Conduit.Internal.Fusion
Pipe
Types
The underlying datatype for all the types in this package. In has six type parameters:
- l is the type of values that may be left over from this
Pipe
. APipe
with no leftovers would useVoid
here, and one with leftovers would use the same type as the i parameter. Leftovers are automatically provided to the nextPipe
in the monadic chain. - i is the type of values for this
Pipe
's input stream. - o is the type of values for this
Pipe
's output stream. - u is the result type from the upstream
Pipe
. - m is the underlying monad.
- r is the result type.
A basic intuition is that every Pipe
produces a stream of output values
(o), and eventually indicates that this stream is terminated by sending a
result (r). On the receiving end of a Pipe
, these become the i and u
parameters.
Since 0.5.0
HaveOutput (Pipe l i o u m r) (m ()) o | Provide new output to be sent downstream. This constructor has three
fields: the next |
NeedInput (i -> Pipe l i o u m r) (u -> Pipe l i o u m r) | Request more input from upstream. The first field takes a new input
value and provides a new |
Done r | Processing with this |
PipeM (m (Pipe l i o u m r)) | Require running of a monadic action to get the next |
Leftover (Pipe l i o u m r) l | Return leftover input, which should be provided to future operations. |
MonadRWS r w s m => MonadRWS r w s (Pipe l i o u m) Source | |
MonadBase base m => MonadBase base (Pipe l i o u m) Source | |
MonadError e m => MonadError e (Pipe l i o u m) Source | |
MonadReader r m => MonadReader r (Pipe l i o u m) Source | |
MonadState s m => MonadState s (Pipe l i o u m) Source | |
MonadWriter w m => MonadWriter w (Pipe l i o u m) Source | |
MFunctor (Pipe l i o u) Source | Since 1.0.4 |
MonadTrans (Pipe l i o u) Source | |
Monad m => Monad (Pipe l i o u m) Source | |
Monad m => Functor (Pipe l i o u m) Source | |
Monad m => Applicative (Pipe l i o u m) Source | |
MonadThrow m => MonadThrow (Pipe l i o u m) Source | |
MonadCatch m => MonadCatch (Pipe l i o u m) Source | |
MonadIO m => MonadIO (Pipe l i o u m) Source | |
MonadResource m => MonadResource (Pipe l i o u m) Source | |
Monad m => Monoid (Pipe l i o u m ()) Source |
Primitives
awaitE :: Pipe l i o u m (Either u i) Source
This is similar to await
, but will return the upstream result value as
Left
if available.
Since 0.5.0
awaitForever :: Monad m => (i -> Pipe l i o r m r') -> Pipe l i o r m r Source
Wait for input forever, calling the given inner Pipe
for each piece of
new input. Returns the upstream result type.
Since 0.5.0
Send a single output value downstream. If the downstream Pipe
terminates, this Pipe
will terminate as well.
Since 0.5.0
Similar to yield
, but additionally takes a finalizer to be run if the
downstream Pipe
terminates.
Since 0.5.0
leftover :: l -> Pipe l i o u m () Source
Provide a single piece of leftover input to be consumed by the next pipe in the current monadic binding.
Note: it is highly encouraged to only return leftover values from input already consumed from upstream.
Since 0.5.0
Finalization
:: MonadResource m | |
=> IO a | computation to run first ("acquire resource") |
-> (a -> IO ()) | computation to run last ("release resource") |
-> (a -> Pipe l i o u m r) | computation to run in-between |
-> Pipe l i o u m r |
Bracket a pipe computation between allocation and release of a resource. Two guarantees are given about resource finalization:
- It will be prompt. The finalization will be run as early as possible.
- It is exception safe. Due to usage of
resourcet
, the finalization will be run in the event of any exceptions.
Since 0.5.0
:: Monad m | |
=> (Bool -> m ()) |
|
-> Pipe l i o u m r | |
-> Pipe l i o u m r |
Add some code to be run when the given Pipe
cleans up.
Since 0.4.1
Composition
pipe :: Monad m => Pipe l a b r0 m r1 -> Pipe Void b c r1 m r2 -> Pipe l a c r0 m r2 Source
Compose a left and right pipe together into a complete pipe. The left pipe will be automatically closed when the right pipe finishes.
Since 0.5.0
pipeL :: Monad m => Pipe l a b r0 m r1 -> Pipe b b c r1 m r2 -> Pipe l a c r0 m r2 Source
Same as pipe
, but automatically applies injectLeftovers
to the right Pipe
.
Since 0.5.0
runPipe :: Monad m => Pipe Void () Void () m r -> m r Source
Run a pipeline until processing completes.
Since 0.5.0
injectLeftovers :: Monad m => Pipe i i o u m r -> Pipe l i o u m r Source
Transforms a Pipe
that provides leftovers to one which does not,
allowing it to be composed.
This function will provide any leftover values within this Pipe
to any
calls to await
. If there are more leftover values than are demanded, the
remainder are discarded.
Since 0.5.0
(>+>) :: Monad m => Pipe l a b r0 m r1 -> Pipe Void b c r1 m r2 -> Pipe l a c r0 m r2 infixl 9 Source
Fuse together two Pipe
s, connecting the output from the left to the
input of the right.
Notice that the leftover parameter for the Pipe
s must be Void
. This
ensures that there is no accidental data loss of leftovers during fusion. If
you have a Pipe
with leftovers, you must first call injectLeftovers
.
Since 0.5.0
(<+<) :: Monad m => Pipe Void b c r1 m r2 -> Pipe l a b r0 m r1 -> Pipe l a c r0 m r2 infixr 9 Source
Same as >+>
, but reverse the order of the arguments.
Since 0.5.0
Exceptions
catchP :: (MonadBaseControl IO m, Exception e) => Pipe l i o u m r -> (e -> Pipe l i o u m r) -> Pipe l i o u m r Source
See catchC
for more details.
Since 1.0.11
handleP :: (MonadBaseControl IO m, Exception e) => (e -> Pipe l i o u m r) -> Pipe l i o u m r -> Pipe l i o u m r Source
The same as flip catchP
.
Since 1.0.11
tryP :: (MonadBaseControl IO m, Exception e) => Pipe l i o u m r -> Pipe l i o u m (Either e r) Source
See tryC
for more details.
Since 1.0.11
Utilities
transPipe :: Monad m => (forall a. m a -> n a) -> Pipe l i o u m r -> Pipe l i o u n r Source
Transform the monad that a Pipe
lives in.
Note that the monad transforming function will be run multiple times, resulting in unintuitive behavior in some cases. For a fuller treatment, please see:
https://github.com/snoyberg/conduit/wiki/Dealing-with-monad-transformers
This function is just a synonym for hoist
.
Since 0.4.0
mapOutput :: Monad m => (o1 -> o2) -> Pipe l i o1 u m r -> Pipe l i o2 u m r Source
Apply a function to all the output values of a Pipe
.
This mimics the behavior of fmap
for a Source
and Conduit
in pre-0.4
days.
Since 0.4.1
mapOutputMaybe :: Monad m => (o1 -> Maybe o2) -> Pipe l i o1 u m r -> Pipe l i o2 u m r Source
Same as mapOutput
, but use a function that returns Maybe
values.
Since 0.5.0
:: Monad m | |
=> (i1 -> i2) | map initial input to new input |
-> (l2 -> Maybe l1) | map new leftovers to initial leftovers |
-> Pipe l2 i2 o u m r | |
-> Pipe l1 i1 o u m r |
Apply a function to all the input values of a Pipe
.
Since 0.5.0
sourceList :: Monad m => [a] -> Pipe l i a u m () Source
Convert a list into a source.
Since 0.3.0
withUpstream :: Monad m => Pipe l i o u m r -> Pipe l i o u m (u, r) Source
Returns a tuple of the upstream and downstream results. Note that this will force consumption of the entire input stream.
Since 0.5.0
generalizeUpstream :: Monad m => Pipe l i o () m r -> Pipe l i o u m r Source
Generalize the upstream return value for a Pipe
from unit to any type.
Since 1.1.5
Conduit
Types
newtype ConduitM i o m r Source
Core datatype of the conduit package. This type represents a general
component which can consume a stream of input values i
, produce a stream
of output values o
, perform actions in the m
monad, and produce a final
result r
. The type synonyms provided here are simply wrappers around this
type.
Since 1.0.0
ConduitM | |
|
MonadRWS r w s m => MonadRWS r w s (ConduitM i o m) Source | |
MonadBase base m => MonadBase base (ConduitM i o m) Source | |
MonadError e m => MonadError e (ConduitM i o m) Source | |
MonadReader r m => MonadReader r (ConduitM i o m) Source | |
MonadState s m => MonadState s (ConduitM i o m) Source | |
MonadWriter w m => MonadWriter w (ConduitM i o m) Source | |
MFunctor (ConduitM i o) Source | |
MonadTrans (ConduitM i o) Source | |
Monad (ConduitM i o m) Source | |
Functor (ConduitM i o m) Source | |
Applicative (ConduitM i o m) Source | |
MonadThrow m => MonadThrow (ConduitM i o m) Source | |
MonadCatch m => MonadCatch (ConduitM i o m) Source | |
MonadIO m => MonadIO (ConduitM i o m) Source | |
MonadResource m => MonadResource (ConduitM i o m) Source | |
Monad m => Monoid (ConduitM i o m ()) Source |
type Source m o = ConduitM () o m () Source
Provides a stream of output values, without consuming any input or producing a final result.
Since 0.5.0
type Producer m o = forall i. ConduitM i o m () Source
A component which produces a stream of output values, regardless of the
input stream. A Producer
is a generalization of a Source
, and can be
used as either a Source
or a Conduit
.
Since 1.0.0
type Sink i = ConduitM i Void Source
Consumes a stream of input values and produces a final result, without producing any output.
type Sink i m r = ConduitM i Void m r
Since 0.5.0
type Consumer i m r = forall o. ConduitM i o m r Source
A component which consumes a stream of input values and produces a final
result, regardless of the output stream. A Consumer
is a generalization of
a Sink
, and can be used as either a Sink
or a Conduit
.
Since 1.0.0
type Conduit i m o = ConduitM i o m () Source
Consumes a stream of input values and produces a stream of output values, without producing a final result.
Since 0.5.0
data ResumableSource m o Source
A Source
which has been started, but has not yet completed.
This type contains both the current state of the Source
, and the finalizer
to be run to close it.
Since 0.5.0
ResumableSource (Pipe () () o () m ()) (m ()) |
MFunctor ResumableSource Source | Since 1.0.13 |
data ResumableConduit i m o Source
A generalization of ResumableSource
. Allows to resume an arbitrary
conduit, keeping its state and using it later (or finalizing it).
Since 1.0.17
ResumableConduit (Pipe i i o () m ()) (m ()) |
Provide for a stream of data that can be flushed.
A number of Conduit
s (e.g., zlib compression) need the ability to flush
the stream at some point. This provides a single wrapper datatype to be used
in all such circumstances.
Since 0.3.0
Newtype wrappers
A wrapper for defining an Applicative
instance for Source
s which allows
to combine sources together, generalizing zipSources
. A combined source
will take input yielded from each of its Source
s until any of them stop
producing output.
Since 1.0.13
ZipSource | |
|
A wrapper for defining an Applicative
instance for Sink
s which allows
to combine sinks together, generalizing zipSinks
. A combined sink
distributes the input to all its participants and when all finish, produces
the result. This allows to define functions like
sequenceSinks :: (Monad m) => [Sink i m r] -> Sink i m [r] sequenceSinks = getZipSink . sequenceA . fmap ZipSink
Note that the standard Applicative
instance for conduits works
differently. It feeds one sink with input until it finishes, then switches
to another, etc., and at the end combines their results.
This newtype is in fact a type constrained version of ZipConduit
, and has
the same behavior. It's presented as a separate type since (1) it
historically predates ZipConduit
, and (2) the type constraining can make
your code clearer (and thereby make your error messages more easily
understood).
Since 1.0.13
ZipSink | |
|
newtype ZipConduit i o m r Source
Provides an alternative Applicative
instance for ConduitM
. In this instance,
every incoming value is provided to all ConduitM
s, and output is coalesced together.
Leftovers from individual ConduitM
s will be used within that component, and then discarded
at the end of their computation. Output and finalizers will both be handled in a left-biased manner.
As an example, take the following program:
main :: IO () main = do let src = mapM_ yield [1..3 :: Int] conduit1 = CL.map (+1) conduit2 = CL.concatMap (replicate 2) conduit = getZipConduit $ ZipConduit conduit1 <* ZipConduit conduit2 sink = CL.mapM_ print src $$ conduit =$ sink
It will produce the output: 2, 1, 1, 3, 2, 2, 4, 3, 3
Since 1.0.17
ZipConduit | |
|
Functor (ZipConduit i o m) Source | |
Monad m => Applicative (ZipConduit i o m) Source |
Primitives
await :: Monad m => Consumer i m (Maybe i) Source
Wait for a single input value from upstream. If no data is available,
returns Nothing
. Once await
returns Nothing
, subsequent calls will
also return Nothing
.
Since 0.5.0
awaitForever :: Monad m => (i -> ConduitM i o m r) -> ConduitM i o m () Source
Wait for input forever, calling the given inner component for each piece of new input. Returns the upstream result type.
This function is provided as a convenience for the common pattern of
await
ing input, checking if it's Just
and then looping.
Since 0.5.0
Send a value downstream to the next component to consume. If the
downstream component terminates, this call will never return control. If you
would like to register a cleanup function, please use yieldOr
instead.
Since 0.5.0
Similar to yield
, but additionally takes a finalizer to be run if the
downstream component terminates.
Since 0.5.0
leftover :: i -> ConduitM i o m () Source
Provide a single piece of leftover input to be consumed by the next component in the current monadic binding.
Note: it is highly encouraged to only return leftover values from input already consumed from upstream.
Since 0.5.0
runConduit :: Monad m => ConduitM () Void m r -> m r Source
Run a pipeline until processing completes.
Since 1.2.1
Composition
connectResume :: Monad m => ResumableSource m o -> Sink o m r -> m (ResumableSource m o, r) Source
Connect a Source
to a Sink
until the latter closes. Returns both the
most recent state of the Source
and the result of the Sink
.
We use a ResumableSource
to keep track of the most recent finalizer
provided by the Source
.
Since 0.5.0
connectResumeConduit :: Monad m => ResumableConduit i m o -> Sink o m r -> Sink i m (ResumableConduit i m o, r) Source
Connect a ResumableConduit
to a sink and return the output of the sink
together with a new ResumableConduit
.
Since 1.0.17
fuseLeftovers :: Monad m => ([b] -> [a]) -> ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r Source
Similar to fuseReturnLeftovers
, but use the provided function to convert
downstream leftovers to upstream leftovers.
Since 1.0.17
fuseReturnLeftovers :: Monad m => ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m (r, [b]) Source
Same as normal fusion (e.g. =$=
), except instead of discarding leftovers
from the downstream component, return them.
Since 1.0.17
($$+) :: Monad m => Source m a -> Sink a m b -> m (ResumableSource m a, b) infixr 0 Source
The connect-and-resume operator. This does not close the Source
, but
instead returns it to be used again. This allows a Source
to be used
incrementally in a large program, without forcing the entire program to live
in the Sink
monad.
Mnemonic: connect + do more.
Since 0.5.0
($$++) :: Monad m => ResumableSource m a -> Sink a m b -> m (ResumableSource m a, b) infixr 0 Source
Continue processing after usage of $$+
.
Since 0.5.0
($$+-) :: Monad m => ResumableSource m a -> Sink a m b -> m b infixr 0 Source
Complete processing of a ResumableSource
. This will run the finalizer
associated with the ResumableSource
. In order to guarantee process resource
finalization, you must use this operator after using $$+
and $$++
.
Since 0.5.0
($=+) :: Monad m => ResumableSource m a -> Conduit a m b -> ResumableSource m b infixl 1 Source
Left fusion for a resumable source.
Since 1.0.16
(=$$+) :: Monad m => Conduit a m b -> Sink b m r -> Sink a m (ResumableConduit a m b, r) infixr 0 Source
The connect-and-resume operator. This does not close the Conduit
, but
instead returns it to be used again. This allows a Conduit
to be used
incrementally in a large program, without forcing the entire program to live
in the Sink
monad.
Leftover data returned from the Sink
will be discarded.
Mnemonic: connect + do more.
Since 1.0.17
(=$$++) :: Monad m => ResumableConduit i m o -> Sink o m r -> Sink i m (ResumableConduit i m o, r) infixr 0 Source
Continue processing after usage of =$$+
. Connect a ResumableConduit
to
a sink and return the output of the sink together with a new
ResumableConduit
.
Since 1.0.17
(=$$+-) :: Monad m => ResumableConduit i m o -> Sink o m r -> Sink i m r infixr 0 Source
Complete processing of a ResumableConduit
. This will run the finalizer
associated with the ResumableConduit
. In order to guarantee process
resource finalization, you must use this operator after using =$$+
and
=$$++
.
Since 1.0.17
($$) :: Monad m => Source m a -> Sink a m b -> m b infixr 0 Source
The connect operator, which pulls data from a source and pushes to a sink.
If you would like to keep the Source
open to be used for other
operations, use the connect-and-resume operator $$+
.
Since 0.4.0
($=) :: Monad m => Conduit a m b -> ConduitM b c m r -> ConduitM a c m r infixl 1 Source
A synonym for =$=
for backwards compatibility.
Since 0.4.0
(=$) :: Monad m => Conduit a m b -> ConduitM b c m r -> ConduitM a c m r infixr 2 Source
A synonym for =$=
for backwards compatibility.
Since 0.4.0
(=$=) :: Monad m => Conduit a m b -> ConduitM b c m r -> ConduitM a c m r infixr 2 Source
Fusion operator, combining two Conduit
s together into a new Conduit
.
Both Conduit
s will be closed when the newly-created Conduit
is closed.
Leftover data returned from the right Conduit
will be discarded.
Since 0.4.0
Generalizing
sourceToPipe :: Monad m => Source m o -> Pipe l i o u m () Source
sinkToPipe :: Monad m => Sink i m r -> Pipe l i o u m r Source
conduitToPipe :: Monad m => Conduit i m o -> Pipe l i o u m () Source
toProducer :: Monad m => Source m a -> Producer m a Source
toConsumer :: Monad m => Sink a m b -> Consumer a m b Source
Cleanup
:: MonadResource m | |
=> IO a | computation to run first ("acquire resource") |
-> (a -> IO ()) | computation to run last ("release resource") |
-> (a -> ConduitM i o m r) | computation to run in-between |
-> ConduitM i o m r |
Bracket a conduit computation between allocation and release of a resource. Two guarantees are given about resource finalization:
- It will be prompt. The finalization will be run as early as possible.
- It is exception safe. Due to usage of
resourcet
, the finalization will be run in the event of any exceptions.
Since 0.5.0
addCleanup :: Monad m => (Bool -> m ()) -> ConduitM i o m r -> ConduitM i o m r Source
Add some code to be run when the given component cleans up.
The supplied cleanup function will be given a True
if the component ran to
completion, or False
if it terminated early due to a downstream component
terminating.
Note that this function is not exception safe. For that, please use
bracketP
.
Since 0.4.1
Exceptions
catchC :: (MonadBaseControl IO m, Exception e) => ConduitM i o m r -> (e -> ConduitM i o m r) -> ConduitM i o m r Source
Catch all exceptions thrown by the current component of the pipeline.
Note: this will not catch exceptions thrown by other components! For
example, if an exception is thrown in a Source
feeding to a Sink
, and
the Sink
uses catchC
, the exception will not be caught.
Due to this behavior (as well as lack of async exception handling), you
should not try to implement combinators such as onException
in terms of this
primitive function.
Note also that the exception handling will not be applied to any finalizers generated by this conduit.
Since 1.0.11
handleC :: (MonadBaseControl IO m, Exception e) => (e -> ConduitM i o m r) -> ConduitM i o m r -> ConduitM i o m r Source
The same as flip catchC
.
Since 1.0.11
tryC :: (MonadBaseControl IO m, Exception e) => ConduitM i o m r -> ConduitM i o m (Either e r) Source
A version of try
for use within a pipeline. See the comments in catchC
for more details.
Since 1.0.11
Utilities
transPipe :: Monad m => (forall a. m a -> n a) -> ConduitM i o m r -> ConduitM i o n r Source
Transform the monad that a ConduitM
lives in.
Note that the monad transforming function will be run multiple times, resulting in unintuitive behavior in some cases. For a fuller treatment, please see:
https://github.com/snoyberg/conduit/wiki/Dealing-with-monad-transformers
This function is just a synonym for hoist
.
Since 0.4.0
mapOutput :: Monad m => (o1 -> o2) -> ConduitM i o1 m r -> ConduitM i o2 m r Source
Apply a function to all the output values of a ConduitM
.
This mimics the behavior of fmap
for a Source
and Conduit
in pre-0.4
days. It can also be simulated by fusing with the map
conduit from
Data.Conduit.List.
Since 0.4.1
mapOutputMaybe :: Monad m => (o1 -> Maybe o2) -> ConduitM i o1 m r -> ConduitM i o2 m r Source
Same as mapOutput
, but use a function that returns Maybe
values.
Since 0.5.0
:: Monad m | |
=> (i1 -> i2) | map initial input to new input |
-> (i2 -> Maybe i1) | map new leftovers to initial leftovers |
-> ConduitM i2 o m r | |
-> ConduitM i1 o m r |
Apply a function to all the input values of a ConduitM
.
Since 0.5.0
closeResumableSource :: Monad m => ResumableSource m a -> m () Source
Execute the finalizer associated with a ResumableSource
, rendering the
ResumableSource
invalid for further use.
This is just a more explicit version of $$+- return ()
.
Since 1.1.3
unwrapResumable :: MonadIO m => ResumableSource m o -> m (Source m o, m ()) Source
Unwraps a ResumableSource
into a Source
and a finalizer.
A ResumableSource
represents a Source
which has already been run, and
therefore has a finalizer registered. As a result, if we want to turn it
into a regular Source
, we need to ensure that the finalizer will be run
appropriately. By appropriately, I mean:
- If a new finalizer is registered, the old one should not be called.
- If the old one is called, it should not be called again.
This function returns both a Source
and a finalizer which ensures that the
above two conditions hold. Once you call that finalizer, the Source
is
invalidated and cannot be used.
Since 0.5.2
unwrapResumableConduit :: MonadIO m => ResumableConduit i m o -> m (Conduit i m o, m ()) Source
Unwraps a ResumableConduit
into a Conduit
and a finalizer.
Since unwrapResumable
for more information.
Since 1.0.17
newResumableSource :: Monad m => Source m o -> ResumableSource m o Source
Turn a Source
into a ResumableSource
with no attached finalizer.
Since 1.1.4
newResumableConduit :: Monad m => Conduit i m o -> ResumableConduit i m o Source
Turn a Conduit
into a ResumableConduit
with no attached finalizer.
Since 1.1.4
zipSinks :: Monad m => Sink i m r -> Sink i m r' -> Sink i m (r, r') Source
Combines two sinks. The new sink will complete when both input sinks have completed.
Any leftovers are discarded.
Since 0.4.1
zipSources :: Monad m => Source m a -> Source m b -> Source m (a, b) Source
Combines two sources. The new source will stop producing once either source has been exhausted.
Since 1.0.13
zipSourcesApp :: Monad m => Source m (a -> b) -> Source m a -> Source m b Source
Combines two sources. The new source will stop producing once either source has been exhausted.
Since 1.0.13
zipConduitApp :: Monad m => ConduitM i o m (x -> y) -> ConduitM i o m x -> ConduitM i o m y Source
Since 1.0.17
mergeSource :: Monad m => Source m i -> Conduit a m (i, a) Source
Merge a Source
into a Conduit
.
The new conduit will stop processing once either source or upstream have been exhausted.
Turn a Sink
into a Conduit
in the following way:
- All input passed to the
Sink
is yielded downstream. - When the
Sink
finishes processing, the result is passed to the provided to the finalizer function.
Note that the Sink
will stop receiving input as soon as the downstream it
is connected to shuts down.
An example usage would be to write the result of a Sink
to some mutable
variable while allowing other processing to continue.
Since 1.1.0
sourceToList :: Monad m => Source m a -> m [a] Source
Convert a Source
into a list. The basic functionality can be explained as:
sourceToList src = src $$ Data.Conduit.List.consume
However, sourceToList
is able to produce its results lazily, which cannot
be done when running a conduit pipeline in general. Unlike the
Data.Conduit.Lazy
module (in conduit-extra), this function performs no
unsafe I/O operations, and therefore can only be as lazily as the
underlying monad.
Since 1.2.6
fuseBoth :: Monad m => ConduitM a b m r1 -> ConduitM b c m r2 -> ConduitM a c m (r1, r2) Source
Fuse two ConduitM
s together, and provide the return value of both. Note
that this will force the entire upstream ConduitM
to be run to produce the
result value, even if the downstream terminates early.
Since 1.1.5
fuseBothMaybe :: Monad m => ConduitM a b m r1 -> ConduitM b c m r2 -> ConduitM a c m (Maybe r1, r2) Source
Like fuseBoth
, but does not force consumption of the Producer
.
In the case that the Producer
terminates, the result value is
provided as a Just
value. If it does not terminate, then a
Nothing
value is returned.
One thing to note here is that "termination" here only occurs if the
Producer
actually yields a Nothing
value. For example, with the
Producer
mapM_ yield [1..5]
, if five values are requested, the
Producer
has not yet terminated. Termination only occurs when the
sixth value is awaited for and the Producer
signals termination.
Since 1.2.4
fuseUpstream :: Monad m => ConduitM a b m r -> Conduit b m c -> ConduitM a c m r Source
Same as fuseBoth
, but ignore the return value from the downstream
Conduit
. Same caveats of forced consumption apply.
Since 1.1.5
sequenceSources :: (Traversable f, Monad m) => f (Source m o) -> Source m (f o) Source
Coalesce all values yielded by all of the Source
s.
Implemented on top of ZipSource
, see that data type for more details.
Since 1.0.13
sequenceSinks :: (Traversable f, Monad m) => f (Sink i m r) -> Sink i m (f r) Source
Send incoming values to all of the Sink
providing, and ultimately
coalesce together all return values.
Implemented on top of ZipSink
, see that data type for more details.
Since 1.0.13
sequenceConduits :: (Traversable f, Monad m) => f (ConduitM i o m r) -> ConduitM i o m (f r) Source
Provide identical input to all of the Conduit
s and combine their outputs
into a single stream.
Implemented on top of ZipConduit
, see that data type for more details.
Since 1.0.17
Fusion (highly experimental!!!)
module Data.Conduit.Internal.Fusion