
Henning Thielemann wrote:
Sittampalam, Ganesh wrote:
Henning Thielemann wrote:
What about adding the Maybe monad transformer as provided in MaybeT package to the transformers package?
The module name could be Control.Monad.Trans.Maybe which would also avoid conflicts with the MaybeT package.
What MonadPlus instance will it get, if any?
The one which is currently used by MaybeT:
instance (Monad m) => MonadPlus (MaybeT m) where mzero = MaybeT (return Nothing) mplus x y = MaybeT $ do v <- runMaybeT x case v of Nothing -> runMaybeT y Just _ -> return v
It is also the one I needed recently.
I tend to agree that this is the right one to use, but I think care should be taken when adding this to what is/is expected to be a widely used package, as it could make it difficult for people who want the alternate behaviour, and it might imply a degree of standardisation/ canonicity that is not really justified. On the other hand, perhaps there are no real uses for the other one. Cheers, Ganesh ============================================================================== Please access the attached hyperlink for an important electronic communications disclaimer: http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html ==============================================================================

On Fri, Feb 6, 2009 at 5:56 PM, Sittampalam, Ganesh
I tend to agree that this is the right one to use, but I think care should be taken when adding this to what is/is expected to be a widely used package, as it could make it difficult for people who want the alternate behaviour, and it might imply a degree of standardisation/ canonicity that is not really justified.
On the other hand, perhaps there are no real uses for the other one.
ErrorT has had the equivalent MonadPlus instance for a while, hasn't it? Anybody run into problems with that? All the best, - Benja

On Fri, Feb 6, 2009 at 12:40 PM, Benja Fallenstein
On Fri, Feb 6, 2009 at 5:56 PM, Sittampalam, Ganesh
wrote: I tend to agree that this is the right one to use, but I think care should be taken when adding this to what is/is expected to be a widely used package, as it could make it difficult for people who want the alternate behaviour, and it might imply a degree of standardisation/ canonicity that is not really justified.
On the other hand, perhaps there are no real uses for the other one.
ErrorT has had the equivalent MonadPlus instance for a while, hasn't it? Anybody run into problems with that?
In my own monad implementations, I prefer to keep exception handling distinct from nondeterminism. From that perspective, Maybe and MaybeT are better suited to MonadError than MonadPlus. There are also times where it would be nice if you could assume that
= distributed over mplus, as it does in a nondeterminism monad.
Let's say I have a state monad implemented using CPS.
newtype StateT s m a = C { unC :: forall b. (a -> s -> m b) -> s -> m b }
The simple way to promote mplus is to do:
mplus a b = C (\k s -> unC a k s `mplus` unC b k s)
But that version always distributes, regardless of what the underlying
mplus does. In particular, it does not satisfy this equation:
lift (mplus a b) = mplus (lift a) (lift b)
So intead, you have to do something like
mplus a b = C (\k s -> unC a (uncurry return) s `mplus` unC b
(uncurry return) s >>= curry k)
which is more complicated and involves four operations in the
underlying monad, instead of just one.
Here's an easy way to test whether a monad's mplus distributes:
test = mplus (return 0) (return 1) >>= \x -> guard (odd x) >> return x
If the monad distributes over mplus, then test = return 1. Otherwise,
test = mzero.
--
Dave Menendez

On Fri, 6 Feb 2009, Sittampalam, Ganesh wrote:
I tend to agree that this is the right one to use, but I think care should be taken when adding this to what is/is expected to be a widely used package, as it could make it difficult for people who want the alternate behaviour, and it might imply a degree of standardisation/ canonicity that is not really justified.
On the other hand, perhaps there are no real uses for the other one.
I guess the other one is simply liftM2 mplus on (m (Maybe a)) and thus there would not be much advantage of using (MaybeT m) instead of (m (Maybe a)).
participants (4)
-
Benja Fallenstein
-
David Menendez
-
Henning Thielemann
-
Sittampalam, Ganesh