[Haskell] A collection of related proposals regarding monads

Cale Gibbard cgibbard at gmail.com
Thu Jan 5 06:00:45 EST 2006


On 05/01/06, David Menendez <zednenem at psualum.com> wrote:
> 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.

My main concern is that mplus means fairly different things in
different monads -- it would be good to be able to expect instances of
MonadPlus to satisfy monoid, left zero, and left distribution laws,
and instances of MonadElse to satisfy monoid, left zero and left
catch. It's just good to know what kinds of transformations you can do
to a piece of code which is meant to be generic.
>
> > 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.

Well, me too :)  Of course, this sort of thing (especially with the
inclusion of PointedFunctor and Applicative) brings us back to wanting
something along the lines of John Meacham's class alias proposal. I
remember there was a lot of commotion about that and people arguing
about concrete syntax. Was any kind of consensus reached? Do we like
it? How does it fare on this hierarchy? I think we need some provision
for simplifying instance declarations in this kind of situation.

It seems to be a common scenario that you have some finely graded
class hierarchy, and you really want to be able to declare default
instances for superclasses based on instances for subclasses in order
to not force everyone to type out a large number of class instances.

Another idea I've had for this, though I haven't really thought all of
the consequences out, (and I'm looking forward to hearing about all
the awful interactions with the module system) is to allow for default
instances somewhat like default methods, together with potentially a
little extra syntax to delegate responsibility for methods in default
instances. The start of your hierarchy could look something like:

----
class Functor f where
    map :: (a -> b) -> f a -> f b

class Functor f => PointedFunctor f where
    return :: a -> f a

    instance Functor f where
        require map
           -- this explicitly allows PointedFunctor instances to define map

class PointedFunctor f => Applicative f where
    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

    instance Functor f where
        require map

    instance PointedFunctor f => Functor f where
        map = ap . return

    instance PointedFunctor f where
        require return

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)

    instance Functor m where
        require map

    instance PointedFunctor m where
        require return
        map f x = x >>= (return . f)

    instance PointedFunctor m => Applicative m where
        ap fs xs = do f <- fs
                      x <- xs
                      return (f x)
----

This is a little verbose, but the intent is to have classes explicitly
declare what default instances they allow, and what extra function
declarations they'll need in an instance to achieve them. Here I used
'require' for this purpose.

To be clear, in order to define an instance of Monad with the above
code, along with all its superclasses, we could simply define return
and (>>=) as we would in Haskell 98.

Since a definition of return is then available, an instance of
PointedFunctor would be inferred, with the default instance providing
an implementation of map which satisfies the requirement for the
default Functor instance for PointedFunctor. We then get a default
implementation of Applicative for free due to the instance of
PointedFunctor which we've been able to construct.

An alternate route here would be to just define return, map, and join.
The declaration for map leads to an instance of Functor. The default
instance of PointedFunctor requiring return is used, but the default
implementation of map there is ignored since the user has already
provided an explicit implementation of map. Bind is defined by the
default method provided using join and map, then an instance of
Applicative is constructed using bind and return.

Some things to note:
* The goal should always be to take implementations as early as they
become available, that is, if the user provides something it's taken
first, then each subclass gets a shot at it starting with the
bottom-most classes in the partial order and working up. We'll likely
run into problems with multiple inheritance, but I think that simply
reporting an error of conflicting instance declarations when two
incomparable default instances would otherwise be available is good
enough. Such situations are rare, and the user will always be able to
simply provide their own instance and resolve ambiguities.

* Class constraints on classes (like the Applicative constraint on the
Monad class above) are used to deny instances only after it's been
determined what instances are really available via defaulting. Since
the class definition for Monad provides a default instance for
Applicative, the user can avoid the trouble of declaring one, provided
that an instance for PointedFunctor can be constructed.

* What extra methods might be needed, and what defaults are available
are specified directly in the classes, rather than simply allowing any
instance to come along and mess with the class hierarchy by providing
implementations of arbitrary superclass methods.

 - Cale


More information about the Haskell mailing list