conduit-1.3.1.2: Streaming data processing library.

Safe HaskellNone
LanguageHaskell98

Data.Conduit

Contents

Description

If this is your first time with conduit, you should probably start with the tutorial: https://github.com/snoyberg/conduit#readme.

Synopsis

Core interface

Types

data 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

Instances
MonadRWS r w s m => MonadRWS r w s (ConduitT i o m) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

MonadWriter w m => MonadWriter w (ConduitT i o m) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

writer :: (a, w) -> ConduitT i o m a #

tell :: w -> ConduitT i o m () #

listen :: ConduitT i o m a -> ConduitT i o m (a, w) #

pass :: ConduitT i o m (a, w -> w) -> ConduitT i o m a #

MonadState s m => MonadState s (ConduitT i o m) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

get :: ConduitT i o m s #

put :: s -> ConduitT i o m () #

state :: (s -> (a, s)) -> ConduitT i o m a #

MonadReader r m => MonadReader r (ConduitT i o m) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

ask :: ConduitT i o m r #

local :: (r -> r) -> ConduitT i o m a -> ConduitT i o m a #

reader :: (r -> a) -> ConduitT i o m a #

MonadError e m => MonadError e (ConduitT i o m) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

throwError :: e -> ConduitT i o m a #

catchError :: ConduitT i o m a -> (e -> ConduitT i o m a) -> ConduitT i o m a #

MonadTrans (ConduitT i o) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

lift :: Monad m => m a -> ConduitT i o m a #

Monad (ConduitT i o m) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

(>>=) :: ConduitT i o m a -> (a -> ConduitT i o m b) -> ConduitT i o m b #

(>>) :: ConduitT i o m a -> ConduitT i o m b -> ConduitT i o m b #

return :: a -> ConduitT i o m a #

fail :: String -> ConduitT i o m a #

Functor (ConduitT i o m) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

fmap :: (a -> b) -> ConduitT i o m a -> ConduitT i o m b #

(<$) :: a -> ConduitT i o m b -> ConduitT i o m a #

MonadFail m => MonadFail (ConduitT i o m) Source #

Since: 1.3.1

Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

fail :: String -> ConduitT i o m a #

Applicative (ConduitT i o m) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

pure :: a -> ConduitT i o m a #

(<*>) :: ConduitT i o m (a -> b) -> ConduitT i o m a -> ConduitT i o m b #

liftA2 :: (a -> b -> c) -> ConduitT i o m a -> ConduitT i o m b -> ConduitT i o m c #

(*>) :: ConduitT i o m a -> ConduitT i o m b -> ConduitT i o m b #

(<*) :: ConduitT i o m a -> ConduitT i o m b -> ConduitT i o m a #

MonadIO m => MonadIO (ConduitT i o m) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

liftIO :: IO a -> ConduitT i o m a #

MonadThrow m => MonadThrow (ConduitT i o m) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

throwM :: Exception e => e -> ConduitT i o m a #

PrimMonad m => PrimMonad (ConduitT i o m) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Associated Types

type PrimState (ConduitT i o m) :: Type #

Methods

