Monad m => m (Maybe a) -> m (Maybe a) -> m (Maybe a)

I've been using these functions lately: try :: Monad m => m (Maybe a) -> m (Maybe a) -> m (Maybe a) try action alternative = maybe alternative (return . Just) =<< action tries :: Monad m => [m (Maybe a)] -> m (Maybe a) tries = foldr try (return Nothing) It's sort of like (<|>) on Maybe, or MonadPlus, but within a monad. It seems like the sort of thing that should be already available, but hoogle shows nothing. I think 'm' has to be a monad, and I can't figure out how to generalize the Maybe to MonadPlus or Alternative. It's sort of a mirror image to another function I use a lot: justm :: Monad m => m (Maybe a) -> (a -> m (Maybe b)) -> m (Maybe b) justm op1 op2 = maybe (return Nothing) op2 =<< op1 ... which is just MaybeT for when I can't be bothered to put runMaybeT and lifts and hoists on everything. So you could say 'try' is like MaybeT with the exceptional case reversed. Is 'try' just the instantiation of some standard typeclass, or is it its own thing?

On Tue, Nov 11, 2014 at 08:57:48AM -0800, Evan Laforge wrote:
try :: Monad m => m (Maybe a) -> m (Maybe a) -> m (Maybe a) try action alternative = maybe alternative (return . Just) =<< action
Looks like the MonadPlus instance for MaybeT to me runMaybeT $ MaybeT (print "first" >> return (Just 1)) `mplus` MaybeT (print "second" >> return (Just 2)) Just 1 runMaybeT $ MaybeT (print "first" >> return Nothing) `mplus` MaybeT (print "second" >> return (Just 2)) "first" "second" Just 2 Tom

On Tue, Nov 11, 2014 at 05:18:56PM +0000, Tom Ellis wrote:
On Tue, Nov 11, 2014 at 08:57:48AM -0800, Evan Laforge wrote:
try :: Monad m => m (Maybe a) -> m (Maybe a) -> m (Maybe a) try action alternative = maybe alternative (return . Just) =<< action
Looks like the MonadPlus instance for MaybeT to me
runMaybeT $ MaybeT (print "first" >> return (Just 1)) `mplus` MaybeT (print "second" >> return (Just 2))
Just 1
I mistranscribed the output. The output is "first" Just 1

On Tue, Nov 11, 2014 at 9:18 AM, Tom Ellis
On Tue, Nov 11, 2014 at 08:57:48AM -0800, Evan Laforge wrote:
try :: Monad m => m (Maybe a) -> m (Maybe a) -> m (Maybe a) try action alternative = maybe alternative (return . Just) =<< action
Looks like the MonadPlus instance for MaybeT to me
runMaybeT $ MaybeT (print "first" >> return (Just 1)) `mplus` MaybeT (print "second" >> return (Just 2))
Ah, so it looks like it does exist, but requires explicit running and wrapping, e.g. compare to: try (print "first" >> return (Just 1)) $ print "second" >> return (Just 2) I guess it's like 'justm' then, which is also just MaybeT, but with less typing. Thanks!

Well, "try" is really doing two things: chaining Maybes, and then adding a
monadic context:
try :: Monad m => m (Maybe a) -> m (Maybe a) -> m (Maybe a)
try = liftM2 (<|>)
(You could weaken the assumption by using (Applicative m) instead)
"tries" is similar, only there is an intermediate "threading" step [m x] ->
m [x]:
tries :: Monad m => [m (Maybe a)] -> m (Maybe a)
tries = liftM asum . sequence
These are both special cases, they only rely on Maybe being an Alternative:
try :: (Monad m, Alternative f) => m (f a) -> m (f a) -> m (f a)
tries :: (Monad m, Alternative f) => [m (f a)] -> m (f a)
If you *really* want to generalise you can even write this. ([] is also an
unnecessary specialisation right?:))
tries :: (Monad m, Alternative f, Traversable t) => t (m (f a)) -> m (f a)
"justm" is a bit different, as you rely on Maybe's concrete structure by
using 'maybe'. However you can still generalise it if you really want to.
The first thing to realise is because you are "binding" with an (a -> _)
function you'll need to use the monadic structure of both 'm' and 'Maybe'
to unpack-repack properly. The second is the need of n (m x) -> m (n x),
which is Data.Traversable:mapM
justm :: (Monad m, Monad n, Traversable n) => m (n a) -> (a -> m (n b)) ->
m (n b)
justm m f = m >>= liftM join . mapM f
However if you ask me, these generalisations are completely useless in
practice 99 out of a 100 times. Your original functions are way more
discoverable and intuitive. Generalising just for the sake of generalising
is rarely a good design practice when you write "real" software.
Imho these abstractions only make sense when you are designing a library
API and you want to make as few assumptions as you can about the user's
calling context.
On 11 November 2014 22:41, Evan Laforge
On Tue, Nov 11, 2014 at 9:18 AM, Tom Ellis
wrote: On Tue, Nov 11, 2014 at 08:57:48AM -0800, Evan Laforge wrote:
try :: Monad m => m (Maybe a) -> m (Maybe a) -> m (Maybe a) try action alternative = maybe alternative (return . Just) =<< action
Looks like the MonadPlus instance for MaybeT to me
runMaybeT $ MaybeT (print "first" >> return (Just 1)) `mplus` MaybeT (print "second" >> return (Just 2))
Ah, so it looks like it does exist, but requires explicit running and wrapping, e.g. compare to:
try (print "first" >> return (Just 1)) $ print "second" >> return (Just 2)
I guess it's like 'justm' then, which is also just MaybeT, but with less typing.
Thanks! _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thu, Nov 13, 2014 at 11:07 AM, Andras Slemmer <0slemi0@gmail.com> wrote:
Well, "try" is really doing two things: chaining Maybes, and then adding a monadic context: try :: Monad m => m (Maybe a) -> m (Maybe a) -> m (Maybe a) try = liftM2 (<|>) (You could weaken the assumption by using (Applicative m) instead)
That's different to Evan's original function. Evan's solution short-circuits: it does not execute the second action if the first succeeds. But your one runs both actions unconditionally. For example, the expression try (return $ Just ()) (putStrLn "second action executed" >> return Nothing) outputs "second action executed" with your solution, but not with Evan's. The lesson is, applicative and monadic composition don't always yield the same results. Chris

