
Hello fellow Haskellers, I'm trying to solve a very practical problem: I need a stateful iteratee monad transformer. Explicit state passing is very inconvenient and would destroy the elegance of my library. There are two approaches to this: 1. type MyT a m = Iteratee a (StateT MyConfig m) 2. type MyT a m = StateT MyConfig (Iteratee a m) Both work well except in two very specific corner cases: - I need to convert the transformer to 'Iteratee a m', i.e. remove the state layer. This is obviously trivial with the second variant, but seems very difficult with the first one, if it's possible at all. - I need to use control structures of Iteratee like catchError. This is obviously trivial with the first variant, but very inconvenient with the second, because I would need to reinvent many wheels. Does someone know a cleaner, more elegant solution? Encapsulating the state in the iteratee's input type is not an option. Many thanks in advance. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

On Thu, Apr 7, 2011 at 7:04 PM, Ertugrul Soeylemez
Hello fellow Haskellers,
I'm trying to solve a very practical problem: I need a stateful iteratee monad transformer. Explicit state passing is very inconvenient and would destroy the elegance of my library.
There are two approaches to this:
1. type MyT a m = Iteratee a (StateT MyConfig m) 2. type MyT a m = StateT MyConfig (Iteratee a m)
Both work well except in two very specific corner cases:
- I need to convert the transformer to 'Iteratee a m', i.e. remove the state layer. This is obviously trivial with the second variant, but seems very difficult with the first one, if it's possible at all.
Why can't you use #1 and do this when you call "run_"?
G
--
Gregory Collins

Gregory Collins
I'm trying to solve a very practical problem: I need a stateful iteratee monad transformer. Explicit state passing is very inconvenient and would destroy the elegance of my library.
There are two approaches to this:
1. type MyT a m = Iteratee a (StateT MyConfig m) 2. type MyT a m = StateT MyConfig (Iteratee a m)
Both work well except in two very specific corner cases:
- I need to convert the transformer to 'Iteratee a m', i.e. remove the state layer. This is obviously trivial with the second variant, but seems very difficult with the first one, if it's possible at all.
Why can't you use #1 and do this when you call "run_"?
Because that runs the iteratee and leaves me with a StateT. Even though I use a CPS-based StateT, I doubt that it can be converted back to Iteratee easily. With the first variant, I would need a function like this: runMyApp :: Iteratee a (StateT MyConfig m) b -> Iteratee a m b I think, this function is impossible to write. The reason behind this requirement is that I have multiple monad transformers of this kind, each in different libraries, each with different state types, and I need to compose them. But I have another idea in mind. I could do the following instead: -- First library. class Monad m => OneStateMonad m where mapOneConfig :: (OneConfig -> OneConfig) -> m OneConfig oneComp :: OneStateMonad m => Iteratee Input m Output -- Second library. class TwoStateMonad m where mapTwoConfig :: (TwoConfig -> TwoConfig) -> m TwoConfig twoComp :: TwoStateMonad m => Iteratee Input m Output Then the user of the library has to build the monad transformer stack by themselves, like this: instance Monad m => OneStateMonad (StateT (OneConfig, TwoConfig) m) instance Monad m => TwoStateMonad (StateT (OneConfig, TwoConfig) m) appComp :: Monad m => Iteratee Input (StateT (OneConfig, TwoConfig) m) Output That might work, but it seems to be cumbersome. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

