Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
- type Pump a b = CofreeT (PumpF a b)
- data PumpF a b k = PumpF {}
- mkPump :: 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 => b -> Pump a b w r -> Pump a b w r
- pump :: (Comonad w, Monad m) => (x -> y -> r) -> Pump a b w x -> Tube a b m y -> m r
- pumpM :: (Comonad w, Monad m) => (x -> y -> r) -> Pump a b w (m x) -> Tube a b m y -> m r
- meta :: (x -> a -> x) -> x -> (x -> (b, x)) -> Pump b a Identity x
- enumerator :: [a] -> Pump (Maybe a) a Identity [a]
- enumerate :: (Monad m, Comonad w) => Pump (Maybe a) b w r -> Tube c a m ()
Documentation
type Pump a b = CofreeT (PumpF a b) Source
A Pump
is the dual to a Tube
. Intuitively, if a Tube
is a stream-
processing computation, then a Pump
is both a stream generator and reducer.
Examples may help!
One interesting use of a Pump
is as a data stream, which can be fed into a
Tube
or Sink
.
import Data.Functor.Identity e :: Pump (Maybe Int) Int Identity Int e = mkPump (Identity 0) ((Identity x) -> (Just x, Identity (x+1))) const ex1 :: IO () ex1 = do run $ each e >10show< display -- displays 0-9 in the console
A Pump
may also be used to fold a Source
. Indeed, a Pump
may be thought
of as both a non-recursive left fold and a non-recursive unfold paired
together. (This is called a "metamorphism," hence the function "meta".)
num_src :: Source Int IO () num_src = do forM_ [1..] $ n -> do lift . putStrLn $ "Yielding " ++ (show n) yield n enum_ex :: IO () enum_ex = do v <- reduce (flip send) (meta (+) 0 (x -> (x,x))) extract $ num_src >< take 5 putStrLn . show $ "v = " ++ (show v) -- v = 15
The following is an example of a Pump
both accumulating values from a
Source
and then enumerating them into a Sink
. This gives back both the
result of the computation and the unused input.
import Data.Functor.Identity
-- a Sink
that stops after 5 loops, or when input is exhausted
sum_snk :: Sink (Maybe Int) IO Int
sum_snk = do
ns <- forM [1,2,3,4,5] $ _ -> do
mn <- await
case mn of
Just n -> return [n]
Nothing -> return []
return $ sum . concat $ ns
source_sink_ex :: IO ([Int], Int)
source_sink_ex = do
e <- reduce (flip send) (enumerator []) id $ num_src >< take 10
(unused, total) <- pump (,) e sum_snk
putStrLn $ "Total: " ++ (show total)
putStrLn $ "Unused: " ++ (show unused)
-- "Total: 15"
-- "Unused: [6,7,8,9,10]"
Note that when a Pump
and a Tube
are combined with pump
, that the Tube
determines control flow. Pump
s are comonads, not monads.
There are doubtless more and more interesting examples of combining Tube
s
and Pump
s. If you think of any, drop the author a line!
send :: Comonad w => b -> Pump a b w r -> Pump a b w r Source
Send a value into a Pump
, effectively re-seeding the stream.
pumpM :: (Comonad w, Monad m) => (x -> y -> r) -> Pump a b w (m x) -> Tube a b m y -> m r Source
A variant of pump
which allows effects to be executed inside the pump as well.
meta :: (x -> a -> x) -> x -> (x -> (b, x)) -> Pump b a Identity x Source
Takes a fold function, an initial value, and an unfold to produce a metamorphism. Can be used to change.