pipes-2.0.0: Compositional pipelines

Safe HaskellSafe
LanguageHaskell2010

Control.Pipe.Final

Contents

Synopsis

Introduction

A Frame is a higher-order type built on top of Pipe. It enables a richer composition with the ability to finalize resources in a manner that is:

  • Prompt: You can close resources when you no longer need input from them
  • Deterministic: Composition finalizes every Frame when one terminates

Frames differ from Pipes in that they do not form monads, but instead form parametrized monads. Unfortunately, parametrized monads are not mainstream in Haskell and require a ton of extensions along with a modified Prelude in order to recover do notation, so this first release of the Frame implementation essentially "in-lines" the parametrized monad by splitting it into two monads. Future releases will split off a version that takes advantage of parametrized monads for a much simpler underlying type and a significantly cleaner implementation.

Ordinary users should start at the section "Create Frames", but if you encounter weird type errors and want to understand them, then consult the "Types" section.

Types

type Prompt p a b m r = p a b m (p () b m r) Source #

An illustrative type synonym that demonstrates how Prompt finalization works

This type simulates a parametrized monad by breaking it up into two monads where the first monad returns the second one. The first monad permits any pipe code and the second monad only permits pipe code that doesn't need input.

For example if p = Pipe, the first monad becomes an ordinary Pipe and the second monad becomes a Producer:

Prompt Pipe a b m r = Pipe a b m (Pipe () b m r)

The pipe does not require input by the time it reaches the second block, meaning that the finalization machinery can safely finalize upstream resources the moment. The earlier you use close the input end, the more promptly you release upstream resources.

The finalization machinery also finalizes downstream pipes when the second monad terminates. I use this trick to ensure a strict ordering of finalizers from upstream to downstream.

I don't actually use the Prompt type synonym, since that would require newtyping everything, but I will reference it in documentation to clarify type signatures.

type Ensure a b m r = Pipe (Maybe a) (m (), b) m r Source #

A pipe type that Ensures deterministic finalization

The finalization machinery uses the input and output ends in different ways to finalize the pipe when another pipe terminates first.

If an upstream pipe terminates first, the current pipe will receive a Nothing once. This allows it to finalize itself and if it terminates then its return value takes precedence over upstream's return value. However, if it awaits again, it defers to upstream's return value and never regains control. You do not need to "rethrow" the Nothing (nor can you): composition takes care of this for you.

On the output end, the pipe must supply its most up-to-date finalizer alongside every value it yields downstream. This finalizer is guaranteed to be called if downstream terminates first. You do not need to relay upstream finalizers alongside the pipe's own finalizer (nor can you): composition takes care of this for you.

The combination of these two tricks allows a bidirectional guarantee of deterministic finalization that satisfies the Category laws.

newtype Frame a b m r Source #

A pipe type that combines Prompt and Ensure to enable both prompt and deterministic finalization.

The name connotes a stack frame, since finalized pipes can be thought of as forming the Category of stack frames, where upstream finalization is equivalent to finalizing the heap, and downstream finalization is equivalent to throwing an exception up the stack.

The type is equivalent to:

type Frame a b m r = Prompt Ensure a b m r

Constructors

Frame 

Fields

Instances

Monad m => Functor (Frame a b m) Source # 

Methods

fmap :: (a -> b) -> Frame a b m a -> Frame a b m b #

(<$) :: a -> Frame a b m b -> Frame a b m a #

type Stack = Frame () Void Source #

A Stack is a Frame that doesn't need input and doesn't generate output

Create Frames

The first step to convert Pipe code to Frame code is to replace all yields with yieldFs and all awaits with awaitFs.

contrived = do   -->  contrived = do
    x1 <- await  -->      x1 <- awaitF
    yield x1     -->      yieldF x1
    x2 <- await  -->      x2 <- awaitF
    yield x2     -->      yieldF x2

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

Like yield, but also yields an empty finalizer alongside the value

awaitF :: Monad m => Ensure a b m a Source #

Like await, but ignores all Nothings and just awaits again

Prompt Finalization

The second step to convert Pipe code to Frame code is to mark the point where your Pipe no longer awaits by wrapping it in the close function and then wrapping the Pipe in a Frame newtype:

