PartialTypeSignatures trigger bogus "unbound implicit parameter" error
GHC seems to forget about in-scope implicit parameters when there's a hole in the type signature. Given
{-# LANGUAGE ImplicitParams, PartialTypeSignatures #-}
module Bad where
f1 :: (?loc :: Int, _) => Int
f1 = ?loc
f2 :: (?loc :: Int) => _
f2 = ?loc
GHC incorrectly reports the following errors.
% ghc -fforce-recomp Bad.hs
[1 of 1] Compiling Bad ( Bad.hs, Bad.o )
Bad.hs:8:6:
Unbound implicit parameter (?loc::Int)
arising from a use of implicit parameter ‘?loc’
In the expression: ?loc
In an equation for ‘f1’: f1 = ?loc
Bad.hs:11:1:
Occurs check: cannot construct the infinite type:
_ ~ (?loc::Int) => _
When checking that ‘f2’ has the specified type
f2 :: (?loc::Int) => _
Probable cause: the inferred type is ambiguous
Bad.hs:11:6:
Unbound implicit parameter (?loc::_)
arising from a use of implicit parameter ‘?loc’
Relevant bindings include f2 :: _ (bound at Bad.hs:11:1)
In the expression: ?loc
In an equation for ‘f2’: f2 = ?loc
?loc
is very clearly bound by both f1
and f2
's signature. f2
additionally reports what looks to me to be a bogus occurs-check error; we know from the theta that ?loc :: Int
so the hole should be solved for Int
.
I suspect this is all related to the fact that PartialTypeSignatures triggers tcPolyInfer
instead of tcPolyCheck
.
I think this is the same underlying bug as #10846 (closed).
Trac metadata
Trac field | Value |
---|---|
Version | 7.10.2 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |