conduit-0.4.0: Streaming data processing library.

Safe HaskellSafe-Infered

Data.Conduit.Internal

Contents

Synopsis

Types

data Pipe i o m r Source

The underlying datatype for all the types in this package. In has four type parameters:

  • i is the type of values for this Pipe's input stream.
  • o is the type of values for this Pipe's output stream.
  • m is the underlying monad.
  • r is the result type.

Note that o and r are inherently different. o is the type of the stream of values this Pipe will produce and send downstream. r is the final output of this Pipe.

Pipes can be composed via the pipe function. To do so, the output type of the left pipe much match the input type of the left pipe, and the result type of the left pipe must be unit (). This is due to the fact that any result produced by the left pipe must be discarded in favor of the result of the right pipe.

Since 0.4.0

Constructors

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

Provide new output to be sent downstream. This constructor has three records: the next Pipe to be used, an early-closed function, and the output value.

NeedInput (i -> Pipe i o m r) (Pipe i o m r)

Request more input from upstream. The first record takes a new input value and provides a new Pipe. The second is for early termination. It gives a new Pipe which takes no input from upstream. This allows a Pipe to provide a final stream of output values after no more input is available from upstream.

Done (Maybe i) r

Processing with this Pipe is complete. Provides an optional leftover input value and and result.

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

Require running of a monadic action to get the next Pipe. Second record is an early cleanup function. Technically, this second record could be skipped, but doing so would require extra operations to be performed in some cases. For example, for a Pipe pulling data from a file, it may be forced to pull an extra, unneeded chunk before closing the Handle.

Instances

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

type Source m a = Pipe Void a m ()Source

A Pipe which provides a stream of output values, without consuming any input. The input parameter is set to () instead of Void since there is no way to statically guarantee that the NeedInput constructor will not be used. A Source is not used to produce a final result, and thus the result parameter is set to () as well.

Since 0.4.0

type Sink i m r = Pipe i Void m rSource

A Pipe which consumes a stream of input values and produces a final result. It cannot produce any output values, and thus the output parameter is set to Void. In other words, it is impossible to create a HaveOutput constructor for a Sink.

Since 0.4.0

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

A Pipe which consumes a stream of input values and produces a stream of output values. It does not produce a result value, and thus the result parameter is set to ().

Since 0.4.0

Functions

pipeClose :: Monad m => Pipe i o m r -> m rSource

Perform any close actions available for the given Pipe.

Since 0.4.0

pipe :: Monad m => Pipe a b m () -> Pipe b c m r -> Pipe a c m rSource

Compose a left and right pipe together into a complete pipe. The left pipe will be automatically closed when the right pipe finishes, and any leftovers from the right pipe will be discarded.

This is in fact a wrapper around pipeResume. This function closes the left Pipe returns by pipeResume and returns only the result.

Since 0.4.0

pipeResume :: Monad m => Pipe a b m () -> Pipe b c m r -> Pipe a c m (Pipe a b m (), r)Source

Same as pipe, but retain both the new left pipe and the leftovers from the right pipe. The two components are combined together into a single pipe and returned, together with the result of the right pipe.

Note: we're biased towards checking the right side first to avoid pulling extra data which is not needed. Doing so could cause data loss.

Since 0.4.0

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

Run a complete pipeline until processing completes.

Since 0.4.0

sinkToPipe :: Monad m => Sink i m r -> Pipe i o m rSource

A Sink has a Void type parameter for the output, which makes it difficult to compose with Sources and Conduits. This function replaces that parameter with a free variable. This function is essentially id; it only modifies the types, not the actions performed.

Since 0.4.0

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

Wait for a single input value from upstream, and remove it from the stream. Returns Nothing if no more data is available.

Since 0.4.0

yield :: Monad m => o -> Pipe i o m ()Source

Send a single output value downstream.

Since 0.4.0

hasInput :: Pipe i o m BoolSource

Check if input is available from upstream. Will not remove the data from the stream.

Since 0.4.0

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

Transform the monad that a Pipe lives in.

Since 0.4.0