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

From HaskellWiki
Jump to navigation Jump to search
(GHC Proposal)
(Rewrite the page!)
Line 1: Line 1:
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 standard class hierarchy is a consequence of Haskell's historical development, rather than logic.
   
  +
This article attempts to document various suggestions that have been brought up over the years, along with arguments for and against.
<haskell>
 
class Functor f where
 
map :: (a -> b) -> f a -> f b
 
   
class Functor f => Applicative f where
+
== Make <hask>Applicative</hask> a superclass of <hask>Monad</hask> ==
return :: a -> f a
 
(<*>) :: f (a -> b) -> f a -> f b
 
(*>) :: f a -> f b -> f b
 
(<*) :: f a -> f b -> f a
 
   
  +
<haskell>
 
class Applicative m => Monad m where
 
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
 
 
class Monad m => MonadFail m where
 
fail :: String -> m a
 
 
</haskell>
 
</haskell>
   
  +
=== For ===
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>].
 
   
  +
* Code that is polymorphic over the Monad can use Applicative operators rather than the ugly <hask>liftM</hask> and <hask>ap</hask>.
A monad which requires custom handling for pattern match failures can implement <hask>MonadFail</hask>; otherwise, a failed pattern match will error in the same way as is does for pure code.
 
   
  +
* Most types that implement Monad also implement Applicative already. This change will only make explicit a current best practice.
<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.
 
   
  +
=== Against ===
Backward compatibility could be eased with a legacy module, such as:
 
   
  +
* 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.
<haskell>
 
module Legacy where
 
   
  +
* 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.
fmap :: Functor f => (a -> b) -> f a -> f b
 
fmap = map
 
   
  +
== Add <hask>join</hask> as a method of <hask>Monad</hask> ==
liftA :: Applicative f => (a -> b) -> f a -> f b
 
liftA = map
 
 
liftM :: Monad m => (a -> b) -> m a -> m b
 
liftM = map
 
 
ap :: Monad m => m (a -> b) -> m a -> m b
 
ap = (<*>)
 
 
(>>) :: Monad m => m a -> m b -> m b
 
(>>) = (*>)
 
 
concat :: [[a]] -> [a]
 
concat = join
 
 
etc.
 
</haskell>
 
 
And for those who really want a list map,
 
   
 
<haskell>
 
<haskell>
  +
class Applicative m => Monad m where
listMap :: (a -> b) -> [a] -> [b]
 
  +
(>>=) :: (a -> m b) -> m a -> m b
listMap = map
 
  +
join :: m (m a) -> m a
  +
...
  +
m >>= k = join (fmap k m)
  +
join m = m >>= id
 
</haskell>
 
</haskell>
   
  +
=== For ===
[[Context alias]] would also be a great help with backwards compatibility. The [[class system extension proposal]] may also help.
 
   
  +
* <hask>fmap</hask>/<hask>join</hask> is more orthogonal than <hask>fmap</hask>/<hask>>>=</hask>, and the former is closer to the categorical definition.
Another variant might be to split a <hask>Pointed</hask> class from the <hask>Applicative</hask> class.
 
   
  +
* <hask>join</hask> is often easier to implement. See [http://article.gmane.org/gmane.comp.lang.haskell.libraries/14926].
<haskell>
 
class Pointed f where
 
return :: a -> f a
 
   
  +
* The analogous [http://hackage.haskell.org/packages/archive/comonad/3.0.2/doc/html/Control-Comonad.html comonad] package is written this way.
class (Functor f, Pointed f) => Applicative f where
 
(<*>) :: f (a -> b) -> f a -> f b
 
(*>) :: f a -> f b -> f b
 
(<*) :: f a -> f b -> f a
 
</haskell>
 
   
  +
=== Against ===
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.
 
   
  +
* <hask>>>=</hask> is used much more frequently in real-world code than <hask>join</hask>.
== GHC Proposal ==
 
A subset of this proposal has been formally proposed for GHC. The patches attached to the [http://hackage.haskell.org/trac/ghc/ticket/4834 ticket] make Applicative into a superclass of Monad, but does not deprecate any names.
 
   
  +
* Performance: The default implementation of <hask>>>=</hask> requires two traversals. Any container-like type which only implements <hask>fmap</hask> and <hask>join</hask> would be slower.
Copied from the [http://article.gmane.org/gmane.comp.lang.haskell.libraries/14905 mailing list]:
 
   
  +
== Remove <hask>liftM</hask>, <hask>ap</hask>, etc. in favor of their Applicative counterparts ==
The patch for base makes a few changes:
 
   
  +
=== For ===
1) Make Applicative a superclass of Monad. So the new hierarchy becomes:
 
<haskell>
 
class Functor f where
 
fmap :: (a -> b) -> f a -> f b
 
   
  +
* We will end up with a simpler base library.
(<$) :: a -> f b -> f a
 
(<$) = fmap . const
 
   
  +
=== Against ===
class Functor f => Applicative f where
 
pure :: a -> f a
 
   
  +
* A lot of code will be broken by this change. There is no compelling reason to remove these functions outright, rather than gradually deprecating them as with <hask>Prelude.catch</hask>.
(<*>) :: f (a -> b) -> f a -> f b
 
   
  +
* A common pattern is to write a full instance of Monad, then set <hask>fmap = liftM</hask> and <hask>(<*>) = ap</hask>.
(*>) :: f a -> f b -> f b
 
a *> b = fmap (const id) a <*> b
 
   
  +
== Split <hask>fail</hask> into its own class ==
(<*) :: 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
 
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
 
   
  +
<haskell>
  +
class Monad m => MonadFail m where
 
fail :: String -> m a
 
fail :: String -> m a
fail s = error s
 
 
</haskell>
 
</haskell>
2) Make 'join' a method of Monad.
 
   
  +
== Rename <hask>fmap</hask> to <hask>map</hask> ==
3) Export Applicative(pure, (<*>), (*>), (<*)) from the Prelude.
 
(Maybe we shouldn't export the (*>) and (<*) methods.)
 
   
4) Also export the join method from the Prelude.
+
== Export <hask>Applicative</hask> in the Prelude ==
   
  +
== Redefine <hask>>></hask> in terms of <hask>*></hask> rather than <hask>>>=</hask> ==
5) Add Applicative instances for all monads in base.
 
  +
  +
