pipes-2.3.0: Compositional pipelines

Safe HaskellSafe
LanguageHaskell2010

Control.Proxy

Contents

Description

A Proxy requests input from upstream and responds with output to downstream.

For an extended tutorial, consult Control.Proxy.Tutorial.

Synopsis

Types

A Proxy communicates with an upstream interface and a downstream interface.

The type variables of Proxy req_a resp_a req_b resp_b m r signify:

  • req_a - The request supplied to the upstream interface
  • resp_a - The response provided by the upstream interface
  • req_b - The request supplied by the downstream interface
  • resp_b - The response provided to the downstream interface
  • m - The base monad
  • r - The final return value

data ProxyF a' a b' b x Source #

The base functor for the Proxy type

Constructors

Request a' (a -> x) 
Respond b (b' -> x) 

Instances

Functor (ProxyF a' a b' b) Source # 

Methods

fmap :: (a -> b) -> ProxyF a' a b' b a -> ProxyF a' a b' b b #

(<$) :: a -> ProxyF a' a b' b b -> ProxyF a' a b' b a #

type Proxy a' a b' b = FreeT (ProxyF a' a b' b) Source #

A Proxy converts one interface to another

type Server req resp = Proxy Void () req resp Source #

Server req resp receives requests of type req and sends responses of type resp.

Servers only respond and never request anything.

type Client req resp = Proxy req resp () Void Source #

Client req resp sends requests of type req and receives responses of type resp.

Clients only request and never respond to anything.

type Session = Proxy Void () () Void Source #

A self-contained Session, ready to be run by runSession

Sessions never request anything or respond to anything.

Build Proxies

Proxy forms both a monad and a monad transformer. This means you can assemble a Proxy using do notation using only request, respond, and lift:

truncate :: Int -> Int -> Proxy Int ByteString Int ByteString IO r
truncate maxBytes bytes = do
    when (bytes > maxBytes) $ lift $ putStrLn "Input truncated"
    bs <- request (min bytes maxBytes)
    bytes' <- respond bs
    truncate maxBytes bytes'

You define a Proxy as a function of its initial input (bytes in the above example), and subsequent inputs are bound by the respond command.

request :: Monad m => a' -> Proxy a' a b' b m a Source #

request input from upstream, passing an argument with the request

request a' passes a' as a parameter to upstream that upstream can use to decide what response to return. request binds the response to its return value.

respond :: Monad m => b -> Proxy a' a b' b m b' Source #

respond with an output for downstream and bind downstream's next request

respond b satisfies a downstream request by supplying the value b. respond blocks until downstream requests a new value and binds the argument from the next request as its return value.

Compose Proxies

Proxy defines a Category, where the objects are the interfaces and the morphisms are Proxys parametrized on their initial input.

(<-<) is composition and idT is the identity. The identity laws guarantee that idT is truly transparent:

idT <-< p = p

p <-< idT = p

... and the associativity law guarantees that Proxy composition does not depend on the grouping:

(p1 <-< p2) <-< p3 = p1 <-< (p2 <-< p3)

Note that in order to compose Proxys, you must write them as functions of their initial argument. All subsequent arguments are bound by the respond command. In other words, the actual composable unit is:

composable :: (Monad m) => b' -> Proxy a' a b' b m r

(<-<) :: Monad m => (c' -> Proxy b' b c' c m r) -> (b' -> Proxy a' a b' b m r) -> c' -> Proxy a' a c' c m r infixr 9 Source #

Compose two proxies, satisfying all requests from downstream with responses from upstream

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

(>->) :: Monad m => (b' -> Proxy a' a b' b m r) -> (c' -> Proxy b' b c' c m r) -> c' -> Proxy a' a c' c m r infixl 9 Source #

Compose two proxies, satisfying all requests from downstream with responses from upstream

Corresponds to (>>>) from Control.Category

idT :: Monad m => a' -> Proxy a' a a' a m r Source #

idT acts like a 'T'ransparent Proxy, passing all requests further upstream, and passing all responses further downstream.

Corresponds to id from Control.Category

Run Sessions

runSession ensures that the Proxy passed to it does not have any open responses or requests. This restriction makes runSession less polymorphic than it could be, and I settled on this restriction for four reasons:

  • It prevents against accidental data loss.
  • It protects against silent failures
  • It prevents wastefully draining a scarce resource by gratuitously driving it to completion
  • It encourages an idiomatic programming style where unfulfilled requests or responses are satisfied in a structured way using composition.

If you believe that loose requests or responses should be discarded or ignored, then you can explicitly ignore them by using discard (which discards all responses), and ignore (which ignores all requests):

runSession $ discard <-< p <-< ignore

runSession :: Monad m => (() -> Session m r) -> m r Source #

Run a self-contained Session, converting it back to the base monad

Utility functions

discard provides a fallback Client that gratuitously requests input from a Server, but discards all responses.

ignore provides a fallback Server that trivially responds with output to a Client, but ignores all request parameters.

Use foreverK to abstract away the following common pattern:

p a = do
    ...
    a' <- respond b
    p a'

Using foreverK, you can avoid the manual recursion:

p = foreverK $ \a -> do
    ...
    respond b

discard :: Monad m => () -> Client () a m r Source #

Discard all responses

ignore :: Monad m => a -> Server a () m r Source #

Ignore all requests

foreverK :: Monad m => (a -> m a) -> a -> m b Source #

Compose a 'K'leisli arrow with itself forever

Pipe compatibility

The following definitions are drop-in replacements for their Pipe equivalents. Consult Control.Pipe and Control.Pipe.Tutorial for more extensive documentation.

type Pipe a b = Proxy () a () b Source #

The type variables of Pipe a b m r signify:

  • a - The type of input received from upstream pipes
  • b - The type of output delivered to downstream pipes
  • m - The base monad
  • r - The type of the return value

type Producer b = Pipe () b Source #

A pipe that produces values

type Consumer a = Pipe a Void Source #

A pipe that consumes values

type Pipeline = Pipe () Void Source #

A self-contained pipeline that is ready to be run

await :: Monad m => Pipe a b m a Source #

Wait for input from upstream

await blocks until input is available

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

Deliver output downstream

yield restores control back downstream and binds the result to await.

pipe :: Monad m => (a -> b) -> Pipe a b m r Source #

Convert a pure function into a pipe

(<+<) :: Monad m => Pipe b c m r -> Pipe a b m r -> Pipe a c m r infixr 9 Source #

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

(>+>) :: Monad m => Pipe a b m r -> Pipe b c m r -> Pipe a c m r infixl 9 Source #

Corresponds to (>>>) from Control.Category

idP :: Monad m => Pipe a a m r Source #

Corresponds to id from Control.Category

runPipe :: Monad m => Pipeline m r -> m r Source #

Run the Pipe monad transformer, converting it back to the base monad