Proposal: Applicative => Monad: Call for consensus

Henning Thielemann lemming at henning-thielemann.de
Fri Jan 7 11:59:53 CET 2011


Bas van Dijk schrieb:

> The patch for base makes a few changes:
> 
> 1) Make Applicative a superclass of Monad. So the new hierarchy becomes:
> 
> class  Functor f  where
>     fmap        :: (a -> b) -> f a -> f b
> 
>     (<$)        :: a -> f b -> f a
>     (<$)        =  fmap . const
> 
> class Functor f => Applicative f where
>     pure :: a -> f a
> 
>     (<*>) :: f (a -> b) -> f a -> f b
> 
>     (*>) :: f a -> f b -> f b
>     a *> b = fmap (const id) a <*> b
> 
>     (<*) :: f a -> f b -> f a
>     a <* b = fmap const a <*> b
> 
> class Applicative m => Monad m  where
>     (>>=) :: forall a b. m a -> (a -> m b) -> m b

Is the explicit 'forall' intended?

>     m >>= f = join $ fmap f m
> 
>     join :: m (m a) -> m a
>     join m = m >>= id
> 
>     (>>) :: forall a b. m a -> m b -> m b
>     (>>) = (*>)
> 
>     return :: a -> m a
>     return = pure
> 
>     fail :: String -> m a
>     fail s = error s
> 
> 2) Make 'join' a method of Monad.

Is there a need for it?

> 3) Export Applicative(pure, (<*>), (*>), (<*)) from the Prelude.
> (Maybe we shouldn't export the (*>) and (<*) methods.)

No, please avoid that. Importing Applicative explicitly is completely ok
for me. I use (<*>) already for scalar product in NumericPrelude. For me
it looks like a commutative operator, which Applicative.<*> is not. The
existence of (<*>) in Applicative module is ok for me, but I do not want
name clashes with it when automatically imported by Prelude.

If at all, Functor stuff should be moved from Control.Applicative and
Control.Monad to a new module Control.Functor (and could be re-exported
by Control.Applicative and Control.Monad for compatibility reasons).
Then fmap could be renamed to 'map' and used as F.map (using "import
qualified Control.Functor as F"). All those infix operators for Monad
and Functor are not so important for me to be imported automatically
from Prelude. Thus I would not like to move Applicative in this direction.

> 4) Also export the join method from the Prelude.

no please, as above

> 5) Add Applicative instances for all monads in base.

+1

> 6) Add a Monad instance for ((,) a): (There are already Functor and
> Applicative instances for it.)

That is, a Writer instance?

I am uncertain about it, because using it may hide a bug. So far I am
happy with Writer from transformers package. Using Writer explicitly
shows everybody, what I am doing and that I do it intentionally.

> The patch for ghc simply adds Applicative instances for all monads in
> ghc. Also included in the ghc patch bundle are some refactoring
> patches that will make the transition easier:
> 
> * Added (<>) = mappend to compiler/utils/Util.hs.
> * Add a Monoid instance for AGraph and remove the <*> splice operator.
> Instead of <*>, the (<>) = mappend operator is now used to splice AGraphs.
> This change is needed because <*> clashes with the Applicative apply
> operator <*>, which is probably going to be exported from the Prelude
> when the new Monad hierarchy is going through. (Simply hiding <*> from
> the Prelude is also possible of course. However, I think this makes
> things easier to understand)

For me this is another argument against automatic import of (<*>).

> * Make SDoc an abstract newtype and add a Monoid instance for it.
> The (<>) combinator of SDocs is removed and replaced by the more
> general (<>) = mappend combinator from Util.

An infix operator for monoids would be nice, indeed. Why not use
something that resembles (++), which is the "mappend" for lists? I am
uncertain. Maybe something containing '+' looks too commutative. :-) But
'<>' looks too much like 'not equal' in other languages.




More information about the Libraries mailing list