Safe Haskell | Safe-Inferred |
---|
This module remains as a wistful reminder of this library's humble origins.
This library now builds upon the more general Proxy
type, but still keeps
the pipes
name. Read Control.Proxy.Tutorial to learn about this new
implementation.
The Pipe
type is a monad transformer that enriches the base monad with the
ability to await
or yield
data to and from other Pipe
s.
- data Pipe a b m r
- type Producer b m r = Pipe () b m r
- type Consumer a m r = Pipe a C m r
- type Pipeline m r = Pipe () C m r
- await :: Pipe a b m a
- yield :: b -> Pipe a b m ()
- pipe :: Monad m => (a -> b) -> Pipe a b m r
- (<+<) :: Monad m => Pipe b c m r -> Pipe a b m r -> Pipe a c m r
- (>+>) :: Monad m => Pipe a b m r -> Pipe b c m r -> Pipe a c m r
- idP :: Monad m => Pipe a a m r
- newtype PipeC m r a b = PipeC {}
- runPipe :: Monad m => Pipe () b m r -> m r
Types
The Pipe
type is strongly inspired by Mario Blazevic's Coroutine
type in
his concurrency article from Issue 19 of The Monad Reader.
The base type for pipes
-
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
Create Pipes
yield
and await
are the only two primitives you need to create pipes.
Since Pipe a b m
is a monad, you can assemble yield
and await
statements using ordinary do
notation. Since Pipe a b
is also a monad
transformer, you can use lift
to invoke the base monad. For example, you
could write a pipe stage that requests permission before forwarding any
output:
check :: (Show a) => Pipe a a IO r check = forever $ do x <- await lift $ putStrLn $ "Can '" ++ (show x) ++ "' pass?" ok <- read <$> lift getLine when ok (yield x)
Wait for input from upstream.
await
blocks until input is available from upstream.
pipe :: Monad m => (a -> b) -> Pipe a b m rSource
Convert a pure function into a pipe
pipe f = forever $ do x <- await yield (f x)
Compose Pipes
Pipe
s form a Category
, meaning that you can compose Pipe
s using
(>+>
) and also define an identity Pipe
: idP
. These satisfy the
category laws:
idP >+> p = p p >+> idP = p (p1 >+> p2) >+> p3 = p1 >+> (p2 >+> p3)
(p1 >+> p2)
satisfies all await
s in p2
with yield
s in p1
. If any
Pipe
terminates the entire Pipeline
terminates.
(>+>) :: Monad m => Pipe a b m r -> Pipe b c m r -> Pipe a c m rSource
Corresponds to (>>>
) from Control.Category