Safe Haskell | Safe-Infered |
---|
- data Pipe a b m r
- = Pure r (Finalizer m)
- | Throw SomeException (Finalizer m)
- | Await (a -> Pipe a b m r) (SomeException -> Pipe a b m r)
- | M MaskState (m (Pipe a b m r)) (SomeException -> Pipe a b m r)
- | Yield b (Pipe a b m r) (Finalizer m)
- type Producer b m = Pipe () b m
- type Consumer a m = Pipe a Void m
- type Pipeline m = Pipe () Void m
- data Void
- await :: Monad m => Pipe a b m a
- yield :: Monad m => b -> Pipe a b m ()
- masked :: Monad m => m r -> Pipe a b m r
- pipe :: Monad m => (a -> b) -> Pipe a b m r
- idP :: Monad m => Pipe a a m r
- discard :: Monad m => Pipe a b m r
- (>+>) :: Monad m => Pipe a b m r -> Pipe b c m r -> Pipe a c m r
- (<+<) :: Monad m => Pipe b c m r -> Pipe a b m r -> Pipe a c m r
- runPipe :: MonadBaseControl IO m => Pipeline m r -> m r
- runPurePipe :: Monad m => Pipeline m r -> m (Either SomeException r)
- runPurePipe_ :: Monad m => Pipeline m r -> m r
- data BrokenPipe
- data MaskState
- throwP :: Monad m => SomeException -> Pipe a b m r
- catchP :: Monad m => Pipe a b m r -> (SomeException -> Pipe a b m r) -> Pipe a b m r
- liftP :: Monad m => MaskState -> m r -> Pipe a b m r
Types
The base type for pipes.
a
- The type of input received fom upstream pipes.
b
- The type of output delivered to downstream pipes.
m
- The base monad.
r
- The type of the monad's final result.
Pure r (Finalizer m) | |
Throw SomeException (Finalizer m) | |
Await (a -> Pipe a b m r) (SomeException -> Pipe a b m r) | |
M MaskState (m (Pipe a b m r)) (SomeException -> Pipe a b m r) | |
Yield b (Pipe a b m r) (Finalizer m) |
Primitives
await
and yield
are the two basic primitives you need to create
Pipe
s. Because Pipe
is a monad, you can assemble them using ordinary
do
notation. Since Pipe
is also a monad trnasformer, you can use
lift
to invoke the base monad. For example:
check :: Pipe a a IO r check = forever $ do x <- await lift $ putStrLn $ "Can " ++ show x ++ " pass?" ok <- lift $ read <$> getLine when ok $ yield x
Basic combinators
pipe :: Monad m => (a -> b) -> Pipe a b m rSource
Convert a pure function into a pipe.
pipe = forever $ do x <- await yield (f x)
(>+>) :: Monad m => Pipe a b m r -> Pipe b c m r -> Pipe a c m rSource
Left to right pipe composition.
(<+<) :: Monad m => Pipe b c m r -> Pipe a b m r -> Pipe a c m rSource
Right to left pipe composition.
Running pipes
runPipe :: MonadBaseControl IO m => Pipeline m r -> m rSource
runPurePipe :: Monad m => Pipeline m r -> m (Either SomeException r)Source
Run a self-contained pipeline over an arbitrary monad, with fewer
exception-safety guarantees than runPipe
.
Only pipe termination exceptions and exceptions thrown using
throw
will be catchable within the Pipe
monad.
Any other exception will terminate execution immediately and finalizers will
not be called.
Any captured exception will be returned in the left component of the result.
runPurePipe_ :: Monad m => Pipeline m r -> m rSource
A version of runPurePipe
which rethrows any captured exception instead
of returning it.
Low level types
data BrokenPipe Source
The BrokenPipe
exception is used to signal termination of the
upstream portion of a Pipeline
before the current pipe
A BrokenPipe
exception can be caught to perform cleanup actions
immediately before termination, like returning a result or yielding
additional values.
Type of action in the base monad.
Low level primitives
These functions can be used to implement exception-handling combinators.
For normal use, prefer the functions defined in Exception
.