Proposal: Applicative => Monad: Call for consensus

Conor McBride conor at strictlypositive.org
Wed Jan 5 17:05:22 CET 2011


Hi

On 5 Jan 2011, at 15:22, John Smith wrote:

> On 05/01/2011 12:33, Simon Marlow wrote:
>> We have a hard time explaining Monads to people already. But now  
>> the entire API goes from being one class with 3 methods
>> (only 2 of which you need to care about) to being 3 classes with a  
>> total of 11 methods, with a lot of complex
>> interactions. That's a significant increase in cognitive overhead.  
>> It might well be the "right" thing in some sense, but
>> is it really worth the pain? What about all those monad tutorials?  
>> They now have to include some Functor/Applicative
>> boilerplate, and hope it doesn't put the reader off too much. I  
>> like Applicative, I really do, but I want it to be
>> something you only have to buy into if you want to.

I think a lot of people take that entirely reasonable position,
and it's worth thinking about how to choreograph a good compromise
if possible. I believe it is.

> The original Arrow was one class with a few simple methods, and  
> extremely easy to explain. There are now several classes in the  
> Arrow module, and Arrow itself is a subclass of Category. Tutorials  
> simply use the original Arrow definition, which gets the concept  
> across fine. The learner can then proceed to understand the richer,  
> and better factored, current implementation.

Arrows (rightly or wrongly) tend to be a pedagogical step beyond
Monad, anyway, so one can expect more of Arrow-learners. It's
better to avoid unlearning experiences, so it's worth thinking
about how to ensure that people can engage with the Monad concept,
as available when they fire up ghci, without needing to see its
further refinements.

>> Someone knocking up a monad for a simple job now has to define 3  
>> instances, not one.

It's one interesting instance, plus a copy-paste mantra, but it's
still annoying, even if you actually want to use those extra
instances.

>> So it affects not just people
>> learning the language, but also those already familiar with it and  
>> trying to get the job done.
>
> This creates a little extra work for those who don't want Functor or  
> Applicative (the methods have to be defined anyway, it's just split  
> across the new class hierarchy). Those who do want Functor or  
> Applicative now have them where they belong, without writing  
> boilerplate definitions.

They must still write boilerplate instances, but not those awful
(Functor m, Monad m) contexts.

> Much like anyone declaring an instance of Ord also needs an instance  
> of Eq, even if they're not going to use it.
>
>> Furthermore, we have some significant compatibility issues with  
>> Haskell 98/2010 code. I wouldn't be in favour of doing
>> this unless we can retain Haskell 98/2010 compatibility somehow  
>> (e.g. with superclass defaults or class aliases).
>
> This is part of a larger problem. Is Haskell to be forever frozen as  
> something which can be easily made compatible with Haskell 98?  
> Haskell 98 an earlier made many non-backwards compatible changes,  
> including changes to the Monad class.

Change that breaks stuff gets more expensive as uptake grows, so the H98
comparison needs refinement: the cost-benefit analysis is different.
I'm in favour of Applicative => Monad in principle, and as soon as is
practicable. I just think that if there are helpful measures we can take
first to reduce the cost of that change, then we should try to do it
the easier way around. The choreography matters.

To that end, a little joyride...

 > {-# OPTIONS_GHC -F -pgmF she #-}
 > {-# LANGUAGE NoImplicitPrelude #-}

 > module NewMonad where

 > import Prelude hiding (Functor, Monad, return, (>>=), fmap)

 > class Functor f where
 >   fmap :: (s -> t) -> f s -> f t

 > class Functor f => Applicative f where
 >   return :: x -> f x
 >   (<*>) :: f (s -> t) -> f s -> f t
 >   instance Functor f where
 >     fmap = (<*>) . return

 > pure :: Applicative f => x -> f x
 > pure = return  -- for backward compatibility

 > class Applicative f => Monad f where
 >   (>>=) :: f s -> (s -> f t) -> f t
 >   instance Applicative f where
 >     ff <*> fs = ff >>= \f -> fs >>= \s -> return (f s)

Now, hark at the dog not barking in the nighttime.

 > instance Monad [] where
 >   return x = [x]
 >   [] >>= f = []
 >   (x : xs) >>= f = f x ++ xs >>= f

And away we go!

 > ex1 :: [Bool]
 > ex1 = fmap (>2) [0..9]

 > ex2 :: [Int]
 > ex2 = (| [1..6] + [1..6] |)  -- she has idiom brackets

 > ex3 :: [Int]
 > ex3 = do
 >   n <- [0..5]
 >   [0..n]

Let's go for win-win, or as close as we can get.

All the best

Conor




More information about the Libraries mailing list