I'm Haskell beginner and newbie in Streaming library (https://hackage.haskell.org/package/streaming) as fastest and (I'm hope) simplest stream library. I'm trying to make next common and popular "pattern": processing of stream items with common state, see Fig, please:
.--state-------+--state'--------+--state''-->
| | |
[e0..eN] ==> [e0'...eN'] ==> [e0''..eN''] =====>
This "state" will be used for statistics, errors, whatever - through the whole workflow. Some of "pipe" nodes will iterate over eN
items (which will be lists/streams too), concatenates results... How this can be achieved with Streaming library? I mean each "node" should have access to stream items but to "global" state too. Also nodes will do IO actions! I tried to use return of "node" as state (second component in Stream's pair): stream is monad, so do e <- stream
binds one of returning values to e
, but this does not look very rightly...
One of my attempts is:
{-# LANGUAGE FlexibleContexts #-}
module Main where
import Control.Monad
import Control.Monad.Writer
import Data.Functor.Identity
import Streaming
import qualified Streaming.Prelude as S
type R = Writer [String] ()
gen :: S.Stream (S.Of Int) IO R
gen = do
S.yield 1000
S.yield 2000
-- lift $ putStr "enter x: " -- ERROR: shown after input!!!
x <- lift getLine
let n = read x::Int
S.yield n
return $ do
tell ["genErr1"]
tell ["genErr2"]
proc1 :: S.Stream (S.Of Int) IO R -> S.Stream (S.Of Int) IO R
proc1 str = loop str
where
loop str = do
e <- lift $ S.next str
e' <- case e of
Left err -> return err
Right (e', str') -> (S.yield $ e' + 123) >> loop str'
return $ do
tell ["proc1Err1"]
tell ["proc1Err2"]
main :: IO ()
main = do
p <- S.mapM_ print $ proc1 gen
putStr "p: " >> print p
where I use "Write"-monad as return value (to save there my logs/statistics)...
So, I want to process with proc1
stream items getting from gen
and to have at the end some state global for all pipe where will be "genErr1", "genErr2", "proc1Err1", "proc1Err2" (they simulate errors occuring while process stream's items). How to achieve this? Could somebody help me, please?
PS. Interesting error: print happens after input (marked as ERROR in code).