tubes-0.2.2.1: Effectful, iteratee-inspired stream processing based on a free monad.

Safe HaskellSafe
LanguageHaskell2010

Tubes.Pump

Synopsis

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)
   

Pumps are still being investigated by the author so if you come up with something interesting, please share!

data PumpF a b k Source

Constructors

PumpF 

Fields

recvF :: (a, k)
 
sendF :: b -> k
 

Instances

pump :: Comonad w => w a -> (w a -> (b, w a)) -> (w a -> c -> w a) -> Pump b c w a Source

Creates a Pump for a Tube using a comonadic seed value, a function to give it more data upon request, and a function to handle any yielded results.

Values received from the Tube may be altered and sent back into the tube, hence this mechanism does act like something of a pump.

recv :: Comonad w => Pump a b w r -> (a, Pump a b w r) Source

Pull a value from a Pump, along with the rest of the Pump.

send :: Comonad w => Pump a b w r -> b -> Pump a b w r Source

Send a value into a Pump, effectively re-seeding the stream.

runPump :: (Comonad w, Monad m) => (x -> y -> r) -> Pump a b w x -> Tube a b m y -> m r Source

Given a suitably matching Tube and Pump, you can use the latter to execute the former.