primitive :: (State# (PrimState (ConduitT i o m)) -> (#State# (PrimState (ConduitT i o m)), a#)) -> ConduitT i o m a #

MonadResource m => MonadResource (ConduitT i o m) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

liftResourceT :: ResourceT IO a -> ConduitT i o m a #

Monad m => Semigroup (ConduitT i o m ()) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

(<>) :: ConduitT i o m () -> ConduitT i o m () -> ConduitT i o m () #

sconcat :: NonEmpty (ConduitT i o m ()) -> ConduitT i o m () #

stimes :: Integral b => b -> ConduitT i o m () -> ConduitT i o m () #

Monad m => Monoid (ConduitT i o m ()) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

mempty :: ConduitT i o m () #

mappend :: ConduitT i o m () -> ConduitT i o m () -> ConduitT i o m () #

mconcat :: [ConduitT i o m ()] -> ConduitT i o m () #

type PrimState (ConduitT i o m) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

type PrimState (ConduitT i o m) = PrimState m

Deprecated

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

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 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 ConduitM = ConduitT Source #

Same as ConduitT, for backwards compat

Connect/fuse operators

(.|) infixr 2 Source #

Arguments

:: Monad m 
=> ConduitM a b m ()

upstream

-> ConduitM b c m r

downstream

-> ConduitM a c m r 

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 ConduitT do not match. We would need to change ConduitT i o m r to ConduitT r m i o, which would preclude a Monad or MonadTrans instance.
  • 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 Pipe datatype, but this is not generally recommended. See https://stackoverflow.com/a/15263700.

Since: 1.2.8

connect :: Monad m => ConduitT () a m () -> ConduitT a Void m r -> m r Source #

Equivalent to using runConduit and .| together.

Since 1.2.3

fuse :: Monad m => Conduit a m b -> ConduitM b c m r -> ConduitM a c m r Source #

Named function synonym for .|

Equivalent to .| and =$=. However, the latter is deprecated and will be removed in a future version.

Since 1.2.3

Deprecated

($$) :: 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 infixl 1 Source #

Deprecated: Use .|

A synonym for =$= for backwards compatibility.

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 .|

A synonym for =$= for backwards compatibility.

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

Fuse with upstream results

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 -> Conduit b m c -> 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

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

yield Source #

Arguments

:: Monad m 
=> o

output value

-> ConduitT i o m () 

Send a value downstream to the next component to consume. If the downstream component terminates, this call will never return control.

Since 0.5.0

yieldM :: Monad m => m o -> ConduitT i o m () Source #

Send a monadic value downstream for the next component to consume.

Since: 1.2.7

leftover :: i -> ConduitT 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 => ConduitT () Void m r -> m r Source #

Run a pipeline until processing completes.

Since 1.2.1

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

Finalization

bracketP Source #

Arguments

:: MonadResource m 
=> IO a

computation to run first ("acquire resource")

-> (a -> IO ())

computation to run last ("release resource")

-> (a -> ConduitT i o m r)

computation to run in-between

-> ConduitT i o m r 

Bracket a conduit computation between allocation and release of a resource. Two guarantees are given about resource finalization:

  1. It will be prompt. The finalization will be run as early as possible.
  2. It is exception safe. Due to usage of resourcet, the finalization will be run in the event of any exceptions.

Since 0.5.0

Exception handling

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

Generalized conduit types

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 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

toProducer :: Monad m => Source m a -> Producer m a Source #

Generalize a Source to a Producer.

Since 1.0.0

toConsumer :: Monad m => Sink a m b -> Consumer a m b Source #

Generalize a Sink to a Consumer.

Since 1.0.0

Utility functions

awaitForever :: Monad m => (i -> ConduitT i o m r) -> ConduitT i o m () Source #

Wait for input forever, calling the given inner component for each piece of new input.

This function is provided as a convenience for the common pattern of awaiting input, checking if it's Just and then looping.

Since 0.5.0

transPipe :: Monad m => (forall a. m a -> n a) -> ConduitT i o m r -> ConduitT i o n r Source #

Transform the monad that a ConduitT 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

Since 0.4.0

mapOutput :: Monad m => (o1 -> o2) -> ConduitT i o1 m r -> ConduitT i o2 m r Source #

Apply a function to all the output values of a ConduitT.

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) -> ConduitT i o1 m r -> ConduitT i o2 m r Source #

Same as mapOutput, but use a function that returns Maybe values.

Since 0.5.0

mapInput Source #

Arguments

:: Monad m 
=> (i1 -> i2)

map initial input to new input

-> (i2 -> Maybe i1)

map new leftovers to initial leftovers

-> ConduitT i2 o m r 
-> ConduitT i1 o m r 

Apply a function to all the input values of a ConduitT.

Since 0.5.0

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.

passthroughSink Source #

Arguments

:: Monad m 
=> Sink i m r 
-> (r -> m ())

finalizer

-> Conduit i m i 

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

Connect-and-resume

data 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

unsealConduitT :: Monad m => SealedConduitT i o m r -> ConduitT i o m r Source #

($$+) :: Monad m => Source m a -> Sink a 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 () -> Sink a m b -> m (SealedConduitT () a m (), b) infixr 0 Source #

Continue processing after usage of $$+.

Since 0.5.0

($$+-) :: Monad m => SealedConduitT () a m () -> Sink a 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 () -> Conduit a m b -> SealedConduitT () b m () infixl 1 Source #

Left fusion for a sealed source.

Since 1.0.16

For Conduits

(=$$+) :: 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

Fusion with leftovers

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

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

Flushing

data Flush a Source #

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

Constructors

Chunk a 
Flush 
Instances
Functor Flush Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

fmap :: (a -> b) -> Flush a -> Flush b #

(<$) :: a -> Flush b -> Flush a #

Eq a => Eq (Flush a) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

(==) :: Flush a -> Flush a -> Bool #

(/=) :: Flush a -> Flush a -> Bool #

Ord a => Ord (Flush a) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

compare :: Flush a -> Flush a -> Ordering #

(<) :: Flush a -> Flush a -> Bool #

(<=) :: Flush a -> Flush a -> Bool #

(>) :: Flush a -> Flush a -> Bool #

(>=) :: Flush a -> Flush a -> Bool #

max :: Flush a -> Flush a -> Flush a #

min :: Flush a -> Flush a -> Flush a #