On Thu, Apr 7, 2011 at 7:35 PM, Ertugrul Soeylemez
Why can't you use #1 and do this when you call "run_"?
Because that runs the iteratee and leaves me with a StateT. Even though I use a CPS-based StateT, I doubt that it can be converted back to Iteratee easily.
With the first variant, I would need a function like this:
runMyApp :: Iteratee a (StateT MyConfig m) b -> Iteratee a m b
Let me rephrase my question: why do you need a function like this?
Anyways, something like this is definitely doable (using enumerator
formulation, sorry), but your type needs to be this:
runStateIteratee :: Monad m => Iteratee a (StateT s m) r -> s ->
Iteratee a m (r, s)
See runStateT for a parallel. The implementation isn't even too bad:
-----------------------------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
import qualified Data.ByteString.Char8 as S
import Data.ByteString.Char8 (ByteString)
import Data.Enumerator hiding (head)
import qualified Data.Enumerator.List as EL
import Control.Monad.State
import Control.Monad.Trans
mapStep :: Monad m => Step a (StateT s m) r -> s -> Step a m (r, s)
mapStep (Yield x r) st = Yield (x, st) r
mapStep (Error e) _ = Error e
mapStep (Continue k) st = Continue $ \str -> Iteratee $ do
(step, st') <- runStateT (runIteratee (k str)) st
return $ mapStep step st'
runStateIteratee :: Monad m => Iteratee a (StateT s m) r -> s ->
Iteratee a m (r, s)
runStateIteratee iter st = do
(step, st') <- lift $ runStateT (runIteratee iter) st
returnI $ mapStep step st'
-- example
byteCounter :: Monad m => Iteratee ByteString (StateT Int m) ()
byteCounter = do
EL.head >>= maybe (return ())
(\x -> do
lift $ modify (S.length x +)
byteCounter)
main :: IO ()
main = do
(_, c) <- run_ $ enumList 1 input $$ iter
putStrLn $ "count was " ++ show c
where
iter = runStateIteratee byteCounter 0
input = [ "The quick "
, "brown fox "
, "jumped "
, "over the lazy "
, "dog" ]
-----------------------------------------------------------------------------------------------------
G.
--
Gregory Collins

Gregory Collins
On Thu, Apr 7, 2011 at 7:35 PM, Ertugrul Soeylemez
wrote: Why can't you use #1 and do this when you call "run_"?
Because that runs the iteratee and leaves me with a StateT. Even though I use a CPS-based StateT, I doubt that it can be converted back to Iteratee easily.
With the first variant, I would need a function like this:
runMyApp :: Iteratee a (StateT MyConfig m) b -> Iteratee a m b
Let me rephrase my question: why do you need a function like this?
Because I have multiple, independent libraries, which use a stateful iteratee. They work perfectly well, as long as you don't try to combine them. I have found a solution now, which seems to solve the problems. I have described it in my last post.
Anyways, something like this is definitely doable (using enumerator formulation, sorry), but your type needs to be this:
runStateIteratee :: Monad m => Iteratee a (StateT s m) r -> s -> Iteratee a m (r, s)
Well, yes, but that's only part of the problem. After doing this, I need to put the iteratee on top of another monad transformer, while remembering the state to (again) change the underlying state type. All in all it would become very complicated. The solution I'm working on seems to solve this more nicely and keeps the iteratees clean. But it's good to know that such a transformation is possible. It may help out later. Thanks. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/

On Thu, 2011-04-07 at 19:04 +0200, Ertugrul Soeylemez wrote:
Hello fellow Haskellers,
I'm trying to solve a very practical problem: I need a stateful iteratee monad transformer. Explicit state passing is very inconvenient and would destroy the elegance of my library.
There are two approaches to this:
1. type MyT a m = Iteratee a (StateT MyConfig m) 2. type MyT a m = StateT MyConfig (Iteratee a m)
Both work well except in two very specific corner cases:
- I need to convert the transformer to 'Iteratee a m', i.e. remove the state layer. This is obviously trivial with the second variant, but seems very difficult with the first one, if it's possible at all.
- I need to use control structures of Iteratee like catchError. This is obviously trivial with the first variant, but very inconvenient with the second, because I would need to reinvent many wheels.
Does someone know a cleaner, more elegant solution? Encapsulating the state in the iteratee's input type is not an option.
Many thanks in advance.
The first thing that come to my mind. runWithState :: Iteratee a (StateT s m) b -> s -> Iteratee a m (b, s) runWithState i s = do let onDone v st = return (Right (v, st)) onCont c err = return (Left (c, err)) (i', s') <- runStateT (runIter i onDone onCont) s case i' of Left (c, err) -> icont (\str -> runWithState (c str) s') err Right (v, st) -> idone (v, s') st I believe it is equivalent to: runWithState :: Iteratee a (StateT s m) b -> s -> Iteratee a m (b, s) runWithState i s = do let onDone v st = do s' <- get return (idone (v, s') st) onCont c err = do s' <- get return (icont (\str -> runWithState (c str) s') err) joinIM $ evalStateT (runIter i onDone onCont) s I haven't tested but it compiles so it should work.

Maciej Marcin Piechotka
Does someone know a cleaner, more elegant solution? Encapsulating the state in the iteratee's input type is not an option.
The first thing that come to my mind.
runWithState :: Iteratee a (StateT s m) b -> s -> Iteratee a m (b, s) runWithState i s = do let onDone v st = return (Right (v, st)) onCont c err = return (Left (c, err)) (i', s') <- runStateT (runIter i onDone onCont) s case i' of Left (c, err) -> icont (\str -> runWithState (c str) s') err Right (v, st) -> idone (v, s') st
I believe it is equivalent to:
runWithState :: Iteratee a (StateT s m) b -> s -> Iteratee a m (b, s) runWithState i s = do let onDone v st = do s' <- get return (idone (v, s') st) onCont c err = do s' <- get return (icont (\str -> runWithState (c str) s') err) joinIM $ evalStateT (runIter i onDone onCont) s
Thanks for the code. It might come in handy, but for the current implementation I decided not to use this approach, but instead to generalize over 'm', which gives me better composability, for example: MailMonad m => Iteratee SmtpResponse m () Library users can write their own monads and make them instances of MailMonad, which is very easy, because there is only one function to implement. This seems to solve my original problem.
I haven't tested but it compiles so it should work.
I loved that statement -- specifically because it's not far-fetched in Haskell. You wouldn't dare to write anything like that in any of the more commonly used languages. =) Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/
participants (3)
-
Ertugrul Soeylemez
-
Gregory Collins
-
Maciej Marcin Piechotka