PROPOSAL: Make Applicative a superclass of Monad

http://hackage.haskell.org/trac/ghc/ticket/2392 Make Applicative (in Control.Applicative) a superclass of Monad (in Control.Monad). Rename members of Applicative and other functions, to avoid unnecessary duplication. class Functor f => Applicative f where return :: a -> f a ap :: f (a -> b) -> f a -> f b liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 f a b = ap (fmap f a) b (>>) :: (Applicative f) => f a -> f b -> f b (>>) = liftA2 (const id) -- etc. class Applicative m => Monad m where (>>=) :: m a -> (a -> m b) -> m b fail :: String -> m a fail s = error s I do not have a patch for this change, as it involves mucking around with GHC.Base, and I strongly suspect also fiddling with the GHC source. I'd like to know if it's feasible first. Discussion period: a month? -- Ashley Yakeley

On Tue, Jun 24, 2008 at 02:15:19AM -0700, Ashley Yakeley wrote:
http://hackage.haskell.org/trac/ghc/ticket/2392
Make Applicative (in Control.Applicative) a superclass of Monad (in Control.Monad). Rename members of Applicative and other functions, to avoid unnecessary duplication.
The big problem with this is that it would break compatibility with Haskell 98, and any existing program that defines a Monad instance.

Could someone explain why it breaks H98 compatibility? Control.Applicative alone is at least marked "portable". Thanks Christian Ross Paterson wrote:
On Tue, Jun 24, 2008 at 02:15:19AM -0700, Ashley Yakeley wrote:
http://hackage.haskell.org/trac/ghc/ticket/2392
Make Applicative (in Control.Applicative) a superclass of Monad (in Control.Monad). Rename members of Applicative and other functions, to avoid unnecessary duplication.
The big problem with this is that it would break compatibility with Haskell 98, and any existing program that defines a Monad instance.

On Tue, Jun 24, 2008 at 01:43:08PM +0200, Christian Maeder wrote:
Could someone explain why it breaks H98 compatibility? Control.Applicative alone is at least marked "portable".
The following Haskell 98 code would be rejected: newtype Id a = Id a instance Monad Id where return = Id Id x >>= f = f x

Henning Thielemann wrote:
On Tue, 24 Jun 2008, Christian Maeder wrote:
Could someone explain why it breaks H98 compatibility? Control.Applicative alone is at least marked "portable".
Because existing Monad instances in user code would become invalid.
Ok, I was thinking in terms of language features (not in terms of backward compatibility of the Standard Library). Christian

On Tue, Jun 24, 2008 at 01:43:08PM +0200, Christian Maeder wrote:
Could someone explain why it breaks H98 compatibility? Control.Applicative alone is at least marked "portable".
This Haskell98 module no longer works: module Foo where data Foo a = Foo instance Monad Foo where return _ = Foo Thanks Ian

