pipes-3.2.0: Compositional pipelines

Safe HaskellSafe-Inferred

Control.Proxy.Pipe

Contents

Description

This module provides an API similar to Control.Pipe for those who prefer the classic Pipe API.

This module differs slightly from Control.Pipe in order to promote seamless interoperability with both pipes and proxies. See the "Upgrade Pipes to Proxies" section below for details.

Synopsis

Create Pipes

await :: (Monad m, Proxy p) => Pipe p a b m aSource

Wait for input from upstream

await blocks until input is available from upstream.

yield :: (Monad m, Proxy p) => b -> p a' a b' b m b'Source

Deliver output downstream

yield restores control back downstream and binds its value to await.

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

Convert a pure function into a pipe

Compose Pipes

(<+<) :: (Monad m, Proxy p) => p b' b c' c m r -> p a' a b' b m r -> p a' a c' c m rSource

Corresponds to (<<<)/(.) from Control.Category

(>+>) :: (Monad m, Proxy p) => p a' a b' b m r -> p b' b c' c m r -> p a' a c' c m rSource

Corresponds to (>>>) from Control.Category

idP :: (Monad m, Proxy p) => Pipe p a a m rSource

Corresponds to id from Control.Category

Synonyms

type Pipeline p = p C () () CSource

A self-contained Pipeline that is ready to be run

Pipelines never request nor respond.

Run Pipes

The Control.Proxy.Core.Fast and Control.Proxy.Core.Correct modules provide their corresponding runPipe functions, specialized to their own Proxy implementations.

Each implementation must supply its own runPipe function since it is the only non-polymorphic Pipe function and the compiler uses it to select which underlying proxy implementation to use.

Upgrade Pipes to Proxies

You can upgrade classic Pipe code to work with the proxy ecosystem in steps. Each change enables greater interoperability with proxy utilities and transformers and if time permits you should implement the entire upgrade for your libraries if you want to take advantage of proxy standard libraries.

First, import Control.Proxy and Control.Proxy.Pipe instead of Control.Pipe. Then, add ProxyFast after every Pipe, Producer, or Consumer in any type signature. For example, you would convert this:

 import Control.Pipe

 fromList :: (Monad m) => [b] -> Producer b m ()
 fromList xs = mapM_ yield xs

... to this:

 import Control.Proxy
 import Control.Proxy.Pipe -- transition import

 fromList :: (Monad m) => [b] -> Producer ProxyFast b m ()
 fromList xs = mapM_ yield xs

The change ensures that all your code now works in the ProxyFast monad, which is the faster of the two proxy implementations.

Second, modify all your Pipes to take an empty () as their final argument, and translate the following functions:

  • (<+<) to (<-<)
  • runPipe to runProxy

For example, you would convert this:

 import Control.Proxy
 import Control.Proxy.Pipe

 fromList :: (Monad m) => [b] -> Producer ProxyFast b m ()
 fromList xs = mapM_ yield xs

... to this:

 import Control.Proxy
 import Control.Proxy.Pipe

 fromList :: (Monad m) => [b] -> () -> Producer ProxyFast b m ()
 fromList xs () = mapM_ yield xs

Now when you call these within a do block you must supplying an additional () argument:

 examplePipe () = do
     a <- request ()
     fromList [1..a] ()

This change lets you switch from pipe composition, (<+<), to proxy composition, (<-<), so that you can mix proxy utilities with pipes.

Third, wrap your pipe's implementation in runIdentityP (which Control.Proxy exports):

 import Control.Proxy
 import Control.Proxy.Pipe

 fromList xs () = runIdentityP $ mapM_ yield xs

Then replace the ProxyFast in the type signature with a type variable p constrained by the Proxy type class:

 fromList :: (Monad m, Proxy p) => [b] -> () -> Producer p b m ()

This change upgrades your Pipe to work natively within proxies and proxy transformers, without any manual conversion or lifting. You can now compose or sequence your Pipe within any feature set transparently.

Finally, replace each await with request () and each yield with respond. Also, replace every Pipeline with Session. This lets you drop the Control.Proxy.Pipe import:

 import Control.Proxy

 fromList :: (Monad m, Proxy p) => [b] -> () -> Producer p b m ()
 fromList xs () = runIdentityP $ mapM_ respond xs

Also, I encourage you to continue using the Pipe, Consumer and Producer type synonyms to simplify type signatures. The following examples show how they cleanly mix with proxies and their extensions:

 import Control.Proxy
 import Control.Proxy.Trans.Either as E
 import Control.Proxy.Trans.State

 -- A Producer enriched with pipe-local state
 example1 :: (Monad m, Proxy p) => () -> Producer (StateP Int p) Int m r
 example1 () = forever $ do
     n <- get
     respond n
     put (n + 1)

 -- A Consumer enriched with error-handling
 example2 :: (Proxy p) => () -> Consumer (EitherP String p) Int IO ()
 example2 () = do
     n <- request ()
     if (n == 0)
         then E.throw "Error: received 0"
         else lift $ print n