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

From HaskellWiki
Jump to navigation Jump to search
(Add more things!)
(Updated for AMP 2014)
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 topic has been discussed multiple times in the past (cf. link section at the bottom). '''This article was updated to describe the current, and very likely to succeed, Haskell 2014 Applicative => Monad proposal'''.
This article attempts to document various suggestions that have been brought up over the years, along with arguments for and against.
 
   
  +
== Pragmatic and short version ==
== Make <hask>Applicative</hask> a superclass of <hask>Monad</hask> ==
 
   
  +
The following is a list of things you may have to change in your code so the AMP doesn't break it.
<haskell>
 
class Applicative m => Monad m where
 
...
 
</haskell>
 
 
=== For ===
 
 
* Code that is polymorphic over the Monad can use Applicative operators rather than the ugly <hask>liftM</hask> and <hask>ap</hask>.
 
 
* Most types that implement Monad also implement Applicative already. This change will only make explicit a current best practice.
 
 
=== Against ===
 
 
* Monad is part of standard Haskell, but Applicative is not. If Monad is made a subclass of Applicative, then we will need to add Applicative to the language standard.
 
 
* Some libraries, such as [http://hackage.haskell.org/packages/archive/blaze-markup/0.5.1.5/doc/html/Text-Blaze-Internal.html#t:MarkupM blaze-markup], only implement Monad for its do-notation. For these types, an Applicative instance would have no meaning.
 
 
== Add <hask>join</hask> as a method of <hask>Monad</hask> ==
 
   
  +
* Add Applicative/Functor instances for all your Monads. If you don't care about efficiency, you can simply derive these instances from the Monad by adding the following code:
 
<haskell>
 
<haskell>
class Applicative m => Monad m where
+
-- Monad m
(>>=) :: (a -> m b) -> m a -> m b
 
join :: m (m a) -> m a
 
...
 
m >>= k = join (fmap k m)
 
join m = m >>= id
 
</haskell>
 
   
  +
import Control.Monad (liftM, ap)
=== For ===
 
  +
import Control.Applicative (Applicative(..))
   
 
instance Functor m where
* <hask>fmap</hask>/<hask>join</hask> is more orthogonal, and is closer to the categorical definition.
 
  +
fmap = liftM
   
 
instance Applicative m where
* <hask>join</hask> is often easier to implement. See [http://article.gmane.org/gmane.comp.lang.haskell.libraries/14926].
 
  +
pure = return
 
  +
(<*>) = ap
* The analogous [http://hackage.haskell.org/packages/archive/comonad/3.0.2/doc/html/Control-Comonad.html comonad] package is written this way.
 
 
=== Against ===
 
 
* <hask>>>=</hask> is used much more frequently in real-world code than <hask>join</hask>.
 
 
* Performance: The default implementation of <hask>>>=</hask> requires two traversals. A container-like type which only implements <hask>join</hask> would most likely be slower.
 
 
== Remove <hask>liftM</hask>, <hask>ap</hask>, etc. in favor of their Applicative counterparts ==
 
 
=== For ===
 
 
* We will end up with a simpler base library.
 
 
=== Against ===
 
 
* A lot of code will be broken by this change. Of course, we can gradually deprecate them as with <hask>Prelude.catch</hask>.
 
 
* A common pattern is to write a full instance of Monad, then set <hask>fmap = liftM</hask> and <hask>(<*>) = ap</hask>. The functions are still useful for this purpose.
 
 
== Split <hask>fail</hask> into its own class ==
 
 
<haskell>
 
class Monad m => MonadFail m where
 
fail :: String -> m a
 
 
</haskell>
 
</haskell>
   
  +
* Add an Alternative instance for all instances of MonadZero. This can again be done easily using
== Rename <hask>fmap</hask> to <hask>map</hask> ==
 
 
 
<haskell>
 
<haskell>
  +
-- MonadZero m
class Functor f where
 
map :: (a -> b) -> f a -> f b
 
</haskell>
 
   
  +
import Control.Monad (mzero, mplus)
== Export <hask>Applicative</hask> in the Prelude ==
 
  +
import Control.Applicative (Alternative(..))
   
  +
instance Alternative m where
== Redefine <hask>>></hask> in terms of <hask>*></hask> rather than <hask>>>=</hask> ==
 
  +
(<|>) = mplus
 
  +
empty = mzero
== Add a <hask>Pointed</hask> class ==
 
 
<haskell>
 
class Pointed p where
 
point :: a -> p a
 
 
</haskell>
 
</haskell>
   
  +
* Change your API to not define functions named <hask><*></hask>, <hask>join</hask> or <hask>pure</hask>
This is already implemented in the [http://hackage.haskell.org/package/pointed pointed] package.
 
   
=== For ===
+
== Detailed description ==
   
  +
[https://github.com/quchen/articles/blob/master/applicative_monad.md Main text of the Haskell 2014 AMP]
=== Against ===
 
   
  +
[http://article.gmane.org/gmane.comp.lang.haskell.libraries/19482 Mailing list discussion of the proposal]
* This class has seen little real-world use. On Hackage, there are only [http://packdeps.haskellers.com/reverse/pointed 9 reverse dependencies] for <code>pointed</code>, most of which are by the same author.
 
   
== Related proposals ==
+
== Previous proposals ==
   
 
* From early 2011: [http://hackage.haskell.org/trac/ghc/ticket/4834 GHC ticket] &ndash; Makes Applicative into a superclass of Monad, but does not deprecate any existing names
 
* From early 2011: [http://hackage.haskell.org/trac/ghc/ticket/4834 GHC ticket] &ndash; Makes Applicative into a superclass of Monad, but does not deprecate any existing names
Line 98: Line 48:
 
* [[The Other Prelude]]
 
* [[The Other Prelude]]
   
[[Context alias]] would also be a great help with backwards compatibility. The [[class system extension proposal]] may also help.
 
   
 
[[Category:Proposals]]
 
[[Category:Proposals]]

Revision as of 12:58, 17 June 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 bottom). This article was updated to describe the current, and very likely to succeed, Haskell 2014 Applicative => Monad proposal.

Pragmatic and short version

The following is a list of things you may have to change in your code so the AMP doesn't break it.

  • Add Applicative/Functor instances for all your Monads. If you don't care about efficiency, you can simply derive these instances from the Monad by adding the following code:
-- Monad m

import Control.Monad       (liftM, ap)
import Control.Applicative (Applicative(..))

instance Functor m where
    fmap = liftM

instance Applicative m where
    pure  = return
    (<*>) = ap
  • Add an Alternative instance for all instances of MonadZero. This can again be done easily using
-- MonadZero m

import Control.Monad       (mzero, mplus)
import Control.Applicative (Alternative(..))

instance Alternative m where
    (<|>) = mplus
    empty = mzero
  • Change your API to not define functions named <*>, join or pure

Detailed description

Main text of the Haskell 2014 AMP

Mailing list discussion of the proposal

Previous proposals

  • From early 2011: GHC ticket – Makes Applicative into a superclass of Monad, but does not deprecate any existing names
    • See [1] for the associated discussion.
  • The Other Prelude