#2895: Implement the "Class System Extension" proposal
---------------------------------+------------------------------------------
Reporter: porges | Owner:
Type: feature request | Status: new
Priority: normal | Milestone: _|_
Component: Compiler | Version: 6.10.1
Keywords: proposal | Testcase:
Blockedby: | Difficulty: Unknown
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
Changes (by batterseapower):
* failure: => None/Unknown
Comment:
I think the answers to your questions are:
* What triggers the generation of an instance using superclass defaults
is exactly the same as what triggers an error message like this from GHC:
{{{
No instance for (Functor Maybe)
arising from the superclasses of an instance declaration
Possible fix: add an instance declaration for (Functor Maybe)
In the instance declaration for `Monad Maybe'
}}}
i.e. you get a generated instance only if GHC can't already find one. So
if I add a (Functor m) constraint to the Monad class in base and the user
has already declared a Functor instance we keep that one. In particular,
this means that if the existing instance is overlapped (e.g. we have in
scope an instance (Functor a) for any a) then we use that one instead of
generating a new, more specific, instance.
* There is indeed no textual clue that you get a D instance, but we just
live with that
Here are two more problems though:
1. What do we do about disambiguation?
{{{
class Foo a where
foo :: a -> String
class (Foo a, Foo b) => Bar a b where
bar :: Either a b -> String
foo x = bar $ Left x
foo x = bar $ Right x
}}}
I would argue that it should be a type error because the RHSes for foo
do not have the same type. However, as an extension we could allow this:
{{{
class Foo a where
foo :: a -> String
class (Foo a, Foo b) => Bar a b where
bar :: Either a b -> String
(Foo a).foo = bar . Left
(Foo b).foo = bar . Right
}}}
Allowing qualified names like this is in the spirit that the variables
on the LHS of class/instance method declarations are much more like
references to variables than declarations of them. Neatly, this does not
conflict with existing syntax because programs like this one are rejected
(GHC says "Qualified name in binding position"):
{{{
import Control.Applicative
import qualified Data.Traversable as T
data I a = I a
instance T.Traversable I where
T.traverse f (I x) = pure I <*> f x
}}}
Alternative syntax for disambiguation could use explicit type signatures
(less nicely IMHO):
{{{
class Foo a where
foo :: a -> String
class (Foo a, Foo b) => Bar a b where
bar :: Either a b -> String
foo :: a -> String
foo = bar . Left
foo :: b -> String
foo = bar . Right
}}}
Both of these have their own issues (parsing in the first case, the
necessity of using unification to disambiguate in the second case).
2. Could we relax the requirements above to admit more programs?
{{{
class Baz a where
baz1 :: a -> String
baz2 :: a -> String
class Baz a => Quxx a where
quxx :: a -> (String, String)
baz1 = fst . quxx
baz2 = snd . quxx
instance Baz (String, String) where
baz1 = "Explicit1"
instance Quxx (String, String) where
quxx = id
main = print $ baz2 ("Implicit1", "Implicit2")
}}}
Under the rules I gave above, this is a compile-time error because we
have not given a definition for baz2 in our Baz instance, and we don't get
a Baz instance from superclass defaulting because one has been explicitly
declared. However, we could potentially "look ahead" to the Quxx
definition and use the superclass default to give a baz2 implementation,
thus printing "Implicit2" here.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2895#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs