{-# LANGUAGE ConstraintKinds #-}type Ring = Numinstance Ring [a] where (+) = (++)
Currently this gives an error: (+) is not a visible method of class Ring. After removing the last line, the code compiles with warnings about missing methods.
Trac metadata
Trac field
Value
Version
7.6.1
Type
Bug
TypeOfFailure
OtherFailure
Priority
normal
Resolution
Unresolved
Component
Compiler
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information
Child items
0
Show closed items
No child items are currently assigned. Use child items to break down this issue into smaller parts.
I can see your point; and I agree it's odd that it's accepted when no methods are given. But it's not easy to fix in the way you want. Here's why.
Suppose we have
class C a where reverse :: a -> ainstance C Int where reverse x = x
When GHC encounters the binding reverse x = x, it has to figure out which reverse you mean -- there are two in scope. Ah! Since this is in an instnace declaraction, it must be the one that's method of class C, not the one from Prelude.
This scope resolution is done by the renamer. The renamer does not understand type synonyms (they are interpreted by the subsequent type checker), so it can't figure out that Ring really means Num in your example.
I can't see an easy way round this in GHC's current structure. The only think that comes to mind is to postpone all scope resolution for instance bindings until the type checker. But that would mean a bit of an upheaval of datatypes etc. Quite do-able, but not very simple.
As things stand it might be more consistent to reject an instance declaration if the "class" turns out to be a synonym.
FWIW some form of fix for this would be quite useful to me as well.
In the lens package we have a lot of classes that look like
class Foo s t a b | s -> a, t -> b, s a -> t, t a -> s
where s = t, a = b are always legal to instantiate, so many instances look like
class IsText Text Text Char Char
when we're dealing with these 4 parameter families for data types we adopt the convention that
type Foo' a b = Foo a a b b
But we cannot do this for the declaration site for the instances.
If we could this would (eventually, when we can remove support for pre-constraint kinds compilers) enable us to more easily expand our definitions later on.
More pie-in-the-sky would be being able to use
type Foo a b = Bar a => Baz a b
instance Foo a b
as
instance Bar a => Baz a b
it would be consistent with the other uses of type, but Bar a => Baz a b doesn't (currently) have a sensible kind.
Has there been any more interest in this bug? I happened to run across it for the first time today with a problem essentially identical to @ekmett's. Any chance of it getting fixed one way or the other?
Building on ticket:7543#comment:67427, would it be easy to build this feature if the names of the methods have no scoping conflicts? That is, just do a normal (non-instance-style) lookup of method names, even in instances. If there is no ambiguity, proceed. If there is ambiguity, look at the instance head. If it's a class name, use that to disambiguate. Otherwise (if it's a synonym or bogus), report an error. That seems simple enough and without undue upheaval.
Personally, I don't think disambiguating among multiply-in-scope names should hold this feature up.
Yes we could do as Richard suggests. It'd be one more thing to explain in the user manual. And I'm a little suspicious, because now if I'm hunting for instances of some class I need to take synonyms into account.
I grant that we already allow type synonyms in the instance head, and that too makes hunting for instances harder in a similar way.
Are these disadvantages outweighed by the advantages? Do more than two people want this?
The other thing we could do is support this feature at synonym-definition time. When defining a type synonym such that the head of the RHS is a class, record this fact in the TyCon and corresponding iface info. If such a synonym appears as the head of an instance declaration, we use this tidbit to do the name lookup.
This would be easier to explain, at least, and wouldn't require much upheaval either. Actually, this is probably simpler than my idea in ticket:7543#comment:97309.
About looking up instances: we really need to move beyond grep for this sort of thing! Of course, I exclusively use grep for this sort of thing... because I don't have a better option to hand. But that's a story for another day. In the meantime, worrying about obfuscation via synonyms is valid, but also not something that (I believe) should hold this up.
This would be easier to explain, at least, and wouldn't require much upheaval either. Actually, this is probably simpler than my idea in ticket:7543#comment:97309.
I don't think so.
type C a = X a Numtype X a b = b a
I really don't want to put enough cleverness in the renamer to expand type synonyms on the fly.
I don't have a particular attachment to being able to do this, my biggest concern is that it's somewhat inconsistent behavior. If a constraint isn't a class, then it shouldn't be possible to make an instance of it. Or we should allow all constraints to be instantiated as classes. This could lead to some interesting problems to have to solve, such as when two constraints are used that could have overlapping names
module C1 whereclass C1 a where c :: a -> a
module C2 whereclass C2 a where c :: a -> a
module C whereimport C1import C2type Cs a = (C1 a, C2 a)instance Cs Int where C1.c = pred C2.c = succ
This won't work currently because you can't use qualified names in a binding position, but without the qualification you can't distinguish between the different c methods on the classes. I also can't say I'm a fan of having multiple instances defined in the same block. For example, the following would bother me
newtype MyInt = MyInt Inttype OrdNum a = (Num a, Ord a)instance OrdNum MyInt where compare (MyInt x) (MyInt y) = compare x y fromInteger = MyInt ...-- Results in-- instance Num MyInt-- instance Ord MyInt
Considering that the argument for being able use constraints like this is that it would slightly improve the usability of a handful of libraries, I'm personally leaning towards a fix that would simply disallow instancing anything that is not a class.