[Haskell-cafe] Conduit: Where to run monad stacks?

Michael Snoyman michael at snoyman.com
Fri Aug 24 07:51:24 CEST 2012


I agree that the behavior is a bit confusing (Dan Burton just filed an
issue about this[1], I'm guessing this email is related).

I put up a wiki page[2] to hopefully explain the issue. Can you review
it and let me know if it helps? If so, I'll link to it from the
Haddocks.

Michael

[1] https://github.com/snoyberg/conduit/issues/67
[2] https://github.com/snoyberg/conduit/wiki/Dealing-with-monad-transformers

On Wed, Aug 22, 2012 at 11:19 PM, Niklas Hambüchen <mail at nh2.me> wrote:
> Today I was surprised that transPipe is called for every chunk of data
> going through my pipe, rendering the StateT I put in useless, because it
> was always restarted with the initial value.
>
> It would be nice to have some explanation about this, as it makes it
> easy to write compiling code that has completely unexpected behaviour.
>
>
> I wrote this function (also on http://hpaste.org/73538):
>
> conduitWithState :: (MonadIO m) => Conduit Int (StateT Int m) String
> conduitWithState = do
>   liftIO $ putStrLn $ "Counting Int->String converter ready!"
>   awaitForever $ \x -> do
>     i <- lift get
>     lift $ modify (+1)
>     liftIO $ putStrLn $ "Converting " ++ show x ++ " to a string! " ++
>                         "Processed so far: " ++ show i
>     yield (show x)
>
> and ran it like this:
>
> countingConverterConduit :: (MonadIO m) => Conduit Int m String
> countingConverterConduit = transPipe (\stateTint -> evalStateT stateTint
> 1) conduitWithState
>
> main :: IO ()
> main = do
>   stringList <- CL.sourceList [4,1,9,7,3] $=
>      countingConverterConduit $$
>      CL.consume
>   print stringList
>
> However, the output is not what I expected, but only:
>
> Processed so far:1
> Processed so far:1
> ...
>
> Dan Burton proposed a fix, making the whole sink-conduit-source
> construction run on the StateT:
>
> main = do
>   stringList <- flip evalStateT 1 $ ...
>
>
> So the question is: What is the rationale for this?
>
> I was expecting that if I have an IO pipe in my main conduit, I could
> easily run stuff on top of that in parts of the pipe.
>
> Thanks
> Niklas
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list