Show a => Show (Flush a) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

showsPrec :: Int -> Flush a -> ShowS #

show :: Flush a -> String #

showList :: [Flush a] -> ShowS #

Newtype wrappers

ZipSource

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

Instances
Monad m => Functor (ZipSource m) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

fmap :: (a -> b) -> ZipSource m a -> ZipSource m b #

(<$) :: a -> ZipSource m b -> ZipSource m a #

Monad m => Applicative (ZipSource m) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

pure :: a -> ZipSource m a #

(<*>) :: ZipSource m (a -> b) -> ZipSource m a -> ZipSource m b #

liftA2 :: (a -> b -> c) -> ZipSource m a -> ZipSource m b -> ZipSource m c #

(*>) :: ZipSource m a -> ZipSource m b -> ZipSource m b #

(<*) :: ZipSource m a -> ZipSource m b -> ZipSource m a #

sequenceSources :: (Traversable f, Monad m) => f (Source m o) -> Source m (f o) 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

ZipSink

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)
          => [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

Constructors

ZipSink 

Fields

Instances
Monad m => Functor (ZipSink i m) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

fmap :: (a -> b) -> ZipSink i m a -> ZipSink i m b #

(<$) :: a -> ZipSink i m b -> ZipSink i m a #

Monad m => Applicative (ZipSink i m) Source # 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

pure :: a -> ZipSink i m a #

(<*>) :: ZipSink i m (a -> b) -> ZipSink i m a -> ZipSink i m b #

liftA2 :: (a -> b -> c) -> ZipSink i m a -> ZipSink i m b -> ZipSink i m c #

(*>) :: ZipSink i m a -> ZipSink i m b -> ZipSink i m b #

(<*) :: ZipSink i m a -> ZipSink i m b -> ZipSink i m a #

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

ZipConduit

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
Functor (ZipConduit i o m) Source # 
Instance details

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 #

Monad m => Applicative (ZipConduit i o m) Source # 
Instance details

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 #

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

Convenience reexports

data Void #

Uninhabited data type

Since: base-4.8.0.0

Instances
Eq Void

Since: base-4.8.0.0

Instance details

Defined in Data.Void

Methods

(==) :: Void -> Void -> Bool #

(/=) :: Void -> Void -> Bool #

Data Void

Since: base-4.8.0.0

Instance details

Defined in Data.Void

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Void -> c Void #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Void #

toConstr :: Void -> Constr #

dataTypeOf :: Void -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Void) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Void) #

gmapT :: (forall b. Data b => b -> b) -> Void -> Void #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Void -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Void -> r #

gmapQ :: (forall d. Data d => d -> u) -> Void -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Void -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Void -> m Void #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Void -> m Void #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Void -> m Void #

Ord Void

Since: base-4.8.0.0

Instance details

Defined in Data.Void

Methods

compare :: Void -> Void -> Ordering #

(<) :: Void -> Void -> Bool #

(<=) :: Void -> Void -> Bool #

(>) :: Void -> Void -> Bool #

(>=) :: Void -> Void -> Bool #

max :: Void -> Void -> Void #

min :: Void -> Void -> Void #

Read Void

Reading a Void value is always a parse error, considering Void as a data type with no constructors.

Since: base-4.8.0.0

Instance details

Defined in Data.Void

Show Void

Since: base-4.8.0.0

Instance details

Defined in Data.Void

Methods

showsPrec :: Int -> Void -> ShowS #

show :: Void -> String #

showList :: [Void] -> ShowS #

Ix Void

Since: base-4.8.0.0

Instance details

Defined in Data.Void

Methods

range :: (Void, Void) -> [Void] #

index :: (Void, Void) -> Void -> Int #

unsafeIndex :: (Void, Void) -> Void -> Int

inRange :: (Void, Void) -> Void -> Bool #

rangeSize :: (Void, Void) -> Int #

unsafeRangeSize :: (Void, Void) -> Int

Generic Void 
Instance details

Defined in Data.Void

Associated Types

type Rep Void :: Type -> Type #

Methods

from :: Void -> Rep Void x #

to :: Rep Void x -> Void #

Semigroup Void

Since: base-4.9.0.0

Instance details

Defined in Data.Void

Methods

(<>) :: Void -> Void -> Void #

sconcat :: NonEmpty Void -> Void #

stimes :: Integral b => b -> Void -> Void #

Exception Void

Since: base-4.8.0.0

Instance details

Defined in Data.Void

Hashable Void 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Void -> Int #

hash :: Void -> Int #

type Rep Void

Since: base-4.8.0.0

Instance details

Defined in Data.Void

type Rep Void = D1 (MetaData "Void" "Data.Void" "base" False) (V1 :: Type -> Type)