class default method proposal

I'd just like to float an idea that's related to the Class Alias proposal[1] but is perhaps somewhat simpler. We all know that Functor should have been a superclass of Monad, and indeed we now know that Applicative should be too. Making such a change would break lots of things however so the change does not happen. However in this case the Monad operations can be used to implement the Functor and Applicative class methods. So it would be nice if we could get them for free if the author did not choose to write the Functor and Applicative instances. So my suggestion is that we let classes declare default implementations of methods from super-classes. class Functor m => Monad m where {- the ordinary bits -} fmap f m = m >>= return . f So if there already is a Functor instance for m then the default implementation of fmap is not used. Does this proposal have any unintended consequences? I'm not sure. Please discuss :-) Duncan [1] http://repetae.net/recent/out/classalias.html

On Tue, Dec 11, 2007 at 02:20:52PM +0000, Duncan Coutts wrote:
I'd just like to float an idea that's related to the Class Alias proposal[1] but is perhaps somewhat simpler.
We all know that Functor should have been a superclass of Monad, and indeed we now know that Applicative should be too. Making such a change would break lots of things however so the change does not happen.
However in this case the Monad operations can be used to implement the Functor and Applicative class methods. So it would be nice if we could get them for free if the author did not choose to write the Functor and Applicative instances.
So my suggestion is that we let classes declare default implementations of methods from super-classes.
class Functor m => Monad m where {- the ordinary bits -}
fmap f m = m >>= return . f
So if there already is a Functor instance for m then the default implementation of fmap is not used.
Does this proposal have any unintended consequences? I'm not sure. Please discuss :-)
Duncan
This is almost exactly the http://haskell.org/haskellwiki/Class_system_extension_proposal; that page has some discussion of implementation issues. Stefan

On Tue, 2007-12-11 at 07:07 -0800, Stefan O'Rear wrote:
This is almost exactly the http://haskell.org/haskellwiki/Class_system_extension_proposal; that page has some discussion of implementation issues.
Oh yes, so it is. Did this proposal get discussed on any mailing list? I'd like to see what people thought. Was there any conclusion about feasibility? Duncan

Duncan Coutts wrote:
On Tue, 2007-12-11 at 07:07 -0800, Stefan O'Rear wrote:
This is almost exactly the http://haskell.org/haskellwiki/Class_system_extension_proposal; that page has some discussion of implementation issues.
Oh yes, so it is. Did this proposal get discussed on any mailing list? I'd like to see what people thought. Was there any conclusion about feasibility?
Ross proposed this on the libraries list in 2005: http://www.haskell.org//pipermail/libraries/2005-March/003494.html and I brought it up for Haskell': http://www.haskell.org//pipermail/haskell-prime/2006-April/001344.html see also this: http://www.haskell.org//pipermail/haskell-prime/2006-August/001582.html Unfortunately the Haskell' wiki doesn't have a good summary of the issues; it should. I'll add these links at least. Cheers, Simon

On Tue, Dec 11, 2007 at 04:26:52PM +0000, Simon Marlow wrote:
Duncan Coutts wrote:
On Tue, 2007-12-11 at 07:07 -0800, Stefan O'Rear wrote:
This is almost exactly the http://haskell.org/haskellwiki/Class_system_extension_proposal; that page has some discussion of implementation issues.
Oh yes, so it is. Did this proposal get discussed on any mailing list? I'd like to see what people thought. Was there any conclusion about feasibility?
Ross proposed this on the libraries list in 2005:
http://www.haskell.org//pipermail/libraries/2005-March/003494.html
and again in 2003: http://www.haskell.org/pipermail/haskell-cafe/2003-July/004654.html

On Tue, 2007-12-11 at 16:38 +0000, Ross Paterson wrote:
On Tue, Dec 11, 2007 at 04:26:52PM +0000, Simon Marlow wrote:
Duncan Coutts wrote:
On Tue, 2007-12-11 at 07:07 -0800, Stefan O'Rear wrote:
This is almost exactly the http://haskell.org/haskellwiki/Class_system_extension_proposal; that page has some discussion of implementation issues.
Oh yes, so it is. Did this proposal get discussed on any mailing list? I'd like to see what people thought. Was there any conclusion about feasibility?
Ross proposed this on the libraries list in 2005:
http://www.haskell.org//pipermail/libraries/2005-March/003494.html
and again in 2003:
http://www.haskell.org/pipermail/haskell-cafe/2003-July/004654.html
Ross, you need to shout louder! :-) If it really would work ok we should get it fully specified and implemented so we can fix the most obvious class hierarchy problems in a nice backwards compatible way. Things are only supposed to be candidates for Haskell' if they're already implemented. So how about the objection that two sub classes could try and define conflicting defaults for a superclass method? David Menendez had the example of Monad and CoMonad defining Functor's fmap. Can that easily be rejected? I suppose it gives rise to duplicate instance declarations so it'd be an error in the same way that defining clashing instances in two different modules and importing both into a third module. Another error case would be: module A where data Foo module B where instance Functor Foo module C where instance Monad Foo module D import Bar import Baz Now we get slashing instances for Functor, since both Bar and Baz export Functor instances for Foo. Since the instance for Functor Foo was not visible in module C, so we get the default instance defined in C. So the one slightly surprising thing about this suggestion is that we get an instance defined or not depending on whether there is already an instance in scope. In the Functor, Applicative, Monad case I don't see that causing a problem in practise but is it worse more generally? Duncan

| If it really would work ok we should get it fully specified and | implemented so we can fix the most obvious class hierarchy problems in a | nice backwards compatible way. Things are only supposed to be candidates | for Haskell' if they're already implemented. Getting it fully specified is the first thing. Personally I am not keen about a) coupling it to explicit import/export (independently-desirable though such a change might be) b) having instance declarations silently spring into existence Concerning (b) here's a suggestion. As now, require that every instance requires an instance declaration. So, in the main example of http://haskell.org/haskellwiki/Class_system_extension_proposal, for a new data type T you'd write instance Monad T where return = ... (>>=) = ... instance Functor T instance Applicative T The instance declaration for (Functor T) works just as usual (no explicit method, so use the default method) except for one thing: how the default method is found. The change is this: Given "instance C T where ...", for any method 'm' not defined by "...": for every class D of which C is a superclass where there is an instance for (D T) see if the instance gives a binding for 'm' If this search finds exactly one binding, use it, otherwise behave as now This formulation reduces the problem to a more manageable one: a search for the default method. I'm not sure what is supposed to happen if the instance is for something more complicated (T a, say, or multi-parameter type class) but I bet you could work it out. All these instances would need to be in the same module: - you can't define Functor T without Monad T, because you want to pick up the monad-specific default method - you can't define Monad T without Functor T, because the latter is a superclass of the former It still sounds a bit complicated. Simon

Simon Peyton-Jones wrote:
b) having instance declarations silently spring into existence
Concerning (b) here's a suggestion. As now, require that every instance requires an instance declaration. So, in the main example of http://haskell.org/haskellwiki/Class_system_extension_proposal, for a new data type T you'd write
instance Monad T where return = ... (>>=) = ...
instance Functor T instance Applicative T
Without the automatic search, this is already possible class Functor f where fmap :: (a -> b) -> f a -> f b class Functor m => Monad m where return :: a -> m a (>>=) :: m a -> (a -> m b) -> m b -- aka liftM fmapDefault :: Monad m => (a -> b) -> m a -> m b fmapDefault f m = m >>= (return . f) instance Monad [] where return x = [x] (>>=) = flip concatMap instance Functor [] where fmap = fmapDefault fmap is already written for you, the instance declaration is only boilerplate. I first saw this in Data.Traversable . Regards, apfelmus

On Dec 11, 2007 1:29 PM, apfelmus
Without the automatic search, this is already possible
class Functor f where fmap :: (a -> b) -> f a -> f b
class Functor m => Monad m where return :: a -> m a (>>=) :: m a -> (a -> m b) -> m b
-- aka liftM fmapDefault :: Monad m => (a -> b) -> m a -> m b fmapDefault f m = m >>= (return . f)
instance Monad [] where return x = [x] (>>=) = flip concatMap
instance Functor [] where fmap = fmapDefault
fmap is already written for you, the instance declaration is only boilerplate. I first saw this in Data.Traversable .
This is pretty much how I define Functor and Applicative instances for my
monads. It is admittedly irritating to have to write out the boilerplate,
but it doesn't seem irritating enough to require a language extension to
eliminate.
--
Dave Menendez

Simon Peyton-Jones wrote:
Given "instance C T where ...", for any method 'm' not defined by "...": for every class D of which C is a superclass where there is an instance for (D T) see if the instance gives a binding for 'm' If this search finds exactly one binding, use it, otherwise behave as now
A better rule would be: If this search finds exactly one binding that is minimal in the partial ordering defined by the superclass hierarchy, use it, otherwise behave as now. Would that be much harder to implement? -Yitz

Simon Peyton-Jones wrote:
Concerning (b) here's a suggestion. As now, require that every instance requires an instance declaration. So, in the main example of http://haskell.org/haskellwiki/Class_system_extension_proposal, for a new data type T you'd write instance Monad T where return = ... (>>=) = ...
instance Functor T instance Applicative T
Another alternative is to allow multiple classes in an instance declaration: instance (Monad T, Functor T, Applicative T) where return = ... (>>=) = ... The advantage is that this makes it more clear where the instances come from, especially if a class has multiple sub classes with different defaults. It also eliminates tricky issues with importing. Of course this needs some (albeit very little) new syntax. I wrote a proposal a while ago, http://haskell.org/haskellwiki/Superclass_defaults Twan

I had it pretty well worked out for single parameter type classes, but I
couldn't see any nice extension to multiple parameters.
On Dec 11, 2007 5:30 PM, Simon Peyton-Jones
| If it really would work ok we should get it fully specified and | implemented so we can fix the most obvious class hierarchy problems in a | nice backwards compatible way. Things are only supposed to be candidates | for Haskell' if they're already implemented.
Getting it fully specified is the first thing.
Personally I am not keen about
a) coupling it to explicit import/export (independently-desirable though such a change might be)
b) having instance declarations silently spring into existence
Concerning (b) here's a suggestion. As now, require that every instance requires an instance declaration. So, in the main example of http://haskell.org/haskellwiki/Class_system_extension_proposal, for a new data type T you'd write instance Monad T where return = ... (>>=) = ...
instance Functor T instance Applicative T
The instance declaration for (Functor T) works just as usual (no explicit method, so use the default method) except for one thing: how the default method is found. The change is this: Given "instance C T where ...", for any method 'm' not defined by "...": for every class D of which C is a superclass where there is an instance for (D T) see if the instance gives a binding for 'm' If this search finds exactly one binding, use it, otherwise behave as now
This formulation reduces the problem to a more manageable one: a search for the default method.
I'm not sure what is supposed to happen if the instance is for something more complicated (T a, say, or multi-parameter type class) but I bet you could work it out.
All these instances would need to be in the same module: - you can't define Functor T without Monad T, because you want to pick up the monad-specific default method - you can't define Monad T without Functor T, because the latter is a superclass of the former
It still sounds a bit complicated.
Simon _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On Dec 11, 2007 9:20 AM, Duncan Coutts
So my suggestion is that we let classes declare default implementations of methods from super-classes.
Does this proposal have any unintended consequences? I'm not sure.
Please discuss :-) It creates ambiguity if two classes declare defaults for a common
superclass.
My standard example involves Functor, Monad, and Comonad. Both Monad and
Comonad could provide a default implementation for fmap. But let's say I
have a type which is both a Monad and a Comonad: which default
implementation gets used?
I'm disappointed to see this objection isn't listed on the wiki.
--
Dave Menendez

Duncan Coutts
We all know that Functor should have been a superclass of Monad, and indeed we now know that Applicative should be too. Making such a change would break lots of things however so the change does not happen.
However in this case the Monad operations can be used to implement the Functor and Applicative class methods. So it would be nice if we could get them for free if the author did not choose to write the Functor and Applicative instances.
...
Does this proposal have any unintended consequences? I'm not sure. Please discuss :-)
I started a discussion on these lines on the Haskell prime mailing list a while ago. Apart from the objections others have posted, I think just supplying methods a bit unstructured. In http://article.gmane.org/gmane.comp.lang.haskell.prime/1578/match=all+monads... I suggested instead that such defaults should be instance declarations. It gives much the same effect (and with similar problems), but makes it clear to which class the methods being declared belong. If you were to find a middle ground (say using the syntax I suggest there but with the interpretation that it supplies default methods for the superclass, and use Simons suggestion of requiring explicit empty instance declarations when you want to use them, we might get somewhere sensible. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk
participants (11)
-
apfelmus
-
David Menendez
-
Duncan Coutts
-
Jon Fairbairn
-
Lennart Augustsson
-
Ross Paterson
-
Simon Marlow
-
Simon Peyton-Jones
-
Stefan O'Rear
-
Twan van Laarhoven
-
Yitzchak Gale