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

From HaskellWiki
Jump to navigation Jump to search
m (adding The Other Prelude reference)
(GHC Proposal)
(4 intermediate revisions by 2 users not shown)
Line 61: Line 61:
 
</haskell>
 
</haskell>
   
[[Context alias]] would also be a great help with backwards compatibility.
+
[[Context alias]] would also be a great help with backwards compatibility. The [[class system extension proposal]] may also help.
   
 
Another variant might be to split a <hask>Pointed</hask> class from the <hask>Applicative</hask> class.
 
Another variant might be to split a <hask>Pointed</hask> class from the <hask>Applicative</hask> class.
Line 77: Line 77:
 
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.
 
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.
   
  +
== 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.
  +
  +
Copied from the [http://article.gmane.org/gmane.comp.lang.haskell.libraries/14905 mailing list]:
  +
  +
The patch for base makes a few changes:
  +
  +
1) Make Applicative a superclass of Monad. So the new hierarchy becomes:
  +
<haskell>
  +
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
  +
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
  +
</haskell>
  +
2) Make 'join' a method of Monad.
  +
  +
3) Export Applicative(pure, (<*>), (*>), (<*)) from the Prelude.
  +
(Maybe we shouldn't export the (*>) and (<*) methods.)
  +
  +
4) Also export the join method from the Prelude.
  +
  +
5) Add Applicative instances for all monads in base.
  +
  +
6) Add a Monad instance for ((,) a): (There are already Functor and
  +
Applicative instances for it.)
  +
<haskell>
  +
instance Monoid a => Monad ((,) a) where
  +
(u, x) >>= f = let (v, y) = f x
  +
in (u `mappend` v, y)
  +
</haskell>
  +
(Maybe this one should be left out of the patch)
  +
  +
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)
  +
* 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.
  +
  +
Note that all the ghc patches can be applied independently of the base patch.
  +
  +
Now which notable things are not included in the patch for base:
  +
  +
* 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.
  +
  +
I think these are better left as separate proposals.
   
 
== See also ==
 
== See also ==
 
* A similar proposal exist on the wiki: [[The Other Prelude]]
 
* A similar proposal exist on the wiki: [[The Other Prelude]]
 
   
 
[[Category:Proposals]]
 
[[Category:Proposals]]

Revision as of 07:13, 4 January 2011

The standard class hierarchy is a consequence of Haskell's historical development, rather than logic. The Functor, Applicative, and Monad type classes could be defined as:

class Functor f where
    map :: (a -> b) -> f a -> f b

class Functor f => Applicative f where
    return :: a -> f a
    (<*>) :: f (a -> b) -> f a -> f b
    (*>) :: 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

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

This would eliminate the necessity of declaring a Monad instance for every Applicative, and eliminate the need for sets of duplicate functions such as [fmap, liftM, map, liftA], [(<*>), ap], and [concat, join].

A monad which requires custom handling for pattern match failures can implement MonadFail; otherwise, a failed pattern match will error in the same way as is does for pure code.

Pointed 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.

Backward compatibility could be eased with a legacy module, such as:

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

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.

And for those who really want a list map,

listMap :: (a -> b) -> [a] -> [b]
listMap = map

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

Another variant might be to split a Pointed class from the Applicative class.

class Pointed f where
    return :: a -> f a

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

Such Pointed 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.

GHC Proposal

A subset of this proposal has been formally proposed for GHC. The patches attached to the ticket make Applicative into a superclass of Monad, but does not deprecate any names.

Copied from the mailing list:

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
    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.

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

4) Also export the join method from the Prelude.

5) Add Applicative instances for all monads in base.

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

instance Monoid a => Monad ((,) a) where
        (u, x) >>= f = let (v, y) = f x
                       in (u `mappend` v, y)

(Maybe this one should be left out of the patch)

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)

  • 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.

Note that all the ghc patches can be applied independently of the base patch.

Now which notable things are not included in the patch for base:

  • 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.

I think these are better left as separate proposals.

See also