On 13 November 2014 01:23, Chris Wong
That's different to Evan's original function.
Evan's solution short-circuits: it does not execute the second action if the first succeeds. But your one runs both actions unconditionally.
For example, the expression
try (return $ Just ()) (putStrLn "second action executed" >> return Nothing)
outputs "second action executed" with your solution, but not with Evan's.
The lesson is, applicative and monadic composition don't always yield the same results.
Applicative and monadic composition *should* be the same, given that Applicative contains the law (<*>) = ap And in fact if we rewrite Andras solution as try a b = (<|>) <$> a <*> b It is still broken. The fact that you find libraries where (<*>) is not ap has been confusing for me as well :P. Evan's `try` doesn't use Applicative at all, but short-circuits manually. For this kind of stuff I usually use MaybeT. Francesco

Applicative and monadic composition *should* be the same, given that Applicative contains the law
(<*>) = ap
Ah, I probably wasn't too clear with that last comment. What I meant by "applicative and monadic composition don't always yield the same result" is that Compose m Maybe and MaybeT m are *not* interchangeable, despite their unwrapped types being the same. As you point out, the latter short-circuits but the former does not. I guess a better wording is that there is often more than one way to compose things. (Compose is from Data.Functor.Compose in the transformers package.) Chris
And in fact if we rewrite Andras solution as
try a b = (<|>) <$> a <*> b
It is still broken.
The fact that you find libraries where (<*>) is not ap has been confusing for me as well :P.
Evan's `try` doesn't use Applicative at all, but short-circuits manually. For this kind of stuff I usually use MaybeT.
Francesco

Evan's solution short-circuits: it does not execute the second action if the first succeeds. But your one runs both actions unconditionally.
Thanks for pointing that out! This is what happens when you only look at
the type of a function and *assume* its implementation:)
Actually this is a great way to shed light on the difference between
monadic and applicative: In the original function the context chaining
itself depends on a computed value (short circuiting), meaning it
"properly" relies on (>>=). liftM2 (<|>) - or rather liftA2 (<|>) - does
not, it doesn't unbox anything, so it cannot possibly be correct.
On 13 November 2014 01:23, Chris Wong
On Thu, Nov 13, 2014 at 11:07 AM, Andras Slemmer <0slemi0@gmail.com> wrote:
Well, "try" is really doing two things: chaining Maybes, and then adding a monadic context: try :: Monad m => m (Maybe a) -> m (Maybe a) -> m (Maybe a) try = liftM2 (<|>) (You could weaken the assumption by using (Applicative m) instead)
That's different to Evan's original function.
Evan's solution short-circuits: it does not execute the second action if the first succeeds. But your one runs both actions unconditionally.
For example, the expression
try (return $ Just ()) (putStrLn "second action executed" >> return Nothing)
outputs "second action executed" with your solution, but not with Evan's.
The lesson is, applicative and monadic composition don't always yield the same results.
Chris

On Thu, Nov 13, 2014 at 11:23 AM, Andras Slemmer <0slemi0@gmail.com> wrote:
Actually this is a great way to shed light on the difference between monadic and applicative: In the original function the context chaining itself depends on a computed value (short circuiting), meaning it "properly" relies on (>>=). liftM2 (<|>) - or rather liftA2 (<|>) - does not, it doesn't unbox anything, so it cannot possibly be correct.
That's what I meant by "I think 'm' has to be a monad", sorry if I wasn't clear! I admit I'm weak on Alternative, and haven't really found many uses for it, other than the parser combinator thing, so the conversation was interesting anyway. Come to think of it I've used (<|>) for choice and mzero for failure in parsers, so that's really confusing, why one of each? Perhaps because parsec predates Applicative and Alternative. I'm also not too clear on the uses of MonadPlus, aside from being the pure version of my 'try' function, or the relation between Alternative and MonadPlus. There was some discussion recently with the whole AMP thing that implied that it's a historical relic of Applicative coming after Monad, but then some implication that maybe it's not. I guess you'd need a MonadPlus if choice relied on the value inside, but presumably if there's an Alternative, then MonadPlus should have the same implementation.
participants (5)
-
Andras Slemmer
-
Chris Wong
-
Evan Laforge
-
Francesco Mazzoli
-
Tom Ellis