Hello Ashley, Tuesday, June 24, 2008, 1:15:19 PM, you wrote:
Make Applicative (in Control.Applicative) a superclass of Monad (in
it will break H98 compatibility - some code written in H98 will be impossible to compile with such library. since GHC is (among other features) provides full H98 compatibility, we can't make such change well, at least i expect such answer from GHC HQ :) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello Ashley,
Tuesday, June 24, 2008, 1:15:19 PM, you wrote:
Make Applicative (in Control.Applicative) a superclass of Monad (in
it will break H98 compatibility - some code written in H98 will be impossible to compile with such library. since GHC is (among other features) provides full H98 compatibility, we can't make such change
Is there any practical way we can make this change while still making it possible to compile Haskell98 programs at all? It seems that even with a compiler flag, it will be difficult to do with current haskell implementations (at the very least, a different Monad class would have to be exported from haskell98 modules than from... modern modules.)

On Jun 24, 2008, at 09:57 , Isaac Dupree wrote:
Bulat Ziganshin wrote:
Hello Ashley, Tuesday, June 24, 2008, 1:15:19 PM, you wrote:
Make Applicative (in Control.Applicative) a superclass of Monad (in it will break H98 compatibility - some code written in H98 will be impossible to compile with such library. since GHC is (among other features) provides full H98 compatibility, we can't make such change
Is there any practical way we can make this change while still making it possible to compile Haskell98 programs at all? It seems that even with a compiler flag, it will be difficult to do with
Problem there is that Monad is exported by Prelude. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

G'day all.
Quoting Isaac Dupree
Is there any practical way we can make this change while still making it possible to compile Haskell98 programs at all?
This is being redirected to haskell-prime, of course, however, while we're on the topic, it needs to be said yet again: It's a severe pain to make class hierarchies more granular if you have to declare an instance for all of them. I support the principle of making Applicative a superclass of Monad. However, I don't want to have to declare an instance for Functor and Applicative just to declare an instance for Monad. There are obvious defaults, and I should be able to get them with no effort, or at the very least, no more effort than a "deriving"-like annotation. Cheers, Andrew Bromage

On Tue, Jun 24, 2008 at 09:57:39AM -0400, Isaac Dupree wrote:
Is there any practical way we can make this change while still making it possible to compile Haskell98 programs at all? It seems that even with a compiler flag, it will be difficult to do with current haskell implementations (at the very least, a different Monad class would have to be exported from haskell98 modules than from... modern modules.)
This is one of the issue 'class aliases' were created to address. John -- John Meacham - ⑆repetae.net⑆john⑈

Ashley Yakeley
Make Applicative (in Control.Applicative) a superclass of Monad (in Control.Monad).
I'm strongly against. Some datatypes have several different possible implementations of Applicative, for instance, they may be either lazy or strict. The PolyParse library relies crucially on the fact that the Monad and Applicative instances for the Parser type have different strictness behaviours. I worry that if Applicative were to become a superclass of Monad, this way of partitioning my API into lazy and strict portions may no longer be possible, or least, a good deal less convenient. Regards, Malcolm Footnote. PolyParse does not currently use the real Applicative class, but it probably ought to.

On Tue, 24 Jun 2008, Malcolm Wallace wrote:
Ashley Yakeley
wrote: Make Applicative (in Control.Applicative) a superclass of Monad (in Control.Monad).
I'm strongly against.
Some datatypes have several different possible implementations of Applicative, for instance, they may be either lazy or strict. The PolyParse library relies crucially on the fact that the Monad and Applicative instances for the Parser type have different strictness behaviours.
I worry that if Applicative were to become a superclass of Monad, this way of partitioning my API into lazy and strict portions may no longer be possible, or least, a good deal less convenient.
Although I also see no compatible way to make Applicative a superclass of Monad, I think it should be so. Intuitively it is a superclass and it would surprise me if a library has inconsistent instances of Applicative and Monad. So I count your example as argument _for_ making Applicative a superclass of Monad in order to reduce the risk of surprises for the library user.

Malcolm Wallace wrote:
I'm strongly against.
Some datatypes have several different possible implementations of Applicative, for instance, they may be either lazy or strict. The PolyParse library relies crucially on the fact that the Monad and Applicative instances for the Parser type have different strictness behaviours.
I worry that if Applicative were to become a superclass of Monad, this way of partitioning my API into lazy and strict portions may no longer be possible, or least, a good deal less convenient.
Do you have an example of this? I should make (>>) a member of Applicative. Would that address you concern? Or are (Applicative) pure and (Monad) return different for your type? I intend to re-submit this for Haskell Prime. -- Ashley Yakeley

On Tue, Jun 24, 2008 at 11:14:41AM +0100, Malcolm Wallace wrote:
Some datatypes have several different possible implementations of Applicative, for instance, they may be either lazy or strict. The PolyParse library relies crucially on the fact that the Monad and Applicative instances for the Parser type have different strictness behaviours.
I think you're abusing the class, and it's bound to go wrong sooner or later. A monad is morally an applicative functor, and clients ought to be able to assume, as the docs say, that pure = return and (<*>) = ap. The lazy and strict things should be different types.

On Tue, Jun 24, 2008 at 02:15:19AM -0700, Ashley Yakeley wrote:
http://hackage.haskell.org/trac/ghc/ticket/2392
Make Applicative (in Control.Applicative) a superclass of Monad (in Control.Monad).
I agree with what other people have said about H98 compatibility. I think you would be better off proposing this for Haskell'. Thanks Ian

Ian Lynagh wrote:
On Tue, Jun 24, 2008 at 02:15:19AM -0700, Ashley Yakeley wrote:
http://hackage.haskell.org/trac/ghc/ticket/2392
Make Applicative (in Control.Applicative) a superclass of Monad (in Control.Monad).
I agree with what other people have said about H98 compatibility. I think you would be better off proposing this for Haskell'.
OK. Please close it, and I'll submit it for Prime. Thanks -- Ashley Yakeley

Ashley Yakeley wrote:
class Applicative m => Monad m where (>>=) :: m a -> (a -> m b) -> m b fail :: String -> m a fail s = error s
I'd personally like (join :: m (m a) -> m a) to also be in Monad, with default definitions between (>>=) and join, because some monads are more naturally defined by one than the other. (just while we're (not) making breaking changes, and because the default for (>>=) would have to depend on fmap, I though I'd mention it :-) -Isaac
participants (11)
-
ajb@spamcop.net
-
Ashley Yakeley
-
Brandon S. Allbery KF8NH
-
Bulat Ziganshin
-
Christian Maeder
-
Henning Thielemann
-
Ian Lynagh
-
Isaac Dupree
-
John Meacham
-
Malcolm Wallace
-
Ross Paterson