HsOuterImplicits for associated type family instances are incorrect
While working on #13512, I noticed a buglet in the way that GHC implicitly quantifies type variables in associated type family instances. If you compile the following program with -ddump-rn-ast
on HEAD:
{-# LANGUAGE TypeFamilies #-}
module Bug where
class C a where
type T a b
instance C [a] where
type T [a] b = Either a b
This is what the T
instance's AST will look like:
(ClsInstD
...
(ClsInstDecl
...
(L
...
(HsSig
(NoExtField)
(HsOuterImplicit
[{Name: a_agi}])
...
[(L
...
(TyFamInstDecl
...
(FamEqn
...
(L
...
{Name: Bug.T})
(HsOuterImplicit
[{Name: a_agi}
,{Name: b_agj}])
...)))]))))
The suspicious part is the second HsOuterImplicit
for the T
TyFamInstDecl
. It claims that it implicitly quantifies both a
and b
, but this isn't true—the a
should already be in scope due to the first HsOuterImplicit
for the instance head. I would expect the second HsOuterImplicit
to only implicitly quantify b
.
I'm not aware of any user-observable behavior that results from this bug, but it does cause issues when implementing a fix for #13512. This bug can be fixed independently of #13512, so I decided to open a separate issue for it.