[Haskell-cafe] class default method proposal

Duncan Coutts duncan.coutts at worc.ox.ac.uk
Tue Dec 11 12:10:25 EST 2007


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



More information about the Glasgow-haskell-users mailing list