report ambiguous type variables more consistently
{-# LANGUAGE MultiParamTypeClasses #-}
module Amb where
class C a b where
f :: (a,b)
instance C Int Char where
f = undefined
{-
x = fst f
/home/saizan/snippets/Amb.hs:7:8:
Ambiguous type variables `a', `b' in the constraint:
`C a b'
arising from a use of `f' at /home/saizan/snippets/Amb.hs:7:8
Possible cause: the monomorphism restriction applied to the following:
x :: a (bound at /home/saizan/snippets/Amb.hs:7:0)
Probable fix: give these definition(s) an explicit type signature
or use -XNoMonomorphismRestriction
Failed, modules loaded: none.
-}
{-
y = fst f :: Int
/home/saizan/snippets/Amb.hs:21:8:
No instance for (C Int b)
arising from a use of `f' at /home/saizan/snippets/Amb.hs:21:8
Possible fix: add an instance declaration for (C Int b)
In the first argument of `fst', namely `f'
In the expression: fst f :: Int
In the definition of `y': y = fst f :: Int
Failed, modules loaded: none.
-}
Both x and y have the same problem, there isn't enough type information to let the typechecker decide on an instance, so it seems they should produce similar error messages.
In particular, the error for y is quite confusing since it can be reasonably interpreted as saying there's no type b for which there's an instance C Int b, which in fact is not true, so i think explicitly mentioning the ambiguity like in the first message would help many to understand the problem better.
I can see though that an "instance C Int b" could make sense, more often than C a b, so maybe "Possible fix: add an instance declaration for (C Int b)" should be conserved, even if it still has the problem of expressing that the second argument needs to be a variable.
Trac metadata
Trac field | Value |
---|---|
Version | 7.0.1 |
Type | FeatureRequest |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |