| Safe Haskell | Trustworthy |
|---|---|
| Language | Haskell2010 |
Tubes.Channel
Documentation
A Channel m a b is a stream processor which converts values of type a into
values of type b, while also performing side-effects in some monad m.
If a Channel yields exactly once after each time it awaits then it may be
safely treated as an Arrow. For example:
{-# LANGUAGE Arrows #-}
import Tubes
import Control.Arrow
import Prelude hiding (map)
-- A simple channel which accumulates a total
total :: (Num a, Monad m) => Channel m a a
total = Channel $ loop 0 where
loop acc = do
n <- await
let acc' = n + acc
yield acc'
loop acc'
-- A running average using two totals in parallel
avg :: (Fractional a, Monad m) => Channel m a a
avg = proc value -> do
t <- total -< value
n <- total -< 1
returnA -< t / n
main :: IO ()
main = runTube $ each [0,10,7,8]
>< tune avg
>< map show
>< pour display
This program would output
0.0
5.0
5.666666666666667
6.25
This has interesting potential in FRP applications.
tee :: Monad m => Sink m a -> Channel m a a Source
Convert a 'Sink m a' into a 'Channel m a a', re-forwarding values downstream.
Useful example:
import Data.Semigroup
writeToFile :: Sink IO String
writeToFile = Sink $ do
line <- await
liftIO . putStrLn $ "Totally writing this to a file: " ++ line
writeToConsole :: Sink IO String
writeToConsole = Sink $ do
line <- await
liftIO . putStrLn $ "Console out: " ++ line
writeOut :: Channel IO String String
writeOut = tee $ writeToFile <> writeToConsole
main :: IO ()
main = runTube $ each ["a","b","c"] >< forever (tune writeOut) >< pour display
-- Totally writing this to a file: a
-- Console out: a
-- a
-- Totally writing this to a file: b
-- Console out: b
-- b
-- Totally writing this to a file: c
-- Console out: c
-- c
This takes advantage of the divisible nature of Sinks to merge effectful
computations and then continue the process.