| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Control.Pipe.Final
Contents
- type Prompt p a b m r = p a b m (p () b m r)
- type Ensure a b m r = Pipe (Maybe a) (m (), b) m r
- newtype Frame a b m r = Frame {}
- type Stack = Frame () Void
- yieldF :: Monad m => b -> Ensure a b m ()
- awaitF :: Monad m => Ensure a b m a
- close :: Monad m => Ensure () b m r -> Ensure a b m (Ensure () b m r)
- bindClosed :: Monad m => Frame a b m r1 -> (r1 -> Ensure () b m r2) -> Frame a b m r2
- reopen :: Monad m => Frame a b m r -> Ensure a b m r
- catchP :: Monad m => m () -> Ensure a b m r -> Ensure a b m r
- finallyP :: Monad m => m () -> Ensure a b m r -> Ensure a b m r
- (<-<) :: Monad m => Frame b c m r -> Frame a b m r -> Frame a c m r
- (>->) :: Monad m => Frame a b m r -> Frame b c m r -> Frame a c m r
- idF :: Monad m => Frame a a m r
- newtype FrameC m r a b = FrameC {}
- runFrame :: Monad m => Stack m r -> m r
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
Framewhen 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
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 x2yieldF :: Monad m => b -> Ensure a b m () Source #
Like yield, but also yields an empty finalizer alongside the value
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 x2If 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!
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 x2catchP :: 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.
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..]
When a Frame terminates, the FrameC category strictly orders the
finalizers from upstream to downstream. Specifically:
- When any
Framecloses its input end, it finalizes allFrames upstream of it. These finalizers are ordered from upstream to downstream. - A
Frameis responsible for finalizing its own resources under ordinary operation (either manually, or usingfinallyP). - When a
Frameterminates, 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 yourStack. - You can reason about the finalization behavior of each
Frameindependently of otherFrames it is composed with.
(>->) :: Monad m => Frame a b m r -> Frame b c m r -> Frame a c m r Source #
Corresponds to (>>>) from Control.Category
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.