
Hi all, Max asked earlier[1] how to create a new instance of a class in Persistent using a monad transformer. Without getting into the specific details of persistent, I wanted to pose a question based on a much more general question: how can we lift the inner monad of an enumerator? We can easily do so for an Iteratee[2], but there is nothing to allow it for an Enumerator. At first glance, this problem looks very similar to the shortcomings of MonadIO when dealing with callbacks. In that case, you cannot use liftIO on a function that takes an `IO a` as a parameter. A solution to this issue is monad-control[3], which can be used to allow exception catching, memory allocation, etc. So I'm wondering: can we come up with a similar solution to this issue with enumerators? I have a working solution for the specific case of the ErrorT monad[4], but it would be great to be able to generalize it. Bonus points if we could express this in terms of the typeclasses already provided by monad-control. Michael [1] http://groups.google.com/group/yesodweb/browse_thread/thread/be2a77217a7f334... [2] http://hackage.haskell.org/packages/archive/enumerator/0.4.14/doc/html/Data-... [3] http://hackage.haskell.org/package/monad-control [4] https://gist.github.com/1168128

On 08/24/2011 09:02 AM, Michael Snoyman wrote:
Hi all,
Max asked earlier[1] how to create a new instance of a class in Persistent using a monad transformer. Without getting into the specific details of persistent, I wanted to pose a question based on a much more general question: how can we lift the inner monad of an enumerator? We can easily do so for an Iteratee[2], but there is nothing to allow it for an Enumerator.
I faced the same problem a few weeks back, but for ReaderT. I tried for a while to get it working for all transformers, but couldn't get it to work. After spending time with this a few weeks ago, I think perhaps you could write liftEnum :: (Monad m, MonadTrans t, MonadCont m) => Enumerator a m b -> Enumerator a (t m) b That is, use callCC to return the step from the inner iteratee to be able to execute the step in the correct monad. But I didn't take the time to get it to work, since I got the ReaderT working. In any case, here is what I wrote for ReaderT. John newtype MemcacheBackend m a = MemcacheBackend { unMemBackend :: ReaderT MemcacheConnection m a } deriving (Monad, MonadIO, MonadTrans, Functor, Applicative, Alternative, MonadPlus, MonadCatchIO, MonadControlIO) lower :: Monad m => MemcacheConnection -> Iteratee a (MemcacheBackend m) b -> Iteratee a m b lower c i = Iteratee $ do step <- runReaderT (unMemBackend $ runIteratee i) c case step of (Error ex) -> return $ Error ex (Yield b s) -> return $ Yield b s (Continue f) -> return $ Continue $ lower c . f liftEnum :: (Monad m) => Enumerator a m b -> Enumerator a (MemcacheBackend m) b liftEnum e (Yield b s) = liftTrans $ e $ Yield b s liftEnum e (Error err) = liftTrans $ e $ Error err liftEnum e (Continue f) = Iteratee $ do r <- MemcacheBackend ask step <- lift $ runIteratee $ e $ Continue $ lower r . f case step of (Yield b s) -> return $ Yield b s (Error err) -> return $ Error err (Continue f') -> return $ Continue $ \x -> liftTrans $ f' x

The type signature
liftEnum :: (Monad m, MonadTrans t) => Enumerator a m b ->
Enumerator a (t m) b
expands to:
liftEnum :: (Monad m, MonadTrans t) => (Step a m b -> Iteratee a m
b) -> Step a (t m) b -> Iteratee a (t m) b
So you could implement it iff you can define:
lower :: (Monad m, MonadTrans t) => t m a -> m a
Which is not possible given the standard MonadTrans, but maybe
possible with a custom restricted typeclass such as your
MonadTransControl.
On Wed, Aug 24, 2011 at 07:02, Michael Snoyman
Hi all,
Max asked earlier[1] how to create a new instance of a class in Persistent using a monad transformer. Without getting into the specific details of persistent, I wanted to pose a question based on a much more general question: how can we lift the inner monad of an enumerator? We can easily do so for an Iteratee[2], but there is nothing to allow it for an Enumerator.
At first glance, this problem looks very similar to the shortcomings of MonadIO when dealing with callbacks. In that case, you cannot use liftIO on a function that takes an `IO a` as a parameter. A solution to this issue is monad-control[3], which can be used to allow exception catching, memory allocation, etc.
So I'm wondering: can we come up with a similar solution to this issue with enumerators? I have a working solution for the specific case of the ErrorT monad[4], but it would be great to be able to generalize it. Bonus points if we could express this in terms of the typeclasses already provided by monad-control.
Michael
[1] http://groups.google.com/group/yesodweb/browse_thread/thread/be2a77217a7f334... [2] http://hackage.haskell.org/packages/archive/enumerator/0.4.14/doc/html/Data-... [3] http://hackage.haskell.org/package/monad-control [4] https://gist.github.com/1168128

Actually, I'm looking for a slightly different type signature. Look at
how I've implemented the special case of ErrorT:
liftEnum :: Enumerator In IO (Either OcrError Out)
-> Enumerator In (ErrorT OcrError IO) Out
There's a slightly different value for "b", which is what keeps track
of the monadic state. This is the same trick used in MonadControlIO.
My guess is that a final type signature would be something like:
liftEnum
:: MonadTrans t
=> (forall c. Enumerator a m c)
-> Enumerator a (t m) b
Then the idea would be that, for each instance of MonadTrans, we would
be encoding the state within that "c".
Michael
On Wed, Aug 24, 2011 at 8:23 PM, John Millikin
The type signature
liftEnum :: (Monad m, MonadTrans t) => Enumerator a m b -> Enumerator a (t m) b
expands to:
liftEnum :: (Monad m, MonadTrans t) => (Step a m b -> Iteratee a m b) -> Step a (t m) b -> Iteratee a (t m) b
So you could implement it iff you can define:
lower :: (Monad m, MonadTrans t) => t m a -> m a
Which is not possible given the standard MonadTrans, but maybe possible with a custom restricted typeclass such as your MonadTransControl.
On Wed, Aug 24, 2011 at 07:02, Michael Snoyman
wrote: Hi all,
Max asked earlier[1] how to create a new instance of a class in Persistent using a monad transformer. Without getting into the specific details of persistent, I wanted to pose a question based on a much more general question: how can we lift the inner monad of an enumerator? We can easily do so for an Iteratee[2], but there is nothing to allow it for an Enumerator.
At first glance, this problem looks very similar to the shortcomings of MonadIO when dealing with callbacks. In that case, you cannot use liftIO on a function that takes an `IO a` as a parameter. A solution to this issue is monad-control[3], which can be used to allow exception catching, memory allocation, etc.
So I'm wondering: can we come up with a similar solution to this issue with enumerators? I have a working solution for the specific case of the ErrorT monad[4], but it would be great to be able to generalize it. Bonus points if we could express this in terms of the typeclasses already provided by monad-control.
Michael
[1] http://groups.google.com/group/yesodweb/browse_thread/thread/be2a77217a7f334... [2] http://hackage.haskell.org/packages/archive/enumerator/0.4.14/doc/html/Data-... [3] http://hackage.haskell.org/package/monad-control [4] https://gist.github.com/1168128
participants (3)
-
John Lenz
-
John Millikin
-
Michael Snoyman