== Add a <hask>Pointed</hask> class ==
   
6) Add a Monad instance for ((,) a): (There are already Functor and
 
Applicative instances for it.)
 
 
<haskell>
 
<haskell>
  +
class Pointed p where
instance Monoid a => Monad ((,) a) where
 
(u, x) >>= f = let (v, y) = f x
+
point :: a -> p a
in (u `mappend` v, y)
 
 
</haskell>
 
</haskell>
(Maybe this one should be left out of the patch)
 
   
  +
This is already implemented in the [http://hackage.haskell.org/package/pointed pointed] package.
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:
 
   
  +
=== For ===
* 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)
 
* 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.
 
   
  +
=== Against ===
Note that all the ghc patches can be applied independently of the base patch.
 
   
  +
* 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.
Now which notable things are not included in the patch for base:
 
   
  +
== Related proposals ==
* fmap is not renamed to map.
 
* return and (>>) are not removed as a method.
 
* fail is not removed as a method.
 
* All the liftM functions are not removed in favour of fmap and liftAs.
 
   
  +
* 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
I think these are better left as separate proposals.
 
  +
** See [http://thread.gmane.org/gmane.comp.lang.haskell.libraries/14883/focus=14905] for the associated discussion.
  +
* [[The Other Prelude]]
   
  +
[[Context alias]] would also be a great help with backwards compatibility. The [[class system extension proposal]] may also help.
== See also ==
 
* A similar proposal exist on the wiki: [[The Other Prelude]]
 
   
 
[[Category:Proposals]]
 
[[Category:Proposals]]

Revision as of 02:05, 3 June 2013

The standard class hierarchy is a consequence of Haskell's historical development, rather than logic.

This article attempts to document various suggestions that have been brought up over the years, along with arguments for and against.

Make Applicative a superclass of Monad

class Applicative m => Monad m where
    ...

For

  • Code that is polymorphic over the Monad can use Applicative operators rather than the ugly liftM and ap.
  • 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 blaze-markup, only implement Monad for its do-notation. For these types, an Applicative instance would have no meaning.

Add join as a method of Monad

class Applicative m => Monad m where
    (>>=) :: (a -> m b) -> m a -> m b
    join :: m (m a) -> m a
    ...
    m >>= k = join (fmap k m)
    join m = m >>= id

For

  • fmap/join is more orthogonal than fmap/>>=, and the former is closer to the categorical definition.
  • join is often easier to implement. See [1].
  • The analogous comonad package is written this way.

Against

  • >>= is used much more frequently in real-world code than join.
  • Performance: The default implementation of >>= requires two traversals. Any container-like type which only implements fmap and join would be slower.

Remove liftM, ap, 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. There is no compelling reason to remove these functions outright, rather than gradually deprecating them as with Prelude.catch.
  • A common pattern is to write a full instance of Monad, then set fmap = liftM and (<*>) = ap.

Split fail into its own class

class Monad m => MonadFail m where
    fail :: String -> m a

Rename fmap to map

Export Applicative in the Prelude

Redefine >> in terms of *> rather than >>=

Add a Pointed class

class Pointed p where
    point :: a -> p a

This is already implemented in the pointed package.

For

Against

  • This class has seen little real-world use. On Hackage, there are only 9 reverse dependencies for pointed, most of which are by the same author.

Related proposals

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

Context alias would also be a great help with backwards compatibility. The class system extension proposal may also help.