pipes-2.5.0: Compositional pipelines

Safe HaskellSafe
LanguageHaskell98

Control.Frame

Contents

Description

Frames extend Pipes with:

  • The ability to fold input
  • Prompt and deterministic finalization

Frames differ from Pipes because they form restricted monads rather than forming ordinary monads. This means you must rebind do notation to use restricted monads from the index-core package. See the "Create Frames" section for details. For even more details, consult the index-core package.

Synopsis

Types

The first step to convert Pipe code to Frame code is to translate the types. All types of the form "Pipe a b m r" become "Frame b m (M a) C r". For example, given the following type signatures from the tutorial:

printer  :: (Show a) => Pipe b C IO r
take'    :: Int -> Pipe b b IO ()
fromList :: (Monad m) => [b] -> Pipe () b m ()

... you would replace them with:

printer  :: (Show a) => Frame C IO (M a) C r
take'    :: Int -> Frame a IO (M a) C ()
fromList :: (Monad m) => [a] -> Frame a m (M ()) C ()
-- To use the finalization example, change fromList's base monad to 'IO'
fromList :: [a] -> Frame a IO (M ()) C ()

data C Source #

The empty type, denoting a 'C'losed end

data O a Source #

Index representing an open input end, receiving values of type a

type M a = O (Maybe a) Source #

Index representing an open input end, receiving values of type Maybe a

data FrameF b x i where Source #

Base functor for a pipe that can close its input end

  • b - Output type
  • x - Next step
  • i - Current step's index

Constructors

Yield :: b -> x i -> FrameF b x i 
Await :: (a -> x (O a)) -> FrameF b x (O a) 
Close :: x C -> FrameF b x (O a) 

Instances

IFunctor * * (FrameF b) Source # 

Methods

fmapI :: (FrameF b :-> a) b -> (k1 :-> f a) (f b) #

type Frame b m i j r = IFreeT (FrameF (m (), b)) (U m) (r := j) i Source #

A Frame is like a Pipe with an indexed input end:

  • b - The type of the Frames output
  • m - The base monad
  • i - The initial index of the input end (Open or Closed)
  • j - The final index of the input end (Open or Closed)
  • r - The return value

type Stack m r = Frame C m (M ()) C r Source #

A self-contained Frame that is ready to be run

Create Frames

The second step to convert Pipe code to Frame code is to change your module header to:

{-# LANGUAGE RebindableSyntax #-}

import Control.IMonad.Do
import Control.Frame
import Prelude hiding (Monad(..))

Control.Frame replaces all Pipe awaits and yields with their corresponding Frame counterparts. Control.IMonad.Do rebinds do notation to work with restricted monads, which also requires using the RebindableSyntax extension and hiding the Monad class from the Prelude.

You also must use the restricted monad utility functions, which have the same name as their ordinary monad counterparts except with an 'R' suffix, such as foreverR instead of forever. Finally, you must use liftU instead of lift to invoke operations in the base monad.

Finally, every terminating Frame must be closed exactly once before being passed to composition.

printer = foreverR $ do
    a <- await
    liftU $ print a

take' n = do
    replicateMR_ n $ do
        a <- await
        yield a
    close
    liftU $ putStrLn "You shall not pass!"

fromList xs = do
    close
    mapMR_ yield xs

Primitives

yieldF guards against downstream termination by yielding the most up-to-date finalization alongside each value, so that downstream can call that finalizer if it terminates before requesting another value.

awaitF intercepts upstream termination by returning a Nothing if upstream terminates before providing a value. Further attempts to request input from upstream will terminate the current Frame using the return value provided from upstream.

While awaitF is useful for folds, yieldF is less useful for end-users of this library and the higher-order catchF / finallyF finalization functions are much more user-friendly.

Composing two Frames requires that each Frame invokes close exactly once. Anything else will not type-check. Leave out the close statement when writing library components and let the person assembling the components for composition specify where the close goes.

The earlier you close the upstream Frame, the earlier it is finalized. However, once you close it you may no longer await.

yieldF :: Monad m => m () -> b -> Frame b m i i () Source #

Yield the most current finalizer for this Frame alongside the value

awaitF :: Monad m => Frame b m (M a) (M a) (Maybe a) Source #

Await a value from upstream, returning Nothing if upstream terminates

close :: Monad m => Frame b m (M a) C () Source #

Close the input end, calling the finalizers of every upstream Frame

Pipe-like primitives

The following Pipe-like primitives are built on top of the Frame primitives. They behave identically to their Pipe counterparts and can be used as drop-in replacements for them.

yield :: Monad m => b -> Frame b m i i () Source #

yield a value upstream alongside an empty finalizer

await :: Monad m => Frame b m (M a) (M a) a Source #

await a value from upstream and terminate if upstream terminates

Finalize Frames

The third (and optional) step to convert Pipe code to Frame code is to register finalizers for your Frame. These finalizers may be arbitrarily nested:

printer = foreverR $ catchF (putStrLn "printer interrupted") $ do
    a <- await
    liftU $ print a

take' n = finallyF (putStrLn "You shall not pass!") $ do
    replicateMR_ n $ do
        a <- catchF (putStrLn "take' interrupted") await
        yield a
    close

fromList xs = catchF (putStrLn "fromList interrupted") $ do
    close
    mapMR_ yield xs

These convenience functions register block-level finalizers to be called if another Frame terminates first. The naming conventions are:

  • "catch" functions (i.e. catchD / catchF) call the finalizer only if another Frame terminates before the block completes, but will not call the finalizer if the block terminates normally.
  • "finally" functions (i.e. finallyD / finallyF) are like "catch" functions except that they also call the finalizer if the block terminates normally.
  • Functions that end in a 'D' suffix (i.e. catchD / finallyD) only guard against downstream termination.
  • Functions that end in a 'F' suffix (i.e. catchF / finallyF) guard against termination in both directions. You usually want these ones.

Note that finalization blocks that begin after the close statement may only use the 'D'-suffixed version as upstream has been closed off. This is a consequence of a deficiency in Haskell's type system that will take time to work around. However an 'F'-suffixed block that begins before a close statement may continue through it normally. So, for code blocks after a close statement, use catchD / finallyD, otherwise use catchF / finallyF. In future releases, the 'D'-suffixed versions will be removed and merged into the 'F'-suffixed versions.

catchD :: Monad m => m () -> Frame b m i j r -> Frame b m i j r Source #

catchD m p calls the finalizer m if a downstream Frame terminates before p finishes.

catchF :: Monad m => m () -> Frame b m (M a) j r -> Frame b m (M a) j r Source #

catchF m p calls the finalizer m if any Frame terminates before p finishes.

finallyD :: Monad m => m () -> Frame b m i j r -> Frame b m i j r Source #

finallyD m p calls the finalizer m if a downstream Frame terminates before p finishes or if p completes normally.

finallyF :: Monad m => m () -> Frame b m (M a) j r -> Frame b m (M a) j r Source #

finallyF m p calls the finalizer m if any Frame terminates before p finishes or if p completes normally.

Compose Frames

The fourth step to convert Pipe code to Frame code is to replace (<+<) with (<-<):

printer <-< take' 3 <-< fromList [1..]

Like Pipes, Frames form a Category where composition pipes the output from the upstream Frame to the input of the downstream Frame. Additionally, composition guarantees the following behaviors:

  • Frames receive exactly one Nothing if an upstream Frame terminates.
  • Registered finalizers get called exactly once if a downstream Frame terminates.
  • Finalizers are always ordered from upstream to downstream.

The Category laws cannot be broken, so you don't have to be careful when using Frames.

Note that you may only compose Frames that begin open and end closed.

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

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

(>->) :: Monad m => Frame b m (M a) C r -> Frame c m (M b) C r -> Frame c m (M a) C r infixr 9 Source #

Corresponds to (>>>) from Control.Category

idF :: Monad m => Frame a m (M a) C r Source #

Corresponds to id from Control.Category

newtype FrameC m r a b Source #

Frames form a Category instance when you rearrange the type variables

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 fifth step to convert Pipe code to Frame code is to use runFrame instead of runPipe:

>>> runFrame $ printer <-< take' 3 <-< fromList [1..]
1
2
3
fromList interrupted
You shall not pass!
printer interrupted
>>> runFrame $ printer <-< take' 3 <-< fromList [1]
1
You shall not pass!
take' interrupted
printer interrupted

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

Run the Frame monad transformer, converting it back to the base monad.

runFrame is the Frame equivalent to runPipe and requires a self-contained Stack.