[Haskell-cafe] Monad m => m (Maybe a) -> m (Maybe a) -> m (Maybe a)

Andras Slemmer 0slemi0 at gmail.com
Wed Nov 12 22:07:51 UTC 2014


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 <qdunkan at gmail.com> wrote:

> On Tue, Nov 11, 2014 at 9:18 AM, Tom Ellis
> <tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20141112/cd94d1e5/attachment.html>


More information about the Haskell-Cafe mailing list