Functor hierarchy proposal and class system extension proposal

Hi, In 2006, Ashley Yakeley proposed the functor hierarchy proposal (http://www.haskell.org/haskellwiki/Functor_hierarchy_proposal), and, in 2007, Brianh (his wiki handle since I don't know his name) proposed the class system extension proposal (http://www.haskell.org/haskellwiki/Class_system_extension_proposal). I recently Googled these proposals and didn't see any significant discussion since they were originally proposed. If there has been some, please point me to it so I can read it. Making functor a superclass of monad has the benefit of consistency with the mathematical definitions. It may also simplify the libraries. The class system extension proposal makes it possible to inherit the default implementations of functions from a superclass, thus simplifying the code that would otherwise be required to create a monad if the functor hierarchy proposal is adopted. Is there any interest in considering these proposals for the next iteration of Haskell'? Cheers, Howard B. Golden Northridge, California, USA

See also http://repetae.net/recent/out/classalias.html http://www.haskell.org//pipermail/libraries/2005-March/003494.html http://www.haskell.org//pipermail/haskell-prime/2006-April/001344.html http://www.haskell.org//pipermail/haskell-prime/2006-August/001582.html On 27 Dec 2010, at 22:35, Howard B. Golden wrote:
Hi,
In 2006, Ashley Yakeley proposed the functor hierarchy proposal (http://www.haskell.org/haskellwiki/Functor_hierarchy_proposal), and, in 2007, Brianh (his wiki handle since I don't know his name) proposed the class system extension proposal (http://www.haskell.org/haskellwiki/Class_system_extension_proposal).
I recently Googled these proposals and didn't see any significant discussion since they were originally proposed. If there has been some, please point me to it so I can read it.

Hi On 2 Jan 2011, at 09:29, Malcolm Wallace wrote:
See also http://repetae.net/recent/out/classalias.html http://www.haskell.org//pipermail/libraries/2005-March/003494.html http://www.haskell.org//pipermail/haskell-prime/2006-April/001344.html http://www.haskell.org//pipermail/haskell-prime/2006-August/001582.html
A proposal from Jón Fairbairn for how to add default superclass method definitions gained some traction, and deserves to be revi(v/s)ed now, I think. Some superclass relationships are `shallow' interface extensions: MonadPlus does not give you a standard way to implement Monad, just more functionality within a monad. Other superclass relationships `deepen' existing functionality---if you have Ord, you can certainly make Eq; if you have Monad, you can certainly make Applicative, etc. The former is currently well supported, the latter badly. Jón's proposal was to improve the latter situation by allowing the subclass to specify a default (partial) implementation of a superclass. So we might write class Applicative f where return :: x -> f x (<*>) :: f (s -> t) -> f s -> f t instance Functor f where fmap = pure . (<*>) giving not only a subclass constraint (Functor f =>) but also a standard means to satisfy it. Whenever an Applicative instance is declared, its Functor sub-instance is unpacked: buy one, get one free. This, on its own, is not quite enough. For one thing, we need a way to switch it off. I should certainly be permitted to write something like instance Applicative Blah where return = ... (<*>) = ... hiding instance Functor Blah to prevent the automatic generation of the superclass instance. The subclass constraint would still apply, so in order to use the Applciative functionality of Blah, it would have to be a Functor otherwise, e.g., by being Traversable. This `hiding' option was missing from Jón's proposal, but it seems crucial to address the potential for conflicts which was identified in the discussion at the time. It's also clear that we must be able to override the default behaviour. When the class declaration has a superclass instance, but not otherwise, a subclass instance should be entitled to override and extend the methods of the superclass instance thus generated. It seems unambiguous to allow this to happen without repeating the "instance Mutter Something". So we'd have class Monad f where (>>=) :: f s -> (s -> f t) -> f t instance Applicative f where ff <*> fs = ff >>= \ f -> fs >>= \ s -> return (f s) and we'd still be able to write instance Monad Maybe where return = Just -- completing the generated Applicative Just s >>= f = f s Nothing >>= _ = Nothing and acquire Monad, Applicative, Functor. No new instance inference semantics is required. In order to transform code under this proposal to code acceptable now, one need only keep track of which methods belong to which class and which classes have default superclass instances: each compound instance can then be split into its individual components before compilation under the current rules. Is this clear? Does it seem plausible? All the best Conor

On Tue, Jan 4, 2011 at 1:21 PM, Conor McBride
Jón's proposal was to improve the latter situation by allowing the subclass to specify a default (partial) implementation of a superclass. So we might write
class Applicative f where return :: x -> f x (<*>) :: f (s -> t) -> f s -> f t instance Functor f where fmap = pure . (<*>)
giving not only a subclass constraint (Functor f =>) but also a standard means to satisfy it. Whenever an Applicative instance is declared, its Functor sub-instance is unpacked: buy one, get one free.
This, on its own, is not quite enough. For one thing, we need a way to switch it off. I should certainly be permitted to write something like
instance Applicative Blah where return = ... (<*>) = ... hiding instance Functor Blah
The use of 'hiding' here I'd object to, as it really isn't a good description of what's going on. Personally I'd think it more clear to explicitly opt into an automatic instance: instance Applicative Blah where return = ... (<*>) = ... deriving (Functor) -- or something like that but one of the advantages of John Meachem's original proposal was that it allowed for example a library author to split up a class without users changing their instances, which my idea would not do. I suppose that alone makes it far less useful, but I think there is an argument to be made about how much of this process we want to be explicit and how much we want to be implicit.

Hi Ben On 4 Jan 2011, at 19:19, Ben Millwood wrote:
On Tue, Jan 4, 2011 at 1:21 PM, Conor McBride
wrote: Jón's proposal was to improve the latter situation by allowing the subclass to specify a default (partial) implementation of a superclass. So we might write
This, on its own, is not quite enough. For one thing, we need a way to switch it off. I should certainly be permitted to write something like
instance Applicative Blah where return = ... (<*>) = ... hiding instance Functor Blah
The use of 'hiding' here I'd object to, as it really isn't a good description of what's going on.
It's perhaps suboptimal. I chose "hiding" only because it's already a vaguely keywordy thing. It's only syntax. What's important is...
Personally I'd think it more clear to explicitly opt into an automatic instance: instance Applicative Blah where return = ... (<*>) = ... deriving (Functor) -- or something like that
[..]
but I think there is an argument to be made about how much of this process we want to be explicit and how much we want to be implicit.
...the argument about what should be implicit or explicit, opt-in or opt-out. In this argument, I disagree with you. I'd much rather it was notationally cheaper to go with the supplied default, provided deviation from the default is also fairly cheap (but explicit). My plan also has the advantage of cheaper backward compatibility (for this and other (future) class splittings). Note that in my example, return had moved to Applicative, pure had been dumped, and a typical Monad instance would look like instance Monad Maybe where Just x >>= f = f x Nothing >>= _ = Nothing return = Just -- where this implicitly opts into and extends the -- Applicative instance -- and also implicitly generates Functor We could not simply have said "deriving Applicative" here, because the default instance is incomplete. In general, one might want to override some but not all of the default instance, just as one does when default method implementations come from the class. There's a general engineering concern as well. The refactoring cost of splitting Applicative off as a lesser version of Monad, taking return, adding (<*>) derivable from (>>=) is much reduced by this choice. I'm sure it's not the only instance of a class we might discover is better split: the opt-in default reduces inertia to such design improvements. I'd certainly be happy with a different opt-out notation, but I would be unhappy if opting in (and overriding/extending) were made more complex than necessary to allow an opt-out default. All the best Conor

On Tue, Jan 4, 2011 at 7:59 PM, Conor McBride
Hi Ben
On 4 Jan 2011, at 19:19, Ben Millwood wrote:
On Tue, Jan 4, 2011 at 1:21 PM, Conor McBride
wrote: Jón's proposal was to improve the latter situation by allowing the subclass to specify a default (partial) implementation of a superclass. So we might write
This, on its own, is not quite enough. For one thing, we need a way to switch it off. I should certainly be permitted to write something like
instance Applicative Blah where return = ... (<*>) = ... hiding instance Functor Blah
The use of 'hiding' here I'd object to, as it really isn't a good description of what's going on.
It's perhaps suboptimal. I chose "hiding" only because it's already a vaguely keywordy thing. It's only syntax. What's important is...
Yeah, it's not my main objection, I just thought it worth pointing out :) obviously the explicit approach is better because 'deriving' is a nicer keyword than 'hiding' :P
...the argument about what should be implicit or explicit, opt-in or opt-out. In this argument, I disagree with you.
I'd much rather it was notationally cheaper to go with the supplied default, provided deviation from the default is also fairly cheap (but explicit).
There's a fair question in whether we want deviation from the default at all (although I think the answer is probably yes). I think it's reasonable that any type that is an instance of Monad be forced to have ap = (<*>), for example, so really the only reason I can see we'd want to be able to override those functions would be for efficiency. I always thought it weird that the Haskell report worried about efficiency (see: MR) so I don't know that it's not better to do that sort of thing with inline pragmas, rewrite rules, or similar such arrangements. But the trend has been to increase the number of methods in classes (now *> is in Applicative and <$ in Functor) rather than vice versa, so perhaps there are stronger benefits than I know - I'm not used to dealing with performance-sensitive code.
My plan also has the advantage of cheaper backward compatibility (for this and other (future) class splittings).
Note that in my example, return had moved to Applicative, pure had been dumped, and a typical Monad instance would look like
aww, but pure is a better name than return :P (and the bikeshed should be pink!)
instance Monad Maybe where Just x >>= f = f x Nothing >>= _ = Nothing return = Just -- where this implicitly opts into and extends the -- Applicative instance -- and also implicitly generates Functor
We could not simply have said "deriving Applicative" here, because the default instance is incomplete. In general, one might want to override some but not all of the default instance, just as one does when default method implementations come from the class.
This is fair enough, although I don't think one proposal does this particularly worse than another. I'm unclear now on what exactly the 'hiding' clause does - surely you either implicitly opt into an instance or you don't. If you don't you must provide it somewhere else in scope, since it's a superclass, in which case the implicit instance would be overriden anyway, right? Something to think about - sometimes superclass instances have different contexts, e.g. instance Functor ((,) e) where [...] but instance (Monoid w) => Monad ((,) w). In that case, imagine if the Functor instance disappeared - there would be no error because one would be supplied implicitly, but you'd suddenly get a message about missing a Monoid instance for some type you used fmap on, which would be unpleasant to debug. This is the sort of thing that makes me uneasy about implicit instances, and though I appreciate there are some important advantages to them, things like how they scope, where they can be defined, and how stable they are to other changes, need careful consideration, I think.
There's a general engineering concern as well. The refactoring cost of splitting Applicative off as a lesser version of Monad, taking return, adding (<*>) derivable from (>>=) is much reduced by this choice. I'm sure it's not the only instance of a class we might discover is better split: the opt-in default reduces inertia to such design improvements.
I'd certainly be happy with a different opt-out notation, but I would be unhappy if opting in (and overriding/extending) were made more complex than necessary to allow an opt-out default.
I think you're probably right, but I think these proposals are always more complex than they look and it's good to make sure you've considered all the alternatives :)
All the best
Conor

On 01/04/11 19:48, Ben Millwood wrote:
There's a fair question in whether we want deviation from the default at all (although I think the answer is probably yes). I think it's reasonable that any type that is an instance of Monad be forced to have ap = (<*>), for example, so really the only reason I can see we'd want to be able to override those functions would be for efficiency.
Remember the example Monad implies Functor (fmap = Control.Monad.liftM) Traversable implies Functor (fmap = Data.Traversable.fmapDefault) e.g. [] and Maybe are instances of all these classes. yes, liftM and fmapDefault probably must *do* the same thing[*], but one of those definitions still needs to be picked. [*probably--I'm haven't convinced myself that it's true in all cases of "deepening"-type class hierarchies though--we are here trying to engineer to support all cases of "deepening" hierarchies.] -Isaac

On Wed, Jan 5, 2011 at 5:03 AM, Isaac Dupree
On 01/04/11 19:48, Ben Millwood wrote:
There's a fair question in whether we want deviation from the default at all (although I think the answer is probably yes). I think it's reasonable that any type that is an instance of Monad be forced to have ap = (<*>), for example, so really the only reason I can see we'd want to be able to override those functions would be for efficiency.
Remember the example Monad implies Functor (fmap = Control.Monad.liftM) Traversable implies Functor (fmap = Data.Traversable.fmapDefault)
e.g. [] and Maybe are instances of all these classes.
yes, liftM and fmapDefault probably must *do* the same thing[*], but one of those definitions still needs to be picked.
This is interesting, yes, and I suppose that's what the 'hiding' was for, but it seems uglier to me to have a hiding clause on every instance declaration except one. I suppose if there was an explicit Functor instance this wouldn't be a problem, as neither implicit instance would be used in that case. Or if there wasn't an explicit Functor instance, but there was a definition for fmap in one of the instances, then that would be used - if there was more than one definition for fmap of course that would be an error. It would seem irritating if I had Traversable defined for some type, and I defined Applicative, and this caused the Functor instance to break, but this is not necessarily a critical problem.
[*probably--I'm haven't convinced myself that it's true in all cases of "deepening"-type class hierarchies though--we are here trying to engineer to support all cases of "deepening" hierarchies.]
I think it would be unpleasantly surprising if ap and (<*>) behaved differently. If there was another desirable behaviour for <*> I'd think a newtype would be appropriate.

Conor McBride
My plan also has the advantage of cheaper backward compatibility (for this and other (future) class splittings).
I find compatibility with future class splittings to be a compelling feature to strive for, even *without* any default member definitions. Inserting a new class in a hierarchy (as the Numeric Prelude proposes) shouldn't cause any existing instances to break. For example, say we split class Num a where -- (+), (-), negate, (*), abs, signum (I'll ignore fromInteger and the superclasses Eq and Show in this message) into class Additive a where -- (+), (-), negate class (Additive a) => Num a where -- (*), abs, signum In today's Haskell, all existing instances of Num will break. The problem is that the header "instance Num X where" used to mean "below are definitions for (+), (-), negate, (*), abs, signum" but now means "below are definitions for (*), abs, signum". Here's a crazy idea to future-proof against such a split: let's make every instance header declare not only the instance being defined but also the superclass instance(s) being presupposed. We will write instance () -> Num X where ... to mean "below are definitions for (+), (-), negate, (*), abs, signum", both before and after the split. To say "below are definitions for (*), abs, signum" (which only makes sense after the split), we will write instance (Additive X) -> Num X where ... (I just made up the -> notation, and I'm not satisfied with it, though it's definitely not the same as "instance (Additive X) => Num X where", which needs UndecidableInstances. Maybe "class (Additive a) => Num a" should become "class (Additive a) -> Num a".) Suppose that at t=3 we insert another class into the hierarchy: class Additive a where -- (+), (-), negate class (Additive a) => Ring a where -- (*) class (Ring a) => Num a where -- abs, signum Now "instance (Additive X) -> Num X" still means "below are definitions for (*), abs, signum". To define just (*), we will write "instance (Additive X) -> Ring X". To define just abs and signum, we will write "instance (Ring X) -> Num X". We can also write "instance () -> Ring X" to define (+), (-), negate, (*). So each instance definition in the new syntax can explode into a whole bunch of instance definitions in the old syntax. I have high hopes that this would work well with type-class synonyms. For example, at t=4, let's insert Monoid and Semiring into our class hierarchy: class Monoid a where -- (+) class (Monoid a) => Additive a where -- (-), negate class (Monoid a) => Semiring a where -- (*) class alias Ring a = (Monoid a, Semiring a) class (Ring a) => Num a where -- abs, signum Still "instance (Additive X) -> Num X" means to define (*), abs, signum. Still "instance (Additive X) -> Ring X" means to define just (*). In fact even "instance () -> (Eq X, Show Y)" could be allowed. If the same superclass appears multiple times then member names will clash: class Su a where ... class (Su a, Su b) => Cl a b where ... instance (Su a) -> Cl a b where -- provide (Su b) and Cl a b instance (Su b) -> Cl a b where -- provide (Su a) and Cl a b instance (Su a, Su b) -> Cl a b where -- provide just Cl a b instance () -> Cl a b where -- not a backward compatibility concern because we couldn't have -- gotten our current Cl by splitting out both copies of Su, so -- we don't have to allow this instance at all All this can be emulated using class aliases as proposed at http://repetae.net/recent/out/classalias.html : as the EqOrd example there shows, instead of the code at t=3 above, one would write class Additive a where -- (+), (-), negate class (Additive a) => Additive_Ring a where -- (*) class (Additive_Ring a) => Ring_Num a where -- abs, signum class alias Ring a = (Additive a, Additive_Ring a) class alias Num a = (Additive a, Additive_Ring a, Ring_Num a) class alias Additive_Num a = Additive a => (Additive_Ring a, Ring_Num a) then write "instance Additive_Num X" instead of "instance (Additive X) -> Num X". But this requires a quadratic number of class aliases. Besides, I like to understand *every* instance as covering not a single edge in the hierarchy but a subgraph. So far I haven't said anything about default member definitions. What I want to suggest is, what if instance (Functor Blah) -> Applicative Blah where means to hide the default instance for Functor Blah inside the Applicative class, and instance () -> Applicative Blah where means to use that default instance (which would still allow overriding parts of it)? I guess in terms of the class-alias proposal, my suggestion would be to allow instances as part of a class alias! I imagine a syntax like: class Functor a where ... class (Functor a) => Functor_Applicative a where ... class alias Applicative a = (Functor a, Functor_Applicative a) where fmap f x = pure f <*> x -- Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig <INSERT PARTISAN STATEMENT HERE>
participants (6)
-
Ben Millwood
-
Chung-chieh Shan
-
Conor McBride
-
Howard B. Golden
-
Isaac Dupree
-
Malcolm Wallace