10

I try to make a derived instance for MonadWriter of the Continuation Monad Transformer. This is how i tried it:

{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, UndecidableInstances #-}

import Control.Monad.Cont
import Control.Monad.Writer


instance (MonadWriter w m) => MonadWriter w (ContT r m) where
   tell= lift . tell
   listen m= ContT $ \ c -> do
         (a,w) <- listen $ runContT m (c)
         return (a,w)

   pass m = undefined

This gives me the following error:

Occurs check: cannot construct the infinite type: r = (r, w1)
When generalising the type(s) for `listen'
In the instance declaration for `MonadWriter w (ContT r m)'

Next try was this:

instance (MonadWriter w m) => MonadWriter w (ContT r m) where
   tell= lift . tell
   listen m= ContT $ \ c -> do
         (a,w) <- runContT m (listen . c)
         return (a,w)

   pass m = undefined

Followed by:

Occurs check: cannot construct the infinite type: a = (a, w)
When generalising the type(s) for `listen'
In the instance declaration for `MonadWriter w (ContT r m)'

Does anyone know how to implement listen and pass here? Is there a reason why there is no instance declaration for this in the mtl? Please help me to understand this!

Regards Marian

PS: I've found that Blog Entry at blog.sigfpe.com where somewhere at the end of the discussion Edward Kmett says:

"(...) As I recall, 'pass' and 'local' cause problems with the current MTL when you start mixing in ContT, and should probably be factored into separate classes."

Maybe the same hold's also for listen from MonadWriter. So the simplest solution is, if you dont need listen and pass in a special case, to leave them undefined:

instance (MonadWriter w m) => MonadWriter w (ContT r m) where
   tell= lift . tell
   listen = undefined
   pass = undefined

PS: (2011-03-11) Diving further in this subject I've come up with this solution: (When specifiying the type r on ContT as () we could try this:)

  instance (MonadWriter w m) => MonadWriter w (ContT () m) where    
    listen m = do
        a <- m
        (_,w) <- lift $ listen $ runContT m (return . (const ()))
        return (a,w)

This compiles! And runs! But, alas, the monadic action must be computed twice. May anybody take this as hint to collapse the two calls somehow into one? Then we will get the desired implementation.

makelc
  • 857
  • 8
  • 9

1 Answers1

11

I don't think it's possible. For reference, here's the meaning of ContT:

ContT r m a = (a -> m r) -> m r

Here's my starting point for listen:

listen m = ContT $ \c -> 
    runCont m (\x -> c (x,w))

The question is, where do we get w? w will come from the computation that runCont m performs before it calls our function \x -> c (x,w) with its return value x. That is, the information we need to pass to c comes from runCont, so we would need to do something like this:

listen m = ContT $ \c -> do
    rec (r,w) <- listen . runContT m $ \x -> c (x,w)
    return r

(Needs LANGUAGE DoRec and MonadFix m in the context)

Although that typechecks, it is not correct. w is now the value written by the entire computation, not just the portion before calling our continuation \x -> c (x,w).

Do you see what you would need to do? I know my answer is essentially "I think it's impossible because I can't think of a way to do it" (what Conal Elliott calls "proof by lack of imagination"), but I think my lack of imagination is correct this time. The information we need is destroyed before we have a chance to peek at it.

I believe this instance is possible with the Codensity monad transformer:

newtype CodensityT m a = CodensityT { runCodensityT :: forall r. (a -> m r) -> m r }

which gives you the same performance improvements as Cont in the cases where it does that, but doesn't support callCC. This is because you can runCodensityT in the middle of a computation with whatever r you want.

listen m = CodensityT $ \c -> listen (runCodensityT m return) >>= c

Maybe callCC is the problem. I wouldn't be surprised if you could come up with an example combining listen and callCC that would create a paradox.

luqui
  • 57,324
  • 7
  • 134
  • 191
  • luqui! Thank you for your answer. By the way, you brought me to understand the MonadFix! – makelc Mar 04 '11 at 10:26
  • I've just edited the question and added some information from blog where I've found hints that certain methods in the mtl cause problems when mixed with ContT. Regards, Marian – makelc Mar 04 '11 at 11:28