| Safe Haskell | Safe | 
|---|---|
| Language | Haskell2010 | 
Data.Conduit.Internal
Synopsis
- 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 ()
- leftover :: l -> Pipe l i o u m ()
- unconsM :: Monad m => Pipe Void () o () m () -> m (Maybe (o, Pipe Void () o () m ()))
- unconsEitherM :: Monad m => Pipe Void () o () m r -> m (Either r (o, Pipe Void () o () m r))
- bracketP :: MonadResource m => IO a -> (a -> IO ()) -> (a -> 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 :: (MonadUnliftIO 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 :: (MonadUnliftIO 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 :: (MonadUnliftIO 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 ZipConduit i o m r = ZipConduit {- getZipConduit :: ConduitT i o m r
 
- newtype ZipSink i m r = ZipSink {- getZipSink :: ConduitT i Void m r
 
- newtype ZipSource m o = ZipSource {- getZipSource :: ConduitT () o m ()
 
- data Flush a
- type Conduit i m o = ConduitT i o m ()
- type Consumer i m r = forall o. ConduitT i o m r
- type Sink i = ConduitT i Void
- type Producer m o = forall i. ConduitT i o m ()
- type Source m o = ConduitT () o m ()
- type ConduitM = ConduitT
- newtype SealedConduitT i o m r = SealedConduitT (Pipe i i o () m r)
- newtype ConduitT i o m r = ConduitT {- unConduitT :: forall b. (r -> Pipe i i o () m b) -> Pipe i i o () m b
 
- sealConduitT :: ConduitT i o m r -> SealedConduitT i o m r
- unsealConduitT :: Monad m => SealedConduitT i o m r -> ConduitT i o m r
- connectResume :: Monad m => SealedConduitT () a m () -> ConduitT a Void m r -> m (SealedConduitT () a m (), r)
- sourceToPipe :: Monad m => ConduitT () o m () -> Pipe l i o u m ()
- sinkToPipe :: Monad m => ConduitT i Void m r -> Pipe l i o u m r
- conduitToPipe :: Monad m => ConduitT i o m () -> Pipe l i o u m ()
- toProducer :: Monad m => ConduitT () a m () -> ConduitT i a m ()
- toConsumer :: Monad m => ConduitT a Void m b -> ConduitT a o m b
- catchC :: (MonadUnliftIO m, Exception e) => ConduitT i o m r -> (e -> ConduitT i o m r) -> ConduitT i o m r
- handleC :: (MonadUnliftIO m, Exception e) => (e -> ConduitT i o m r) -> ConduitT i o m r -> ConduitT i o m r
- tryC :: (MonadUnliftIO m, Exception e) => ConduitT i o m r -> ConduitT i o m (Either e r)
- zipSinks :: Monad m => ConduitT i Void m r -> ConduitT i Void m r' -> ConduitT i Void m (r, r')
- zipSources :: Monad m => ConduitT () a m () -> ConduitT () b m () -> ConduitT () (a, b) m ()
- zipSourcesApp :: Monad m => ConduitT () (a -> b) m () -> ConduitT () a m () -> ConduitT () b m ()
- zipConduitApp :: Monad m => ConduitT i o m (x -> y) -> ConduitT i o m x -> ConduitT i o m y
- fuseReturnLeftovers :: Monad m => ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m (r, [b])
- fuseLeftovers :: Monad m => ([b] -> [a]) -> ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
- connectResumeConduit :: Monad m => SealedConduitT i o m () -> ConduitT o Void m r -> ConduitT i Void m (SealedConduitT i o m (), r)
- mergeSource :: Monad m => ConduitT () i m () -> ConduitT a (i, a) m ()
- passthroughSink :: Monad m => ConduitT i Void m r -> (r -> m ()) -> ConduitT i i m ()
- sourceToList :: Monad m => ConduitT () a m () -> m [a]
- connect :: Monad m => ConduitT () a m () -> ConduitT a Void m r -> m r
- fuse :: Monad m => ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
- (.|) :: Monad m => ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
- ($$) :: Monad m => Source m a -> Sink a m b -> m b
- ($=) :: Monad m => Conduit a m b -> ConduitT b c m r -> ConduitT a c m r
- (=$) :: Monad m => Conduit a m b -> ConduitT b c m r -> ConduitT a c m r
- (=$=) :: Monad m => Conduit a m b -> ConduitT b c m r -> ConduitT a c m r
- runConduit :: Monad m => ConduitT () Void m r -> m r
- ($$+) :: Monad m => ConduitT () a m () -> ConduitT a Void m b -> m (SealedConduitT () a m (), b)
- ($$++) :: Monad m => SealedConduitT () a m () -> ConduitT a Void m b -> m (SealedConduitT () a m (), b)
- ($$+-) :: Monad m => SealedConduitT () a m () -> ConduitT a Void m b -> m b
- ($=+) :: Monad m => SealedConduitT () a m () -> ConduitT a b m () -> SealedConduitT () b m ()
- sequenceSources :: (Traversable f, Monad m) => f (ConduitT () o m ()) -> ConduitT () (f o) m ()
- sequenceSinks :: (Traversable f, Monad m) => f (ConduitT i Void m r) -> ConduitT i Void m (f r)
- (=$$+) :: Monad m => ConduitT a b m () -> ConduitT b Void m r -> ConduitT a Void m (SealedConduitT a b m (), r)
- (=$$++) :: Monad m => SealedConduitT i o m () -> ConduitT o Void m r -> ConduitT i Void m (SealedConduitT i o m (), r)
- (=$$+-) :: Monad m => SealedConduitT i o m () -> ConduitT o Void m r -> ConduitT i Void m r
- sequenceConduits :: (Traversable f, Monad m) => f (ConduitT i o m r) -> ConduitT i o m (f r)
- fuseBoth :: Monad m => ConduitT a b m r1 -> ConduitT b c m r2 -> ConduitT a c m (r1, r2)
- fuseBothMaybe :: Monad m => ConduitT a b m r1 -> ConduitT b c m r2 -> ConduitT a c m (Maybe r1, r2)
- fuseUpstream :: Monad m => ConduitT a b m r -> ConduitT b c m () -> ConduitT a c m r
- runConduitPure :: ConduitT () Void Identity r -> r
- runConduitRes :: MonadUnliftIO m => ConduitT () Void (ResourceT m) r -> m r
- module Data.Conduit.Internal.Fusion
Pipe
Types
data Pipe l i o u m r Source #
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. APipewith no leftovers would useVoidhere, and one with leftovers would use the same type as the i parameter. Leftovers are automatically provided to the nextPipein 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
Constructors
| HaveOutput (Pipe l i o u m r) o | Provide new output to be sent downstream. This constructor has two
 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. | 
Instances
| MonadRWS r w s m => MonadRWS r w s (Pipe l i o u m) Source # | |
| Defined in Data.Conduit.Internal.Pipe | |
| MonadError e m => MonadError e (Pipe l i o u m) Source # | |
| Defined in Data.Conduit.Internal.Pipe Methods throwError :: e -> Pipe l i o u m a # catchError :: Pipe l i o u m a -> (e -> Pipe l i o u m a) -> Pipe l i o u m a # | |
| 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 # | |
| MonadTrans (Pipe l i o u) Source # | |
| Defined in Data.Conduit.Internal.Pipe | |
| MonadIO m => MonadIO (Pipe l i o u m) Source # | |
| Defined in Data.Conduit.Internal.Pipe | |
| Monad m => Applicative (Pipe l i o u m) Source # | |
| Defined in Data.Conduit.Internal.Pipe Methods pure :: a -> Pipe l i o u m a # (<*>) :: Pipe l i o u m (a -> b) -> Pipe l i o u m a -> Pipe l i o u m b # liftA2 :: (a -> b -> c) -> Pipe l i o u m a -> Pipe l i o u m b -> Pipe l i o u m c # (*>) :: Pipe l i o u m a -> Pipe l i o u m b -> Pipe l i o u m b # (<*) :: Pipe l i o u m a -> Pipe l i o u m b -> Pipe l i o u m a # | |
| Monad m => Functor (Pipe l i o u m) Source # | |
| Monad m => Monad (Pipe l i o u m) Source # | |
| MonadThrow m => MonadThrow (Pipe l i o u m) Source # | |
| Defined in Data.Conduit.Internal.Pipe | |
| PrimMonad m => PrimMonad (Pipe l i o u m) Source # | |
| MonadResource m => MonadResource (Pipe l i o u m) Source # | |
| Defined in Data.Conduit.Internal.Pipe Methods liftResourceT :: ResourceT IO a -> Pipe l i o u m a # | |
| Monad m => Monoid (Pipe l i o u m ()) Source # | |
| Monad m => Semigroup (Pipe l i o u m ()) Source # | |
| type PrimState (Pipe l i o u m) Source # | |
| Defined in Data.Conduit.Internal.Pipe | |
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
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
unconsM :: Monad m => Pipe Void () o () m () -> m (Maybe (o, Pipe Void () o () m ())) Source #
Split a pipe into head and tail.
Since 1.3.3
unconsEitherM :: Monad m => Pipe Void () o () m r -> m (Either r (o, Pipe Void () o () m r)) Source #
Split a pipe into head and tail or return its result if it is done.
Since 1.3.3
Finalization
Arguments
| :: 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.
 We guarantee, via the MonadResource context, that the resource
 finalization is exception safe. However, it will not necessarily be
 prompt, in that running a finalizer may wait until the ResourceT block
 exits.
Since 0.5.0
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.
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 Pipes, connecting the output from the left to the
 input of the right.
Notice that the leftover parameter for the Pipes 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 :: (MonadUnliftIO 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 :: (MonadUnliftIO 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 :: (MonadUnliftIO 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
Arguments
| :: 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
newtype ZipConduit i o m r Source #
Provides an alternative Applicative instance for ConduitT. In this instance,
 every incoming value is provided to all ConduitTs, and output is coalesced together.
 Leftovers from individual ConduitTs 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
Constructors
| ZipConduit | |
| Fields 
 | |
Instances
| Monad m => Applicative (ZipConduit i o m) Source # | |
| Defined in Data.Conduit.Internal.Conduit Methods pure :: a -> ZipConduit i o m a # (<*>) :: ZipConduit i o m (a -> b) -> ZipConduit i o m a -> ZipConduit i o m b # liftA2 :: (a -> b -> c) -> ZipConduit i o m a -> ZipConduit i o m b -> ZipConduit i o m c # (*>) :: ZipConduit i o m a -> ZipConduit i o m b -> ZipConduit i o m b # (<*) :: ZipConduit i o m a -> ZipConduit i o m b -> ZipConduit i o m a # | |
| Functor (ZipConduit i o m) Source # | |
| Defined in Data.Conduit.Internal.Conduit Methods fmap :: (a -> b) -> ZipConduit i o m a -> ZipConduit i o m b # (<$) :: a -> ZipConduit i o m b -> ZipConduit i o m a # | |
newtype ZipSink i m r Source #
A wrapper for defining an Applicative instance for Sinks 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)
          => [ConduitT i Void m r] -> ConduitT i Void 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
Constructors
| ZipSink | |
| Fields 
 | |
newtype ZipSource m o Source #
A wrapper for defining an Applicative instance for Sources which allows
 to combine sources together, generalizing zipSources. A combined source
 will take input yielded from each of its Sources until any of them stop
 producing output.
Since 1.0.13
Constructors
| ZipSource | |
| Fields 
 | |
Provide for a stream of data that can be flushed.
A number of Conduits (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
type Conduit i m o = ConduitT i o m () Source #
Deprecated: Use ConduitT directly
Consumes a stream of input values and produces a stream of output values, without producing a final result.
Since 0.5.0
type Consumer i m r = forall o. ConduitT i o m r Source #
Deprecated: Use ConduitT directly
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 Sink i = ConduitT i Void Source #
Deprecated: Use ConduitT directly
Consumes a stream of input values and produces a final result, without producing any output.
type Sink i m r = ConduitT i Void m r
Since 0.5.0
type Producer m o = forall i. ConduitT i o m () Source #
Deprecated: Use ConduitT directly
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 Source m o = ConduitT () o m () Source #
Deprecated: Use ConduitT directly
Provides a stream of output values, without consuming any input or producing a final result.
Since 0.5.0
newtype SealedConduitT i o m r Source #
In order to provide for efficient monadic composition, the
 ConduitT type is implemented internally using a technique known
 as the codensity transform. This allows for cheap appending, but
 makes one case much more expensive: partially running a ConduitT
 and that capturing the new state.
This data type is the same as ConduitT, but does not use the
 codensity transform technique.
Since: 1.3.0
Constructors
| SealedConduitT (Pipe i i o () m r) | 
newtype ConduitT 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.3.0
Constructors
| ConduitT | |
| Fields 
 | |
Instances
sealConduitT :: ConduitT i o m r -> SealedConduitT i o m r Source #
unsealConduitT :: Monad m => SealedConduitT i o m r -> ConduitT i o m r Source #
connectResume :: Monad m => SealedConduitT () a m () -> ConduitT a Void m r -> m (SealedConduitT () a m (), 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.
Since 0.5.0
catchC :: (MonadUnliftIO m, Exception e) => ConduitT i o m r -> (e -> ConduitT i o m r) -> ConduitT 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 safety), 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 :: (MonadUnliftIO m, Exception e) => (e -> ConduitT i o m r) -> ConduitT i o m r -> ConduitT i o m r Source #
The same as flip catchC.
Since 1.0.11
tryC :: (MonadUnliftIO m, Exception e) => ConduitT i o m r -> ConduitT 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
zipSinks :: Monad m => ConduitT i Void m r -> ConduitT i Void m r' -> ConduitT i Void 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 => ConduitT () a m () -> ConduitT () b m () -> ConduitT () (a, b) m () Source #
Combines two sources. The new source will stop producing once either source has been exhausted.
Since 1.0.13
zipSourcesApp :: Monad m => ConduitT () (a -> b) m () -> ConduitT () a m () -> ConduitT () b m () Source #
Combines two sources. The new source will stop producing once either source has been exhausted.
Since 1.0.13
zipConduitApp :: Monad m => ConduitT i o m (x -> y) -> ConduitT i o m x -> ConduitT i o m y Source #
Since 1.0.17
fuseReturnLeftovers :: Monad m => ConduitT a b m () -> ConduitT b c m r -> ConduitT 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
fuseLeftovers :: Monad m => ([b] -> [a]) -> ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r Source #
Similar to fuseReturnLeftovers, but use the provided function to convert
 downstream leftovers to upstream leftovers.
Since 1.0.17
connectResumeConduit :: Monad m => SealedConduitT i o m () -> ConduitT o Void m r -> ConduitT i Void m (SealedConduitT i o m (), r) Source #
mergeSource :: Monad m => ConduitT () i m () -> ConduitT a (i, a) m () 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 Sinkis yielded downstream.
- When the Sinkfinishes 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 => ConduitT () a m () -> 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 lazy as the
 underlying monad.
Since 1.2.6
connect :: Monad m => ConduitT () a m () -> ConduitT a Void m r -> m r Source #
Equivalent to using runConduit and .| together.
Since 1.2.3
Combine two Conduits together into a new Conduit (aka fuse).
Output from the upstream (left) conduit will be fed into the
 downstream (right) conduit. Processing will terminate when
 downstream (right) returns.
 Leftover data returned from the right Conduit will be discarded.
Equivalent to fuse and =$=, however the latter is deprecated and will
 be removed in a future version.
Note that, while this operator looks like categorical composition (from Control.Category), there are a few reasons it's different:
- The position of the type parameters to ConduitTdo not match. We would need to changeConduitT i o m rtoConduitT r m i o, which would preclude aMonadorMonadTransinstance.
- The result value from upstream and downstream are allowed to
   differ between upstream and downstream. In other words, we would
   need the type signature here to look like ConduitT a b m r -> ConduitT b c m r -> ConduitT a c m r.
- Due to leftovers, we do not have a left identity in Conduit. This
   can be achieved with the underlying Pipedatatype, but this is not generally recommended. See https://stackoverflow.com/a/15263700.
Since: 1.2.8
($$) :: Monad m => Source m a -> Sink a m b -> m b infixr 0 Source #
Deprecated: Use runConduit and .|
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 -> ConduitT b c m r -> ConduitT a c m r infixr 2 Source #
Deprecated: Use .|
Deprecated fusion operator.
Since 0.4.0
runConduit :: Monad m => ConduitT () Void m r -> m r Source #
Run a pipeline until processing completes.
Since 1.2.1
($$+) :: Monad m => ConduitT () a m () -> ConduitT a Void m b -> m (SealedConduitT () a m (), 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 => SealedConduitT () a m () -> ConduitT a Void m b -> m (SealedConduitT () a m (), b) infixr 0 Source #
Continue processing after usage of $$+.
Since 0.5.0
($$+-) :: Monad m => SealedConduitT () a m () -> ConduitT a Void m b -> m b infixr 0 Source #
Same as $$++ and connectResume, but doesn't include the
 updated SealedConduitT.
NOTE In previous versions, this would cause finalizers to run. Since version 1.3.0, there are no finalizers in conduit.
Since 0.5.0
($=+) :: Monad m => SealedConduitT () a m () -> ConduitT a b m () -> SealedConduitT () b m () infixl 1 Source #
Left fusion for a sealed source.
Since 1.0.16
sequenceSources :: (Traversable f, Monad m) => f (ConduitT () o m ()) -> ConduitT () (f o) m () Source #
Coalesce all values yielded by all of the Sources.
Implemented on top of ZipSource and as such, it exhibits the same
 short-circuiting behavior as ZipSource. See that data type for more
 details. If you want to create a source that yields *all* values from
 multiple sources, use sequence_.
Since 1.0.13
sequenceSinks :: (Traversable f, Monad m) => f (ConduitT i Void m r) -> ConduitT i Void 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
(=$$+) :: Monad m => ConduitT a b m () -> ConduitT b Void m r -> ConduitT a Void m (SealedConduitT a b m (), 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 => SealedConduitT i o m () -> ConduitT o Void m r -> ConduitT i Void m (SealedConduitT i o m (), r) infixr 0 Source #
Continue processing after usage of =$$+. Connect a SealedConduitT to
 a sink and return the output of the sink together with a new
 SealedConduitT.
Since 1.0.17
(=$$+-) :: Monad m => SealedConduitT i o m () -> ConduitT o Void m r -> ConduitT i Void m r infixr 0 Source #
Same as =$$++, but doesn't include the updated
 SealedConduitT.
NOTE In previous versions, this would cause finalizers to run. Since version 1.3.0, there are no finalizers in conduit.
Since 1.0.17
sequenceConduits :: (Traversable f, Monad m) => f (ConduitT i o m r) -> ConduitT i o m (f r) Source #
Provide identical input to all of the Conduits and combine their outputs
 into a single stream.
Implemented on top of ZipConduit, see that data type for more details.
Since 1.0.17
fuseBoth :: Monad m => ConduitT a b m r1 -> ConduitT b c m r2 -> ConduitT a c m (r1, r2) Source #
Fuse two ConduitTs together, and provide the return value of both. Note
 that this will force the entire upstream ConduitT to be run to produce the
 result value, even if the downstream terminates early.
Since 1.1.5
fuseBothMaybe :: Monad m => ConduitT a b m r1 -> ConduitT b c m r2 -> ConduitT 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 => ConduitT a b m r -> ConduitT b c m () -> ConduitT 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
runConduitPure :: ConduitT () Void Identity r -> r Source #
Run a pure pipeline until processing completes, i.e. a pipeline
 with Identity as the base monad. This is equivalient to
 runIdentity . runConduit.
Since: 1.2.8
runConduitRes :: MonadUnliftIO m => ConduitT () Void (ResourceT m) r -> m r Source #
Run a pipeline which acquires resources with ResourceT, and
 then run the ResourceT transformer. This is equivalent to
 runResourceT . runConduit.
Since: 1.2.8
Fusion (highly experimental!!!)
module Data.Conduit.Internal.Fusion