Difference between revisions of "Functor-Applicative-Monad Proposal"

From HaskellWiki
Jump to navigation Jump to search
(Note about the possibility of splitting off a Pointed class)
m (→‎Beginner friendliness: Markdown -> Wiki markup: *x* to ''x'')
(25 intermediate revisions by 6 users not shown)
Line 1: Line 1:
  +
Haskell calls a couple of historical accidents its own. While some of them, such as the "number classes" hierarchy, can be justified by pragmatism or lack of a strictly better suggestion, there is one thing that stands out as, well, not that: Applicative not being a superclass of Monad.
The standard class hierarchy is a consequence of Haskell's historical development, rather than logic. The <hask>Functor</hask>, <hask>Applicative</hask>, and <hask>Monad</hask> type classes could be defined as:
 
   
  +
The topic has been discussed multiple times in the past (cf. link section at the very end). '''This article was updated to describe the current, and very likely to succeed, Haskell 2014 Applicative => Monad proposal (AMP)'''.
<haskell>
 
class Functor f where
 
map :: (a -> b) -> f a -> f b
 
   
  +
Some relevant links:
class Functor f => Applicative f where
 
  +
* [https://github.com/quchen/articles/blob/master/applicative_monad.md Initial text of the Haskell 2014 AMP]
return :: a -> f a
 
  +
* [http://article.gmane.org/gmane.comp.lang.haskell.libraries/19482 AMP mailing list discussion]
(<*>) :: f (a -> b) -> f a -> f b
 
  +
* Phase one: ticket [http://hackage.haskell.org/trac/ghc/ticket/8004 #8004]
(*>) :: f a -> f b -> f b
 
(<*) :: f a -> f b -> f a
 
   
class Applicative m => Monad m where
 
(>>=) :: m a -> (a -> m b) -> m b
 
f >>= x = join $ map f x
 
   
join :: m (m a) -> m a
 
join x = x >>= id
 
</haskell>
 
   
  +
== Proposal contents ==
This would eliminate the necessity of declaring a Monad instance for every Applicative, and eliminate the need for sets of duplicate functions such as [<hask>fmap</hask>, <hask>liftM</hask>, <hask>map</hask>, <hask>liftA</hask>], [<hask>(<*>)</hask>, <hask>ap</hask>], and [<hask>concat</hask>, <hask>join</hask>].
 
   
  +
The list of changes is as follows:
<hask>fail</hask> should be removed from Monad; a failed pattern match could error in the same way as is does for pure code. The only sensible uses for fail seem to be synonyms for <hask>mzero</hask>.
 
   
  +
# Applicative becomes a superclass of Monad, and is added to the Prelude.
<hask>Pointed</hask> has not been included due to controversy as to whether it should be a subclass of Functor, a superclass of Functor, independent of Functor, or perhaps it is not sufficiently useful to include at all.
 
  +
# Alternative becomes a superclass of MonadPlus (in addition to Monad, of course).
  +
# <hask>join</hask> is promoted into the Monad typeclass.
   
  +
The general rationale behind these changes:
Backward compatibility could be eased with a legacy module, such as:
 
   
  +
# ''Break as little code as possible.'' For example, do not move <hask>return</hask> to Applicative and remove <hask>pure</hask>. Instead, leave <hask>return</hask> in Monad, and give it <hask>pure</hask> as default implementation.
<haskell>
 
  +
# ''Change only things that are closely related to the proposal.'' For example, using <hask>join</hask> in a monad definition requires it to be a functor, so it goes hand in hand with the AMP. On the other hand, removing <hask>fail</hask> has nothing to do with what we're trying to accomplish.
module Legacy where
 
   
fmap :: Functor f => (a -> b) -> f a -> f b
 
fmap = map
 
   
liftA :: Applicative f => (a -> b) -> f a -> f b
 
liftA = map
 
   
  +
== Future-proofing current code ==
liftM :: Monad m => (a -> b) -> m a -> m b
 
liftM = map
 
   
  +
GHC 7.8 will issue two types of warnings in order to encourage wide-scale code fixing. The following describes how to get rid of them, and as a result ensures your code builds both now and after the AMP is finished.
ap :: Monad m => m (a -> b) -> m a -> m b
 
ap = (<*>)
 
   
  +
=== Missing superclasses ===
(>>) :: Monad m => m a -> m b -> m b
 
(>>) = (*>)
 
   
  +
(Warnings of the type "Warning: X is an instance of C, but not D")
concat :: [[a]] -> [a]
 
concat = join
 
   
  +
* Add Applicative/Functor instances for all your Monads. You can simply derive these instances from the Monad by adding the following code:
etc.
 
</haskell>
+
<haskell>
  +
import Control.Applicative (Applicative(..))
  +
import Control.Monad (liftM, ap)
   
  +
-- Monad m
And for those who really want a list map,
 
   
  +
instance Functor m where
  +
fmap = liftM
  +
  +
instance Applicative m where
  +
pure = return
  +
(<*>) = ap
  +
</haskell>
  +
  +
* Add an Alternative instance for all instances of MonadPlus. This can again be done easily using
 
<haskell>
 
<haskell>
  +
import Control.Applicative (Alternative(..))
listMap :: (a -> b) -> [a] -> [b]
 
  +
import Control.Monad (mzero, mplus)
listMap = map
 
  +
  +
-- MonadPlus m
  +
  +
instance Alternative m where
  +
(<|>) = mplus
  +
empty = mzero
 
</haskell>
 
</haskell>
   
  +
=== Future Prelude names ===
Another variant might be to split a <hask>Pointed</hask> class from the <hask>Applicative</hask> class.
 
   
  +
"The name X clashes with a future Prelude name" - Prelude will export functions called <hask><*></hask>, <hask>join</hask> and <hask>pure</hask>, so if a module defines its own versions of them, there will be name clashes. There are multiple ways of getting rid of this type of warning (in a future-proof way).
<haskell>
 
class Pointed f where
 
return :: a -> f a
 
   
  +
# Change your code to not define functions named <hask><*></hask>, <hask>join</hask> or <hask>pure</hask>.
class (Functor f, Pointed f) => Applicative f where
 
  +
# Import Prelude definitions you need explicitly. For example, <hask>import Prelude (map, (+))</hask> would not import <hask>join</hask>, so no warning is issued as the module is compatible with the Prelude exporting <hask>join</hask>. <hask>hiding</hask>.
(<*>) :: f (a -> b) -> f a -> f b
 
  +
# Due to GHC internals, you cannot use <hask>hiding (join, (<*>), pure)</hask> to silence the warnings, although this method would be future-proof. If you want to use <hask>hiding</hask>, you will have to silence the warnings using a sledgehammer <code>-fno-warn-amp</code> compiler flag. (If you do so make sure you know what you're doing, otherwise your module ''will'' break in 7.10.) To make 7.10 not complain about the then unrecognized flag, it's best to specify it in a CPP block,
(*>) :: f a -> f b -> f b
 
  +
<haskell>
(<*) :: f a -> f b -> f a
 
  +
{-# LANGUAGE CPP #-}
  +
#if __GLASGOW_HASKELL__ >= 707 && __GLASGOW_HASKELL__ < 710
  +
{-# OPTIONS_GHC -fno-warn-amp #-}
  +
#endif
 
</haskell>
 
</haskell>
   
  +
== Discussion and consequences ==
Such <hask>Pointed</hask> functionality by itself could be useful, for example, in a DSL in which it is only possible to embed values and not to lift functions to functions over those embedded values.
 
  +
  +
  +
=== It's the right thing to do™ ===
  +
  +
Math. You've all heard this one, it's good and compelling so I don't need to spell it out.
  +
  +
  +
=== Redundant functions ===
  +
  +
* <hask>pure</hask> and <hask>return</hask> do the same thing.
  +
* <hask>>></hask> and <hask>*></hask> are identical.
  +
* <hask>liftM</hask> and <hask>liftA</hask> are <hask>fmap</hask>. The <hask>liftM*</hask> are <hask>liftA*</hask>, <hask><*></hask> is <hask>ap</hask>.
  +
* Prelude's <hask>sequence</hask> requres <hask>Monad</hask> right now, while <hask>Applicative</hask> is sufficient to implement it. The more general version of this issue is captured by <hask>Data.Traversable</hask>, whose main typeclass implements the *same* functionality twice, namely <hask>traverse</hask> and <hask>mapM</hask>, and <hask>sequenceA</hask> and <hask>sequence</hask>.
  +
* The <hask>WrappedMonad</hask> type from <hask>Control.Applicative</hask> provides a semi-automatic way to using Functor/Applicative/Alternative functions for Monad/MonadPlus instances as a makeshift patch.
  +
  +
That very much violates the "don't repeat yourself" principle, and even more so it ''forces'' the programmer to repeat himself to achieve maximal generality. It may be too late to take all redundancies out, but at least we can prevent new ones from being created.
  +
  +
(Note that it is not proposed to remove any functions for compatibility reasons. Maybe some of them can be phased out in the long run, but that's beyond scope here.)
  +
  +
  +
=== Using Functor/Applicative functions in monadic code ===
  +
  +
Whenever there's Monad code, you can use Functor/Applicative functions, without introducing an additional constraint. Keep in mind that "Functor/Applicative functions" does not only include what their typeclasses define but many more, for example <hask>void</hask>, <hask>(<$>)</hask>, <hask>(<**>)</hask>.
  +
  +
Even if you think you have monadic code, strictly using the least restrictive functions may result in something that requires only Applicative. This is similar to writing a function that needs <hask>Int</hask>, but it turns out any <hask>Integral</hask> will do - more polymorphism for free.
  +
  +
  +
=== Compatibility issues ===
  +
  +
These are the kinds of issues to be expected:
  +
  +
# Monads lacking Functor or Applicative instances. This is easily fixable by either setting <hask>fmap = liftM</hask>, <hask>pure = return</hask> and <hask>(<*>) = ap</hask>, although more efficient implementations may exist, or by moving an already existing definition from <hask>Control.Applicative</hask> to the appropriate module.
  +
# This one is specific to building GHC: importing <hask>Control.Monad/Applicative</hask> introduces a circular module dependency. In this case, one can rely on handwritten implementations of the desired function, e.g. <hask>ap f x = f >>= ...</hask>.
  +
# Libraries using their own <hask>(<*>)</hask>. This one is potentially the most laborious consequence. For building GHC though, this only concerns Hoopl, and a handful of renames.
  +
  +
  +
  +
=== Beginner friendliness ===
  +
  +
How often did you say ...
  +
  +
* "A Monad is always an Applicative but due to historical reasons it's not but you can easily verify it by setting <hask>pure = return</hask> and <hask>(<*>) = ap</hask>"
  +
* "<hask>liftM</hask> is <hask>fmap</hask> but not really." - "So when should I use <hask>fmap</hask> and when <hask>liftM</hask>?" - ''sigh''
  +
  +
With the new hierarchy, the answer would ''always'' be "use the least restrictive one".
  +
  +
== Applying the AMP to GHC and then Haskell in practice ==
  +
  +
Proposed is a gradual introduction of the AMP in three phases:
  +
  +
  +
=== '''Current stage''': Prepare GHC ===
  +
  +
Using a GHC fork with the full patch applied, find and fix all compilation errors introduced by the change by adding Functor/Applicative instances for all Monads.
  +
  +
According to SPJ, adding an ad-hoc warning of sorts "Monad without Applicative detected" is not a problem, which will be crucial for the next phase. More specifically, issue a warning if:
  +
  +
* Monad without Applicative
  +
* MonadPlus without Alternative
  +
* One of <hask><*></hask>, <hask>pure</hask>, <hask>join</hask> is defined in a different context to avoid naming conflicts, as these functions will go into the Prelude
  +
  +
=== Prepare Hackage ===
  +
  +
The warning just mentioned will hint to all authors that they should fix (or help others fix) the non-complying packages. This will ideally lead to libraries eventually adding Applicative instances, and changing their APIs if they redefine operators like <hask><*></hask>.
  +
  +
After enough time has passed by so libraries adapted to the circumstances, move on to the next phase.
  +
  +
  +
=== Apply the proposal ===
  +
  +
Once Hackage is prepared, applying the changes to the Base package is painless. However, this is not primarily a GHC, but a Haskell change. The previous steps were basically preparing the landscape, and when we've (hopefully) found out that it is a good idea to go through with it, it can be proposed to go into the Report. If we make it this far, the AMP should pass quite easily.
  +
  +
  +
  +
== Previous proposals ==
  +
  +
* Early 2011: [http://hackage.haskell.org/trac/ghc/ticket/4834 GHC ticket] &ndash; changes similar to this proposal, but closed as "not GHC, but Haskell". See [http://thread.gmane.org/gmane.comp.lang.haskell.libraries/14883/focus=14905 here] for the associated discussion.
  +
* [[The Other Prelude]]
  +
   
 
[[Category:Proposals]]
 
[[Category:Proposals]]

Revision as of 13:32, 3 December 2013

Haskell calls a couple of historical accidents its own. While some of them, such as the "number classes" hierarchy, can be justified by pragmatism or lack of a strictly better suggestion, there is one thing that stands out as, well, not that: Applicative not being a superclass of Monad.

The topic has been discussed multiple times in the past (cf. link section at the very end). This article was updated to describe the current, and very likely to succeed, Haskell 2014 Applicative => Monad proposal (AMP).

Some relevant links:


Proposal contents

The list of changes is as follows:

  1. Applicative becomes a superclass of Monad, and is added to the Prelude.
  2. Alternative becomes a superclass of MonadPlus (in addition to Monad, of course).
  3. join is promoted into the Monad typeclass.

The general rationale behind these changes:

  1. Break as little code as possible. For example, do not move return to Applicative and remove pure. Instead, leave return in Monad, and give it pure as default implementation.
  2. Change only things that are closely related to the proposal. For example, using join in a monad definition requires it to be a functor, so it goes hand in hand with the AMP. On the other hand, removing fail has nothing to do with what we're trying to accomplish.


Future-proofing current code

GHC 7.8 will issue two types of warnings in order to encourage wide-scale code fixing. The following describes how to get rid of them, and as a result ensures your code builds both now and after the AMP is finished.

Missing superclasses

(Warnings of the type "Warning: X is an instance of C, but not D")

  • Add Applicative/Functor instances for all your Monads. You can simply derive these instances from the Monad by adding the following code:
import Control.Applicative (Applicative(..))
import Control.Monad       (liftM, ap)

-- Monad m

instance Functor m where
    fmap = liftM

instance Applicative m where
    pure  = return
    (<*>) = ap
  • Add an Alternative instance for all instances of MonadPlus. This can again be done easily using
import Control.Applicative (Alternative(..))
import Control.Monad       (mzero, mplus)

-- MonadPlus m

instance Alternative m where
    (<|>) = mplus
    empty = mzero

Future Prelude names

"The name X clashes with a future Prelude name" - Prelude will export functions called <*>, join and pure, so if a module defines its own versions of them, there will be name clashes. There are multiple ways of getting rid of this type of warning (in a future-proof way).

  1. Change your code to not define functions named <*>, join or pure.
  2. Import Prelude definitions you need explicitly. For example, import Prelude (map, (+)) would not import join, so no warning is issued as the module is compatible with the Prelude exporting join. hiding.
  3. Due to GHC internals, you cannot use hiding (join, (<*>), pure) to silence the warnings, although this method would be future-proof. If you want to use hiding, you will have to silence the warnings using a sledgehammer -fno-warn-amp compiler flag. (If you do so make sure you know what you're doing, otherwise your module will break in 7.10.) To make 7.10 not complain about the then unrecognized flag, it's best to specify it in a CPP block,
{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 707 && __GLASGOW_HASKELL__ < 710
{-# OPTIONS_GHC -fno-warn-amp #-}
#endif

Discussion and consequences

It's the right thing to do™

Math. You've all heard this one, it's good and compelling so I don't need to spell it out.


Redundant functions

  • pure and return do the same thing.
  • >> and *> are identical.
  • liftM and liftA are fmap. The liftM* are liftA*, <*> is ap.
  • Prelude's sequence requres Monad right now, while Applicative is sufficient to implement it. The more general version of this issue is captured by Data.Traversable, whose main typeclass implements the *same* functionality twice, namely traverse and mapM, and sequenceA and sequence.
  • The WrappedMonad type from Control.Applicative provides a semi-automatic way to using Functor/Applicative/Alternative functions for Monad/MonadPlus instances as a makeshift patch.

That very much violates the "don't repeat yourself" principle, and even more so it forces the programmer to repeat himself to achieve maximal generality. It may be too late to take all redundancies out, but at least we can prevent new ones from being created.

(Note that it is not proposed to remove any functions for compatibility reasons. Maybe some of them can be phased out in the long run, but that's beyond scope here.)


Using Functor/Applicative functions in monadic code

Whenever there's Monad code, you can use Functor/Applicative functions, without introducing an additional constraint. Keep in mind that "Functor/Applicative functions" does not only include what their typeclasses define but many more, for example void, (<$>), (<**>).

Even if you think you have monadic code, strictly using the least restrictive functions may result in something that requires only Applicative. This is similar to writing a function that needs Int, but it turns out any Integral will do - more polymorphism for free.


Compatibility issues

These are the kinds of issues to be expected:

  1. Monads lacking Functor or Applicative instances. This is easily fixable by either setting fmap = liftM, pure = return and (<*>) = ap, although more efficient implementations may exist, or by moving an already existing definition from Control.Applicative to the appropriate module.
  2. This one is specific to building GHC: importing Control.Monad/Applicative introduces a circular module dependency. In this case, one can rely on handwritten implementations of the desired function, e.g. ap f x = f >>= ....
  3. Libraries using their own (<*>). This one is potentially the most laborious consequence. For building GHC though, this only concerns Hoopl, and a handful of renames.


Beginner friendliness

How often did you say ...

  • "A Monad is always an Applicative but due to historical reasons it's not but you can easily verify it by setting pure = return and (<*>) = ap"
  • "liftM is fmap but not really." - "So when should I use fmap and when liftM?" - sigh

With the new hierarchy, the answer would always be "use the least restrictive one".

Applying the AMP to GHC and then Haskell in practice

Proposed is a gradual introduction of the AMP in three phases:


Current stage: Prepare GHC

Using a GHC fork with the full patch applied, find and fix all compilation errors introduced by the change by adding Functor/Applicative instances for all Monads.

According to SPJ, adding an ad-hoc warning of sorts "Monad without Applicative detected" is not a problem, which will be crucial for the next phase. More specifically, issue a warning if:

  • Monad without Applicative
  • MonadPlus without Alternative
  • One of <*>, pure, join is defined in a different context to avoid naming conflicts, as these functions will go into the Prelude

Prepare Hackage

The warning just mentioned will hint to all authors that they should fix (or help others fix) the non-complying packages. This will ideally lead to libraries eventually adding Applicative instances, and changing their APIs if they redefine operators like <*>.

After enough time has passed by so libraries adapted to the circumstances, move on to the next phase.


Apply the proposal

Once Hackage is prepared, applying the changes to the Base package is painless. However, this is not primarily a GHC, but a Haskell change. The previous steps were basically preparing the landscape, and when we've (hopefully) found out that it is a good idea to go through with it, it can be proposed to go into the Report. If we make it this far, the AMP should pass quite easily.


Previous proposals

  • Early 2011: GHC ticket – changes similar to this proposal, but closed as "not GHC, but Haskell". See here for the associated discussion.
  • The Other Prelude