Re: In opposition of Functor as super-class of Monad

Hi, I was thinking lately about the well known problem that Monad is neither Functor nor Applicative. As I understand, it is caused by some historical issues. What I like about Haskell is that it allows to describe very nicely what different objects actually are - something that I find very important for programming. And this issue violates this principle. This has been discussed here more than year ago in http://www.haskell.org/pipermail/haskell-prime/2011-January/003312.html : On 1/4/11 11:24, oleg at okmij.org wrote:
I'd like to argue in opposition of making Functor a super-class of Monad. I would argue that superclass constraints are not the right tool for expressing mathematical relationship such that all monads are functors and applicatives.
Then argument is practical. It seems that making Functor a superclass of Monad makes defining new monad instances more of a chore, leading to code duplication. To me, code duplication is a sign that an abstraction is missing or misused. ...
The main objections were that it would break existing code and that it would lead to code duplication. The former is serious, the second can be easily solved by standard Haskell, since one can define instance Applicative ... where pure = return (<*>) = ap instance Functor ... where fmap = liftM To address the first objection: AFAIK nobody mentioned the "Default superclass instances" proposal: http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances To give an example how it would work: class Applicative f => Monad f where (>>=) :: f a -> (a -> f b) -> f b ... instance Applicative f where ff <*> fs = ff >>= \ f -> fs >>= \ s -> return (f s) ... This says that if somebody defines an instance of Monad it automatically becomes an instance of Applicative as defined in the nested "instance" block. So there is no need to define Applicative/Functor explicitly, making existing code work. Implementing this proposal would allow making Monad to extend Functor and Applicative without breaking existing code. Moreover, this would simplify other things, for example it would be possible to define an instance of Traversable and the instances for Functor and Foldable would be defined implicitly using fmapDefault and foldMapDefault. I'm sure there are many other cases where splitting type classes into a more fine-grained hierarchy would be beneficial, and the main reason against it is simply not to break compatibility with existing code. IMHO this would be worthwhile to consider for some future revision of Haskell. Best regards, Petr Pudlak

