
On Thu, Apr 9, 2009 at 2:22 AM, Sebastian Fischer
Let's see whether I got your point here. If we have a computation
a :: Monad m => m a
and we have a pointed functor `f`, then we can get the result of the computation `a` in our functor `f` because `runContT a :: f a`.
Sure, but you can also do the same much more simply: mkPointed :: Pointed f => forall f a. (forall m. Monad m => m a) -> f a mkPointed m = point $ runIdentity m
Clearly, `runContT (lift b)` (or `b` itself) and `runContT b` may behave differently (even if they both (can) have the type `f b`) because `ContT` 'overwrites' the definition for `>>=` of `f` if `f` has one. So it depends on the application which of those behaviours is desired.
My point was slightly more general; what I was saying was there is not a huge use for the "generic" MonadPlus using Alternative, because without "lift", you have a hard time embedding any other effects from the applicative into the continuation use. You may as well do the following:
data MPlus a = Zero | Pure a | Plus (MPlus a) (MPlus a) instance Monad MPlus where return = Pure Zero >>= k = Zero Pure a >>= k = k a Plus a b >>= k = Plus (a >>= k) (b >>= k) instance MonadPlus MPlus where mzero = Zero mplus = Plus
mkAlternative :: forall f a. Alternative f => (forall m. MonadPlus m => m a) -> f a mkAlternative m = convertPlus m where convertPlus :: forall b. MPlus b -> f b convertPlus Zero = empty convertPlus (Pure a) = pure a convertPlus (Plus a b) = convertPlus a <|> convertPlus b
(all this code is really saying is that being polymorphic over MonadPlus is kind of dumb, because you aren't really using Monad at all) Without any way to lift other effects from the underlying functor into ContT, I don't really see how the "generic" ContT MonadPlus instance buys you much :)
Ryan: > The CPS transfrom in ContT also has the nice property that it makes > most applications of >>= in the underlying monad be > right-associative.
Do you have a specific reason to say *most* (rather than *all*) here?
Yes, because
runContT ( (lift (a >>= f)) >>= g ) still has a left-associative >>=.
Now of course that looks silly, but things aren't as simple as they seem; in particular I ran into this first when using Control.Monad.Prompt[1] (which is really just a sophisticated Cont monad with a nice interface)
data MPlus m a = Zero | Plus (m a) (m a)
instance MonadPlus (RecPrompt MPlus) where mzero = prompt Zero mplus x y = prompt (Plus x y)
runPlus :: forall a. RecPrompt MPlus r -> [r] runPlus = runPromptC ret prm . unRecPrompt where ret :: r -> [r] ret x = [x]
prm :: forall a. MPlus (RecPrompt MPlus) a -> (a -> [r]) -> [r] prm Zero k = [] prm (Plus a b) k = (runPlus a ++ runPlus b) >>= k -- this >>= is in the list monad
Now, consider runPlus ((mplus mzero (a >>= f)) >>= g), which uses the Plus "effect"; this will reduce to (runPlus (a >>= f)) >>= k where k is the continuation that runs g using "ret" and "prm" to convert to a list; the result still may have a left-associated >>= in it, depending on the value of "a" and "f". However, you're limited to at most one left associative bind per "recursive" lifted operation; the other binds will all be right-associative. I know this was a pretty in-depth example, so I hope I've made it clear :) -- ryan [1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/MonadPrompt