pipes-core-0.1.0: Compositional pipelines

Safe HaskellSafe-Infered

Control.Pipe.Common

Contents

Synopsis

Types

data Pipe a b m r Source

The base type for pipes.

a
The type of input received fom upstream pipes.
b
The type of output delivered to downstream pipes.
m
The base monad.
r
The type of the monad's final result.

Constructors

Pure r (Finalizer m) 
Throw SomeException (Finalizer m) 
Await (a -> Pipe a b m r) (SomeException -> Pipe a b m r) 
M MaskState (m (Pipe a b m r)) (SomeException -> Pipe a b m r) 
Yield b (Pipe a b m r) (Finalizer m) 

Instances

MonadTrans (Pipe a b) 
Monad m => Monad (Pipe a b m) 
Monad m => Functor (Pipe a b m) 
Monad m => Applicative (Pipe a b m) 
MonadIO m => MonadIO (Pipe a b m) 

type Producer b m = Pipe () b mSource

A pipe that can only produce values.

type Consumer a m = Pipe a Void mSource

A pipe that can only consume values.

type Pipeline m = Pipe () Void mSource

A self-contained pipeline that is ready to be run.

Primitives

await and yield are the two basic primitives you need to create Pipes. Because Pipe is a monad, you can assemble them using ordinary do notation. Since Pipe is also a monad trnasformer, you can use lift to invoke the base monad. For example:

 check :: Pipe a a IO r
 check = forever $ do
   x <- await
   lift $ putStrLn $ "Can " ++ show x ++ " pass?"
   ok <- lift $ read <$> getLine
   when ok $ yield x

await :: Monad m => Pipe a b m aSource

Wait for input from upstream within the Pipe monad.

await blocks until input is ready.

yield :: Monad m => b -> Pipe a b m ()Source

Pass output downstream within the Pipe monad.

yield blocks until the downstream pipe calls await again.

masked :: Monad m => m r -> Pipe a b m rSource

Execute an action in the base monad with asynchronous exceptions masked.

This function is effective only if the Pipeline is run with runPipe, otherwise it is identical to lift

Basic combinators

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

Convert a pure function into a pipe.

 pipe = forever $ do
   x <- await
   yield (f x)

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

The identity pipe.

discard :: Monad m => Pipe a b m rSource

The discard pipe silently discards all input fed to it.

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

Left to right pipe composition.

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

Right to left pipe composition.

Running pipes

runPipe :: MonadBaseControl IO m => Pipeline m r -> m rSource

Run a self-contained Pipeline, converting it to an action in the base monad.

This function is exception-safe. Any exception thrown in the base monad during execution of the pipeline will be captured by catch statements in the Pipe monad.

runPurePipe :: Monad m => Pipeline m r -> m (Either SomeException r)Source

Run a self-contained pipeline over an arbitrary monad, with fewer exception-safety guarantees than runPipe.

Only pipe termination exceptions and exceptions thrown using throw will be catchable within the Pipe monad. Any other exception will terminate execution immediately and finalizers will not be called.

Any captured exception will be returned in the left component of the result.

runPurePipe_ :: Monad m => Pipeline m r -> m rSource

A version of runPurePipe which rethrows any captured exception instead of returning it.

Low level types

data BrokenPipe Source

The BrokenPipe exception is used to signal termination of the upstream portion of a Pipeline before the current pipe

A BrokenPipe exception can be caught to perform cleanup actions immediately before termination, like returning a result or yielding additional values.

data MaskState Source

Type of action in the base monad.

Constructors

Masked

Action to be run with asynchronous exceptions masked.

Unmasked

Action to be run with asynchronous exceptions unmasked.

Low level primitives

These functions can be used to implement exception-handling combinators. For normal use, prefer the functions defined in Exception.

throwP :: Monad m => SomeException -> Pipe a b m rSource

Throw an exception within the Pipe monad.

catchP :: Monad m => Pipe a b m r -> (SomeException -> Pipe a b m r) -> Pipe a b m rSource

Catch an exception within the pipe monad.

liftP :: Monad m => MaskState -> m r -> Pipe a b m rSource

Execute an action in the base monad with the given MaskState.