contrived :: (Monad m) => Frame a a m ()
contrived = Frame $ do
    x1 <- awaitF
    yieldF x1
    x2 <- awaitF
    close $ yieldF x2

If a non-terminating pipe demands input indefinitely, there is no need to close it. It will type-check if the return value is polymorphic as a result of non-termination.

close :: Monad m => Ensure () b m r -> Ensure a b m (Ensure () b m r) Source #

Use this to mark when a Frame no longer requires input. The earlier the better!

bindClosed :: Monad m => Frame a b m r1 -> (r1 -> Ensure () b m r2) -> Frame a b m r2 Source #

Use this to bind to the closed half of the Frame if you want to continue where it left off but you still don't require input.

This function would not be necessary if Prompt were implemented as a parametrized monad, so if it seems ugly, that's because it is.

reopen :: Monad m => Frame a b m r -> Ensure a b m r Source #

Use this to reopen a Frame if you change your mind and decide you want to continue to await input after all.

This postpones finalization of upstream until you close the input end again.

Ensure Finalization

The third (optional) step to convert Pipe code to Frame code is to use catchP or finallyP to register finalizers for blocks of code.

contrived :: Frame a a IO ()
contrived = Frame $ do
    catchP (putStrLn "Stage 1 interrupted") $ do
        x1 <- awaitF
        catchP (putStrLn "Stage 1(b) interrupted") $ yieldF x1
    catchP (putStrLn "Stage 2 interrupted") $ do
        x2 <- awaitF
        close $ yieldF x2

catchP :: Monad m => m () -> Ensure a b m r -> Ensure a b m r Source #

catchP m p registers m to be called only if another composed pipe terminates before p is done.

finallyP :: Monad m => m () -> Ensure a b m r -> Ensure a b m r Source #

finallyP is like catchP except that it also calls the finalizer if p completes normally.

Compose Frames

The fourth step to convert Pipe code to Frame code is to use (<-<) to compose Frames instead of (<+<).

printer  :: Frame a Void IO r
fromList :: (Monad m) => [a] -> Frame () a m ()

p :: Stack IO ()
p = printer <-< contrived <-< fromList [1..]

Similarly, idF replaces idP.

When a Frame terminates, the FrameC category strictly orders the finalizers from upstream to downstream. Specifically:

  • When any Frame closes its input end, it finalizes all Frames upstream of it. These finalizers are ordered from upstream to downstream.
  • A Frame is responsible for finalizing its own resources under ordinary operation (either manually, or using finallyP).
  • When a Frame terminates, everything downstream of it is finalized. These finalizers are ordered from upstream to downstream.

The Category instance for FrameC provides the same strong guarantees as the Lazy category. This confers many practical advantages:

  • Finalizers are never duplicated or dropped in corner cases.
  • The grouping of composition will never affect the ordering or behavior of finalizers.
  • Finalization does not grow more complex the more Frames you add in your Stack.
  • You can reason about the finalization behavior of each Frame independently of other Frames it is composed with.

(<-<) :: Monad m => Frame b c m r -> Frame a b m r -> Frame a c m r Source #

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

(>->) :: Monad m => Frame a b m r -> Frame b c m r -> Frame a c m r Source #

Corresponds to (>>>) from Control.Category

idF :: Monad m => Frame a a m r Source #

Corresponds to id from Control.Category

newtype FrameC m r a b Source #

Constructors

FrameC 

Fields

Instances

Monad m => Category * (FrameC m r) Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

Run Frames

The final step to convert Pipe code to Frame code is to replace runPipe with runFrame.

printer  :: Frame a Void IO r
take     :: (Monad m) => Int -> Frame a a m ()
fromList :: (Monad m) => [a] -> Frame () a m ()
>>> runFrame $ printer <-< contrived <-< fromList [1..]
1
2
>>> runFrame $ printer <-< contrived <-< fromList [1]
1
Stage 2 interrupted
>>> runFrame $ printer <-< take 1 <-< contrived <-< fromList [1..]
Stage 1(b) interrupted
Stage 1 interrupted
1

For the last example, remember that take is written to close its input end before yielding its final value, which is why the finalizers run before printer receives the 1.

runFrame :: Monad m => Stack m r -> m r Source #

Convert a Frame back to the base monad.