[Haskell] A collection of related proposals regarding monads

David Menendez zednenem at psualum.com
Thu Jan 5 00:49:20 EST 2006


Cale Gibbard writes:

> I personally feel that the inclusion of 'fail' in the Monad class is
> an ugly solution to the problem of pattern matching, and gives the
> incorrect impression that monads should have some builtin notion of
> failure. Indeed, it's becoming common to type the result of some
> function in an arbitrary monad in order to indicate the potential for
> failure, which is strictly speaking, not the right thing to do. (In a
> lot of cases, it's going to be no better than complete program
> failure)
> 
> We ought to be using MonadZero when we want to express failure, but
> it's gone!

Yeah, I don't like fail either. In fact, I usually forget to define it,
even for instances of MonadPlus.

There are typically three ways to indicate error in existing monad
libraries, e.g.,

    mzero      :: MonadPlus m =>              m a
    fail       :: Monad m =>        String -> m a
    throwError :: MonadError e m =>      e -> m a
 
I would say that fail and throwError essentially have the same meaning,
but I distinguish them from mzero. To my mind, 'mzero' means "no
answer", whereas fail and throwError mean "something's wrong".

For example, my implementation of Nondet doesn't backtrack over errors:

    mzero        `mplus` m = m
    throwError e `mplus` m = throwError e

Should a pattern match failure call mzero or throwError? I was
originally going to say throwError, but now I'm not so sure. First,
MonadError is severely non-H98 (fundeps). Second, we would either need
the error type to belong to some class which includes pattern match
failures, or have a dedicated throwPatternMatchFailure method in
MonadError. Finally, you can write sensible code which backtracks on
pattern-match failure, e.g.,

    do ...
       Just a <- lookup ...
       ...

> Even if this translation of do-syntax isn't accepted, I still think
> that we should have a separate MonadZero.

I like the idea of a separate MonadZero. Do we know why it was combined
with MonadPlus? Were there efficiency concerns, or did people dislike
having to declare all those separate instances?

> I'd also like to see the current use of MonadPlus split into MonadElse
> (or MonadOr) and MonadPlus, as described at the bottom of
> http://www.haskell.org/hawiki/MonadPlus
> as it helps to clarify the distinction between backtracking-type
> failure and immediate failure in types. We could even put this
> distinction to good use in many monads which do support backtracking
> anyway:
> 
> instance MonadElse [] where
>     [] `morelse` ys = ys
>     (x:xs) `morelse` ys = (x:xs)

With backtracking monads, you can use Oleg's msplit operator to get
morelse, soft-cut, and various other operations.

    class MonadPlus m => MonadChoice m where
        msplit :: m a -> m (Maybe (a, m a))

    mif :: MonadSplit m => m a -> (a -> m b) -> m b -> m b
    mif p t e = msplit p >>= maybe e (\(x,xs) -> t x `mplus` (xs >>= t))
    
    a `orElse` b = mif a return b

With non-backtracking monads, you can use throwError or just use mplus
and remind people that non-backtracking monads don't backtrack.

> Lastly, it would be nice to have some standard name for the function:
> option :: (MonadPlus m) => [a] -> m a
> option = foldr (mplus . return) mzero
> which seems to come up quite a bit in my experience with nondet
> monads.

Mine too. Someone else mentioned "choose", which seems nice. Or,
"fromList".

Incidentally, would GHC optimize "msum (map return xs)" to "foldr (mplus
. return) mzero xs"?

> P.S. Oh, and don't get me started about the whole Functor subclass
> thing, and the inclusion of join in the Monad class. Of course I want
> those too. :)

For the recond, my ideal hierarchy would look something like this:

    class Functor f where
        map :: (a -> b) -> f a -> f b
    
    class Functor f => Applicative f where
        return :: a -> f a
        ap     :: f (a -> b) -> f a -> f b
        lift2  :: (a -> b -> c) -> f a -> f b -> f c
        
        ap = lift2 ($)
        lift2 f a b = map f a `ap` b
    
    class Applicative m => Monad m where
        join  :: m (m a) -> m a
        (>>=) :: m a -> (a -> m b) -> m b
        
        join m = m >>= id
        m >>= f = join (map f m)
    
    class Monad m => MonadZero m where
        nothing :: m a
    
    class MonadZero m => MonadPlus m where
        (++) :: m a -> m a -> m a
        
    class MonadPlus m => MonadChoice m where
        msplit :: m a -> m (Maybe (a, m a))

I guess you could put "return" in its own class, PointedFunctor, between
Functor and Applicative, but I haven't seen a reason to. Even without
that, it's probably excessive.

-- 
David Menendez <zednenem at psualum.com> | "In this house, we obey the laws
<http://www.eyrie.org/~zednenem>      |        of thermodynamics!"


More information about the Haskell mailing list