There are very good reasons for not following this road; indeed everything which is a Monad can also be made an instance of Applicative. But more often than not we want to have a more specific implementation. Because Applicative is less general, there is in general more that you can do with it.
An analogue is the relation between regular grammars and context-free grammars; indeed, once we have the latter concept we might argue that we do not need the first one any more. But if we know that something is in the first category we can do all kins of nice things which we cannot do with conxet-free grammars, such as constructing a finite state machine for recognising sentences.
You proposal would introduce overlapping instances is such cases where we want to give a ``better'' implementation in case we know we are dealing with the more restricted case.
I have explained this phenomenon for the first time in:
@inproceedings{SwieDupo96,
Author = {Swierstra, S. D. and Duponcheel, L.},
Booktitle = {Advanced Functional Programming},
Date-Added = {2009-01-04 17:21:54 +0100},
Date-Modified = {2009-01-04 17:21:54 +0100},
Editor = {Launchbury, John and Meijer, Erik and Sheard, Tim},
Pages = {184-207},
Publisher = {Springer-Verlag},
Series = {LNCS-Tutorial},
Title = {Deterministic, Error-Correcting Combinator Parsers},
Urlpdf = {http://www.cs.uu.nl/people/doaitse/Papers/1996/DetErrCorrComPars.pdf},
Volume = {1129},
Year = {1996}}
If you look at the uu-parsinglib library you will see that the Applicative instance of the parsers used there is definitely more involved that what you can do with the monadic interface. Your proposal would ruin this library.
Unless we have things like e.g. named instances, the possibility to choose between overlapping instances, etc. I think we should leave things the way they are; the only reason I see for having superclasses is to be able to use functions from those classes in the default implementations of functions in the new class, and to group functionality coming from several classes.
Doaitse
On Oct 24, 2012, at 10:01 , Petr P
Hi,
I was thinking lately about the well known problem that Monad is neither Functor nor Applicative. As I understand, it is caused by some historical issues. What I like about Haskell is that it allows to describe very nicely what different objects actually are - something that I find very important for programming. And this issue violates this principle.
This has been discussed here more than year ago in http://www.haskell.org/pipermail/haskell-prime/2011-January/003312.html :
On 1/4/11 11:24, oleg at okmij.org wrote:
I'd like to argue in opposition of making Functor a super-class of Monad. I would argue that superclass constraints are not the right tool for expressing mathematical relationship such that all monads are functors and applicatives.
Then argument is practical. It seems that making Functor a superclass of Monad makes defining new monad instances more of a chore, leading to code duplication. To me, code duplication is a sign that an abstraction is missing or misused. ...
The main objections were that it would break existing code and that it would lead to code duplication. The former is serious, the second can be easily solved by standard Haskell, since one can define
instance Applicative ... where pure = return (<*>) = ap instance Functor ... where fmap = liftM
To address the first objection: AFAIK nobody mentioned the "Default superclass instances" proposal: http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances To give an example how it would work:
class Applicative f => Monad f where (>>=) :: f a -> (a -> f b) -> f b ... instance Applicative f where ff <*> fs = ff >>= \ f -> fs >>= \ s -> return (f s) ...
This says that if somebody defines an instance of Monad it automatically becomes an instance of Applicative as defined in the nested "instance" block. So there is no need to define Applicative/Functor explicitly, making existing code work.
Implementing this proposal would allow making Monad to extend Functor and Applicative without breaking existing code. Moreover, this would simplify other things, for example it would be possible to define an instance of Traversable and the instances for Functor and Foldable would be defined implicitly using fmapDefault and foldMapDefault. I'm sure there are many other cases where splitting type classes into a more fine-grained hierarchy would be beneficial, and the main reason against it is simply not to break compatibility with existing code.
IMHO this would be worthwhile to consider for some future revision of Haskell.
Best regards, Petr Pudlak
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

On 24 October 2012 11:16, S. Doaitse Swierstra
There are very good reasons for not following this road; indeed everything which is a Monad can also be made an instance of Applicative. But more often than not we want to have a more specific implementation. Because Applicative is less general, there is in general more that you can do with it.
I don't think anyone is suggesting that we force all type that are both Monad and Applicative to use (<*>) = ap as the implementation. As you say, that'd be crazy. The details and differences between the various superclass proposals are to do with how you provide the explicit instance vs getting the default. The wiki page explains it and links to the other similar proposals: http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances Duncan

(Just to clarify, it's not my proposal, I just endorse it. Looking at
its history, it's been worked on by pigworker and simonpj.)
The uu-parser library looks quite complex, so before I dive into
exploring it and reading your paper, I'd say I believe that your
objection is already addressed in the proposal, namely in section "The
opt-out mechanism" and perhaps in section "The design of the opt-out
mechanism". To clarify, the proposal doesn't remove `return` in favor
of `pure` etc. We'd still keep all the functions names like we have
now and the ability to define them differently. You could always use
your own definitions for Applicative (Functor etc.) if you didn't want
the default ones resulting from Monad (return/ap for pure/<*>) for any
reason.
Best regards,
Petr Pudlak
2012/10/24 S. Doaitse Swierstra
There are very good reasons for not following this road; indeed everything which is a Monad can also be made an instance of Applicative. But more often than not we want to have a more specific implementation. Because Applicative is less general, there is in general more that you can do with it.
An analogue is the relation between regular grammars and context-free grammars; indeed, once we have the latter concept we might argue that we do not need the first one any more. But if we know that something is in the first category we can do all kins of nice things which we cannot do with conxet-free grammars, such as constructing a finite state machine for recognising sentences.
You proposal would introduce overlapping instances is such cases where we want to give a ``better'' implementation in case we know we are dealing with the more restricted case.
I have explained this phenomenon for the first time in:
@inproceedings{SwieDupo96, Author = {Swierstra, S. D. and Duponcheel, L.}, Booktitle = {Advanced Functional Programming}, Date-Added = {2009-01-04 17:21:54 +0100}, Date-Modified = {2009-01-04 17:21:54 +0100}, Editor = {Launchbury, John and Meijer, Erik and Sheard, Tim}, Pages = {184-207}, Publisher = {Springer-Verlag}, Series = {LNCS-Tutorial}, Title = {Deterministic, Error-Correcting Combinator Parsers}, Urlpdf = {http://www.cs.uu.nl/people/doaitse/Papers/1996/DetErrCorrComPars.pdf}, Volume = {1129}, Year = {1996}}
If you look at the uu-parsinglib library you will see that the Applicative instance of the parsers used there is definitely more involved that what you can do with the monadic interface. Your proposal would ruin this library.
Unless we have things like e.g. named instances, the possibility to choose between overlapping instances, etc. I think we should leave things the way they are; the only reason I see for having superclasses is to be able to use functions from those classes in the default implementations of functions in the new class, and to group functionality coming from several classes.
Doaitse
On Oct 24, 2012, at 10:01 , Petr P
wrote: Hi,
I was thinking lately about the well known problem that Monad is neither Functor nor Applicative. As I understand, it is caused by some historical issues. What I like about Haskell is that it allows to describe very nicely what different objects actually are - something that I find very important for programming. And this issue violates this principle.
This has been discussed here more than year ago in http://www.haskell.org/pipermail/haskell-prime/2011-January/003312.html :
On 1/4/11 11:24, oleg at okmij.org wrote:
I'd like to argue in opposition of making Functor a super-class of Monad. I would argue that superclass constraints are not the right tool for expressing mathematical relationship such that all monads are functors and applicatives.
Then argument is practical. It seems that making Functor a superclass of Monad makes defining new monad instances more of a chore, leading to code duplication. To me, code duplication is a sign that an abstraction is missing or misused. ...
The main objections were that it would break existing code and that it would lead to code duplication. The former is serious, the second can be easily solved by standard Haskell, since one can define
instance Applicative ... where pure = return (<*>) = ap instance Functor ... where fmap = liftM
To address the first objection: AFAIK nobody mentioned the "Default superclass instances" proposal: http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances To give an example how it would work:
class Applicative f => Monad f where (>>=) :: f a -> (a -> f b) -> f b ... instance Applicative f where ff <*> fs = ff >>= \ f -> fs >>= \ s -> return (f s) ...
This says that if somebody defines an instance of Monad it automatically becomes an instance of Applicative as defined in the nested "instance" block. So there is no need to define Applicative/Functor explicitly, making existing code work.
Implementing this proposal would allow making Monad to extend Functor and Applicative without breaking existing code. Moreover, this would simplify other things, for example it would be possible to define an instance of Traversable and the instances for Functor and Foldable would be defined implicitly using fmapDefault and foldMapDefault. I'm sure there are many other cases where splitting type classes into a more fine-grained hierarchy would be beneficial, and the main reason against it is simply not to break compatibility with existing code.
IMHO this would be worthwhile to consider for some future revision of Haskell.
Best regards, Petr Pudlak
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

First, let me make it clear that nowadays we are of course (I hope!) talking about making not only Functor, but Applicative a super-class of Monad (so Functor becomes a super-class by transitivity). Petr P wrote:
The main objections were that it would break existing code and that it would lead to code duplication. The former is serious, [...]
To address the first objection:
I don't buy this "it breaks lots of code" argument. Adding the missing instances is a complete no-brainer; as you wrote:
instance Applicative ... where pure = return (<*>) = ap instance Functor ... where fmap = liftM
I do not think it is unreasonable to expect people to add such a simple and practically automatic fix to some old programs in the interest of cleaning up an old wart (and almost everyone agrees that this would be a good thing, in principle). BTW, I guess most programs already contain the Functor instances (but maybe not Applicative, as it is newer). I agree with Petr Pudlak that code duplication is not an issue, see above. And yes, these "automatic" instances may have stronger super-class constraints than strictly necessary. So what? The program didn't need the Functor (or Applicative) instance anyway (or it already would have defined it, in which case no change would be needed at all). "Default superclass instances" strike me as a complicated proposal for solving trivial problems. The switch in Control.Exception (from data Exception to class Exception) was much more disrupting, adapting programs meant lots of changes everywhere exceptions are handled, not just adding some trivial instances. Still people managed the transition. Cheers -- Ben Franksen () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachments

I should hope not. The identity element (return, coreturn, mempty, pure, Category.id) is almost never needed. * http://hackage.haskell.org/package/semigroupoids * https://gist.github.com/3871764 On 25/10/12 04:49, Ben Franksen wrote:
First, let me make it clear that nowadays we are of course (I hope!) talking about making not only Functor, but Applicative a super-class of Monad (so Functor becomes a super-class by transitivity).
Petr P wrote:
The main objections were that it would break existing code and that it would lead to code duplication. The former is serious, [...]
To address the first objection: I don't buy this "it breaks lots of code" argument. Adding the missing instances is a complete no-brainer; as you wrote:
instance Applicative ... where pure = return (<*>) = ap instance Functor ... where fmap = liftM I do not think it is unreasonable to expect people to add such a simple and practically automatic fix to some old programs in the interest of cleaning up an old wart (and almost everyone agrees that this would be a good thing, in principle).
BTW, I guess most programs already contain the Functor instances (but maybe not Applicative, as it is newer).
I agree with Petr Pudlak that code duplication is not an issue, see above. And yes, these "automatic" instances may have stronger super-class constraints than strictly necessary. So what? The program didn't need the Functor (or Applicative) instance anyway (or it already would have defined it, in which case no change would be needed at all).
"Default superclass instances" strike me as a complicated proposal for solving trivial problems. The switch in Control.Exception (from data Exception to class Exception) was much more disrupting, adapting programs meant lots of changes everywhere exceptions are handled, not just adding some trivial instances. Still people managed the transition.
Cheers
-- Tony Morris http://tmorris.net/

Tony Morris wrote:
I should hope not. The identity element (return, coreturn, mempty, pure, Category.id) is almost never needed.
* http://hackage.haskell.org/package/semigroupoids * https://gist.github.com/3871764
On 25/10/12 04:49, Ben Franksen wrote:
First, let me make it clear that nowadays we are of course (I hope!) talking about making not only Functor, but Applicative a super-class of Monad (so Functor becomes a super-class by transitivity).
Petr P wrote:
The main objections were that it would break existing code and that it would lead to code duplication. The former is serious, [...]
To address the first objection: I don't buy this "it breaks lots of code" argument. Adding the missing instances is a complete no-brainer; as you wrote:
instance Applicative ... where pure = return (<*>) = ap instance Functor ... where fmap = liftM I do not think it is unreasonable to expect people to add such a simple and practically automatic fix to some old programs in the interest of cleaning up an old wart (and almost everyone agrees that this would be a good
Off-topic. Feel free to start a new thread named "The bombastic one-and-true class hierarchy I always wanted to have". These proposals have their merits, and I greatly respect the category theoretic knowledge that went into them -- but this is another discussion. This thread refers to a rather modest correction in the standard libraries, not a complete re-design. The idea is to fix something that is widely accepted as an unfortunate ommision (in fact, Oleg's comment is one of the very few that question the idea of adding super class constraints to Monad in principle). BTW, it is unclear what your "I hope not" refers to, since in both of the hierarchies you linked to Applicative *is* a super class of Monad. Cheers thing,
in principle).
BTW, I guess most programs already contain the Functor instances (but maybe not Applicative, as it is newer).
I agree with Petr Pudlak that code duplication is not an issue, see above. And yes, these "automatic" instances may have stronger super-class constraints than strictly necessary. So what? The program didn't need the Functor (or Applicative) instance anyway (or it already would have defined it, in which case no change would be needed at all).
"Default superclass instances" strike me as a complicated proposal for solving trivial problems. The switch in Control.Exception (from data Exception to class Exception) was much more disrupting, adapting programs meant lots of changes everywhere exceptions are handled, not just adding some trivial instances. Still people managed the transition.
Cheers
-- Ben Franksen () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachments

The major advantage that I see of making Applicative a superclass of Monad is actually not anywhere to do with the data types or instances, but rather to do with functions that operate on the class. For example, the liftM* family of functions becomes entirely redundant, and can be eliminated in favour of liftA*, which reduces the number of arbitrary choices we need to make and understand. As another example, we sometimes want to use functions (like void or fmap) that work with Functor and functions (like join) that need Monad in the same (polymorphic) code. We then have to state *both* constraints in the context for the code, despite the fact that if one is satisfied, the other must surely be. For example, defining instance Functor (StateT s m) you have to choose whether to use the context (Monad m) or (Functor m): the latter is more general, but requires your programs that use fmap *and* bind to specify (Monad m, Functor m), and the former is almost always what's used in practice anyway. This tension just doesn't exist if one is a superclass of the other. Some code will break, yes, but I think most people would agree that the presence of a Monad instance with no corresponding Applicative instance is a bug anyway, and should be fixed. (Note that if Applicative and Monad are both defined for the same type, it is required by the Applicative docs that return = pure and <*> = ap, at least extensionally. Of course the implementation can be cleverer, but if you want it to be actually /different/ in behaviour, please use a newtype).

I should have been clearer sorry. I should hope not that Functor <- Applicative <- Monad. Perhaps I do not understand the purpose of this thread, but "fixing" the hierarchy in this way is a mistake of similar magnitude to the original position -- one that I would cringe at seeing repeated. That is why I thought such a discussion was on-topic. On 25/10/12 10:12, Ben Franksen wrote:
Tony Morris wrote:
I should hope not. The identity element (return, coreturn, mempty, pure, Category.id) is almost never needed.
* http://hackage.haskell.org/package/semigroupoids * https://gist.github.com/3871764 Off-topic. Feel free to start a new thread named "The bombastic one-and-true class hierarchy I always wanted to have". These proposals have their merits, and I greatly respect the category theoretic knowledge that went into them -- but this is another discussion. This thread refers to a rather modest correction in the standard libraries, not a complete re-design. The idea is to fix something that is widely accepted as an unfortunate ommision (in fact, Oleg's comment is one of the very few that question the idea of adding super class constraints to Monad in principle).
BTW, it is unclear what your "I hope not" refers to, since in both of the hierarchies you linked to Applicative *is* a super class of Monad.
Cheers
First, let me make it clear that nowadays we are of course (I hope!) talking about making not only Functor, but Applicative a super-class of Monad (so Functor becomes a super-class by transitivity).
Petr P wrote:
The main objections were that it would break existing code and that it would lead to code duplication. The former is serious, [...]
To address the first objection: I don't buy this "it breaks lots of code" argument. Adding the missing instances is a complete no-brainer; as you wrote:
instance Applicative ... where pure = return (<*>) = ap instance Functor ... where fmap = liftM I do not think it is unreasonable to expect people to add such a simple and practically automatic fix to some old programs in the interest of cleaning up an old wart (and almost everyone agrees that this would be a good
On 25/10/12 04:49, Ben Franksen wrote: thing,
in principle).
BTW, I guess most programs already contain the Functor instances (but maybe not Applicative, as it is newer).
I agree with Petr Pudlak that code duplication is not an issue, see above. And yes, these "automatic" instances may have stronger super-class constraints than strictly necessary. So what? The program didn't need the Functor (or Applicative) instance anyway (or it already would have defined it, in which case no change would be needed at all).
"Default superclass instances" strike me as a complicated proposal for solving trivial problems. The switch in Control.Exception (from data Exception to class Exception) was much more disrupting, adapting programs meant lots of changes everywhere exceptions are handled, not just adding some trivial instances. Still people managed the transition.
Cheers
-- Tony Morris http://tmorris.net/

Tony, I think you misparsed the proposal.
The ...'s were for specific monads indicating the additional work required for each Monad.
I think the only real proposal on the table is the obvious one of adding Applicative as a superclass of monad.
From there there are a couple of incremental "improvements" that could be made like adding the unimplemented superclass defaults or adding the equivalent of DefaultSignatures to the language spec to reduce the burden on Monad implementors.
In practice I think either of those extensions would be premature to add to the language specification at this time.
I would be 100% behind adding the Applicative constraint as a superclass of Monad and even perhaps of some bikeshedding, like exporting Applicative from the Prelude, because otherwise you can't define a Monad without an import, while you can now.
I would be strongly against requiring superclass defaults or DefaultSignatures in the haskell standard, however. The former is a largely untested point in the design space and the latter has issues where it tightly couples classes with their dependencies, leading to unbreakable cycles between classes that all have to be defined together and poor engineering practices.
Best,
--Edward
On Oct 25, 2012, at 5:46 PM, Tony Morris
I should have been clearer sorry. I should hope not that Functor <- Applicative <- Monad.
Perhaps I do not understand the purpose of this thread, but "fixing" the hierarchy in this way is a mistake of similar magnitude to the original position -- one that I would cringe at seeing repeated. That is why I thought such a discussion was on-topic.
On 25/10/12 10:12, Ben Franksen wrote:
Tony Morris wrote:
I should hope not. The identity element (return, coreturn, mempty, pure, Category.id) is almost never needed.
* http://hackage.haskell.org/package/semigroupoids * https://gist.github.com/3871764 Off-topic. Feel free to start a new thread named "The bombastic one-and-true class hierarchy I always wanted to have". These proposals have their merits, and I greatly respect the category theoretic knowledge that went into them -- but this is another discussion. This thread refers to a rather modest correction in the standard libraries, not a complete re-design. The idea is to fix something that is widely accepted as an unfortunate ommision (in fact, Oleg's comment is one of the very few that question the idea of adding super class constraints to Monad in principle).
BTW, it is unclear what your "I hope not" refers to, since in both of the hierarchies you linked to Applicative *is* a super class of Monad.
Cheers
First, let me make it clear that nowadays we are of course (I hope!) talking about making not only Functor, but Applicative a super-class of Monad (so Functor becomes a super-class by transitivity).
Petr P wrote:
The main objections were that it would break existing code and that it would lead to code duplication. The former is serious, [...]
To address the first objection: I don't buy this "it breaks lots of code" argument. Adding the missing instances is a complete no-brainer; as you wrote:
instance Applicative ... where pure = return (<*>) = ap instance Functor ... where fmap = liftM I do not think it is unreasonable to expect people to add such a simple and practically automatic fix to some old programs in the interest of cleaning up an old wart (and almost everyone agrees that this would be a good
On 25/10/12 04:49, Ben Franksen wrote: thing,
in principle).
BTW, I guess most programs already contain the Functor instances (but maybe not Applicative, as it is newer).
I agree with Petr Pudlak that code duplication is not an issue, see above. And yes, these "automatic" instances may have stronger super-class constraints than strictly necessary. So what? The program didn't need the Functor (or Applicative) instance anyway (or it already would have defined it, in which case no change would be needed at all).
"Default superclass instances" strike me as a complicated proposal for solving trivial problems. The switch in Control.Exception (from data Exception to class Exception) was much more disrupting, adapting programs meant lots of changes everywhere exceptions are handled, not just adding some trivial instances. Still people managed the transition.
Cheers
-- Tony Morris http://tmorris.net/
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

OK, sorry about the noise! On 26/10/12 09:41, Edward Kmett wrote:
Tony, I think you misparsed the proposal.
The ...'s were for specific monads indicating the additional work required for each Monad.
I think the only real proposal on the table is the obvious one of adding Applicative as a superclass of monad.
From there there are a couple of incremental "improvements" that could be made like adding the unimplemented superclass defaults or adding the equivalent of DefaultSignatures to the language spec to reduce the burden on Monad implementors.
In practice I think either of those extensions would be premature to add to the language specification at this time.
I would be 100% behind adding the Applicative constraint as a superclass of Monad and even perhaps of some bikeshedding, like exporting Applicative from the Prelude, because otherwise you can't define a Monad without an import, while you can now.
I would be strongly against requiring superclass defaults or DefaultSignatures in the haskell standard, however. The former is a largely untested point in the design space and the latter has issues where it tightly couples classes with their dependencies, leading to unbreakable cycles between classes that all have to be defined together and poor engineering practices.
Best, --Edward
On Oct 25, 2012, at 5:46 PM, Tony Morris
wrote: I should have been clearer sorry. I should hope not that Functor <- Applicative <- Monad.
Perhaps I do not understand the purpose of this thread, but "fixing" the hierarchy in this way is a mistake of similar magnitude to the original position -- one that I would cringe at seeing repeated. That is why I thought such a discussion was on-topic.
On 25/10/12 10:12, Ben Franksen wrote:
Tony Morris wrote:
I should hope not. The identity element (return, coreturn, mempty, pure, Category.id) is almost never needed.
* http://hackage.haskell.org/package/semigroupoids * https://gist.github.com/3871764 Off-topic. Feel free to start a new thread named "The bombastic one-and-true class hierarchy I always wanted to have". These proposals have their merits, and I greatly respect the category theoretic knowledge that went into them -- but this is another discussion. This thread refers to a rather modest correction in the standard libraries, not a complete re-design. The idea is to fix something that is widely accepted as an unfortunate ommision (in fact, Oleg's comment is one of the very few that question the idea of adding super class constraints to Monad in principle).
BTW, it is unclear what your "I hope not" refers to, since in both of the hierarchies you linked to Applicative *is* a super class of Monad.
Cheers
First, let me make it clear that nowadays we are of course (I hope!) talking about making not only Functor, but Applicative a super-class of Monad (so Functor becomes a super-class by transitivity).
Petr P wrote:
The main objections were that it would break existing code and that it would lead to code duplication. The former is serious, [...]
To address the first objection: I don't buy this "it breaks lots of code" argument. Adding the missing instances is a complete no-brainer; as you wrote:
instance Applicative ... where pure = return (<*>) = ap instance Functor ... where fmap = liftM I do not think it is unreasonable to expect people to add such a simple and practically automatic fix to some old programs in the interest of cleaning up an old wart (and almost everyone agrees that this would be a good
On 25/10/12 04:49, Ben Franksen wrote: thing,
in principle).
BTW, I guess most programs already contain the Functor instances (but maybe not Applicative, as it is newer).
I agree with Petr Pudlak that code duplication is not an issue, see above. And yes, these "automatic" instances may have stronger super-class constraints than strictly necessary. So what? The program didn't need the Functor (or Applicative) instance anyway (or it already would have defined it, in which case no change would be needed at all).
"Default superclass instances" strike me as a complicated proposal for solving trivial problems. The switch in Control.Exception (from data Exception to class Exception) was much more disrupting, adapting programs meant lots of changes everywhere exceptions are handled, not just adding some trivial instances. Still people managed the transition.
Cheers
-- Tony Morris http://tmorris.net/
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime
-- Tony Morris http://tmorris.net/

http://haskell.1045720.n5.nabble.com/Interfaces-the-Golden-Path-of-Haskell-t... With this Haskell extension it could be possibe to implement both (Monad m) and (Applicative m => Monad m). Not only both, we could define a lot of Monad for many users. -- View this message in context: http://haskell.1045720.n5.nabble.com/Re-In-opposition-of-Functor-as-super-cl... Sent from the Haskell - Haskell-prime mailing list archive at Nabble.com.
participants (8)
-
Ben Franksen
-
Ben Millwood
-
Duncan Coutts
-
Edward Kmett
-
Petr P
-
S. Doaitse Swierstra
-
Tony Morris
-
Wvv