conduit-0.5.3: Streaming data processing library.

Safe HaskellNone

Data.Conduit.Internal

Contents

Synopsis

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. A Pipe with no leftovers would use Void here, and one with leftovers would use the same type as the i parameter. Leftovers are automatically provided to the next Pipe 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

Constructors

HaveOutput (Pipe l i o u m r) (m ()) o

Provide new output to be sent downstream. This constructor has three fields: the next Pipe to be used, a finalization function, and the output value.

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 Pipe. The second takes an upstream result value, which indicates that upstream is producing no more results.

Done r

Processing with this Pipe is complete, providing the final result.

PipeM (m (Pipe l i o u m r))

Require running of a monadic action to get the next Pipe.

Leftover (Pipe l i o u m r) l

Return leftover input, which should be provided to future operations.

Instances

(Applicative base, Applicative (Pipe l i o u m), Monad base, Monad (Pipe l i o u m), MonadBase base m) => MonadBase base (Pipe l i o u m) 
MonadTrans (Pipe l i o u) 
Monad m => Monad (Pipe l i o u m) 
Monad m => Functor (Pipe l i o u m) 
(Functor (Pipe l i o u m), Monad m) => Applicative (Pipe l i o u m) 
(Monad (Pipe l i o u m), MonadIO m) => MonadIO (Pipe l i o u m) 
Monad m => Monoid (Pipe l i o u m ()) 

type Source m o = Pipe () () o () m ()Source

Provides a stream of output values, without consuming any input or producing a final result.

Since 0.5.0

type GSource m o = forall l i u. Pipe l i o u m ()Source

Generalized Source.

Since 0.5.0

type Sink i m r = Pipe i i Void () m rSource

Consumes a stream of input values and produces a final result, without producing any output.

Since 0.5.0

type GSink i m r = forall l o u. Pipe l i o u m rSource

Generalized Sink without leftovers.

Since 0.5.0

type GLSink i m r = forall o u. Pipe i i o u m rSource

Generalized Sink with leftovers.

Since 0.5.0

type GInfSink i m = forall l o r. Pipe l i o r m rSource

Generalized Sink without leftovers returning upstream result.

Since 0.5.0

type GLInfSink i m = forall o r. Pipe i i o r m rSource

Generalized Sink with leftovers returning upstream result.

Since 0.5.0

type Conduit i m o = Pipe i 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

type GConduit i m o = forall l u. Pipe l i o u m ()Source

Generalized conduit without leftovers.

Since 0.5.0

type GLConduit i m o = forall u. Pipe i i o u m ()Source

Generalized conduit with leftovers.

Since 0.5.0

type GInfConduit i m o = forall l r. Pipe l i o r m rSource

Generalized conduit without leftovers returning upstream result.

Since 0.5.0

type GLInfConduit i m o = forall r. Pipe i i o r m rSource

Generalized conduit with leftovers returning upstream 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

Constructors

ResumableSource (Source m o) (m ()) 

Primitives

await :: Pipe l i o u m (Maybe i)Source

Wait for a single input value from upstream, terminating immediately if no data is available.

Since 0.5.0

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 rSource

Wait for input forever, calling the given inner Pipe for each piece of new input. Returns the upstream result type.

Since 0.5.0

yieldSource

Arguments

:: Monad m 
=> o

output value

-> Pipe l i o u m () 

Send a single output value downstream. If the downstream Pipe terminates, this Pipe will terminate as well.

Since 0.5.0

yieldOrSource

Arguments

:: Monad m 
=> o 
-> m ()

finalizer

-> Pipe l i o u m () 

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

bracketP :: MonadResource m => IO a -> (a -> IO ()) -> (a -> Pipe l i o u m r) -> Pipe l i o u m rSource

Perform some allocation and run an inner Pipe. 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

addCleanupSource

Arguments

:: Monad m 
=> (Bool -> m ())

True if Pipe ran to completion, False for early termination.

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

idP :: Monad m => Pipe l a a r m rSource

The identity Pipe.

Since 0.5.0

pipe :: Monad m => Pipe l a b r0 m r1 -> Pipe Void b c r1 m r2 -> Pipe l a c r0 m r2Source

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 r2Source

Same as pipe, but automatically applies injectLeftovers to the right Pipe.

Since 0.5.0

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

runPipe :: Monad m => Pipe Void () Void () m r -> m rSource

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 rSource

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

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 rSource

conduitToPipe :: Monad m => Conduit i m o -> Pipe l i o u m ()Source

Utilities

transPipe :: Monad m => (forall a. m a -> n a) -> Pipe l i o u m r -> Pipe l i o u n rSource

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

Since 0.4.0

mapOutput :: Monad m => (o1 -> o2) -> Pipe l i o1 u m r -> Pipe l i o2 u m rSource

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 rSource

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

Since 0.5.0

mapInputSource

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

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