Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
- type Pump a b = CofreeT (PumpF a b)
- data PumpF a b k = PumpF {}
- pump :: Comonad w => w a -> (w a -> (b, w a)) -> (w a -> c -> w a) -> Pump b c w a
- recv :: Comonad w => Pump a b w r -> (a, Pump a b w r)
- send :: Comonad w => Pump a b w r -> b -> Pump a b w r
- runPump :: (Comonad w, Monad m) => (x -> y -> r) -> Pump a b w x -> Tube a b m y -> m r
Documentation
type Pump a b = CofreeT (PumpF a b) Source
A Pump
is the dual to a Tube
: where a Tube
is a computation manipulating
a stream of values, a Pump
can be situated on either end of a tube to both
insert values when requested and handle any yielded results.
One interesting use of a Pump
is to feed data to a Tube
, collecting the
result as well as unused input:
import Data.Functor.Identity
p :: [a] -> Pump (Maybe a) x Identity [a]
p inp = pump (return inp)
(wa -> case (extract wa) of
[] -> (Nothing, wa)
x:xs -> (Just x, return xs))
const
-- a Sink
that stops after 5 loops, or when input is exhausted
add5 :: Sink (Maybe Int) IO Int
add5 = loop 0 5 where
loop acc ct = if 0 == ct
then return acc
else do
mn <- await
maybe (return acc)
(n -> loop (acc+n) (ct - 1))
mn
result :: IO ([Int], Int)
result = runPump (curry id) (p [1..10]) add5
-- ([6,7,8,9,10],15)
Pump
s are still being investigated by the author so if you come up with
something interesting, please share!