Jules Bean wrote:
David Menendez wrote:
Duncan Coutts wrote:
So my suggestion is that we let classes declare default implementations of methods from super-classes.

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.

Doesn't sound like a very big problem. That would just be a compile time error ("More than one default for fmap possible for Foo, please reslve ambiguity").

And how would you resolve that ambiguity?

  module Control.Functor.UsefulStuff (hylo) where
    hylo :: Functor f => (a -> f a) -> (f b -> b) -> a -> b
    hylo f g = g . fmap (hylo f g) . f

  module BANG where
    import Foo (Foo)
    import Foo.Is.Monad
    import Foo.Is.Comonad

    import Control.Functor.UsefulStuff (hylo)

    bar :: Bar -> Foo Bar
    baz :: Foo Baz -> Baz

    bang = hylo bar baz

The problem is that the ambiguity may arise by just importing different modules while not having access to the offending call to fmap .

Also note that as much as I'd like explicit import/export of type class instances, the current implicit and global export is no accident, it's crucial for well-definedness. See also the second half of

  http://article.gmane.org/gmane.comp.lang.haskell.general/15471


In other words, the main problem of all those superclass/explicit import/export proposals is that there are no proofs of the fact that they only allow well-defined programs. The homework isn't done yet, discussing adoption is too early.


Regards,
apfelmus

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to