This code typechecks when k is brought into scope explicitly, but not implicitly (code example courtesy of RyanGlScott):
{-# LANGUAGE ExistentialQuantification #-}{-# LANGUAGE PatternSynonyms #-}{-# LANGUAGE PolyKinds #-}{-# LANGUAGE ScopedTypeVariables #-}moduleBugwhereimportData.KindimportData.ProxydataT=forallk(a::k).MkT(Proxya)-- Uncomment `k` and it typecheckspatternP::forall.()=>forall{-k-}(a::k).Proxya->TpatternPx=MkT(x::Proxy(a::k))
I know what is happening here. There are two different culprits in the codebase: the renamer and the typechecker.
The typechecker problem is much easier to understand. When typechecking the body of a pattern synonym, we bring certain type variables into scope. Here is the code that does it:
We bring the universal (required) type variables into scope, of course. We also bring the "existential" (provided) type variables into scope so that if we find any occurrences of them in the pattern synonym body, we can throw the relevant APromotionErr error.
Why did I write "existential" in scare quotes? Because the only existential type variables that are being brought into scope are the //implicitly quantified// ones (extra_ex). The remaining explicitly quantified ones (which live in ex_bndrs) are never brought into scope. Fortunately, fixing that is as simple as replacing extra_ex with ex_bndrs in the code above.
However, that change alone won't be enough. There is another problem in that GHC treats the occurrence of k in the pattern synonym type signature as being completely different from the occurrence of k in the body. Why? It's ultimately due to the renamer. In particular, because of the forall-or-nothing rule, the only explicitly quantified type variables that can ever brought into scope over the body must appear in a forall at the very front of the type signature. Since k is quantified by a nested forall, it is never brought into scope over the body during renaming, so the renamer gives a different unique to the occurrence of k in the body. (This is why GHC doesn't throw an error about k when typechecking the body, since the k that would throw an APromotionErr is actually different from the k in the body.)
I believe that we should be able to tweak things so that the renamer brings in the explicitly quantified universals //and// existentials from a pattern synonym type signature. Experimentally, this change was sufficient to accomplish that:
We also bring the "existential" (provided) type variables into scope so that if we find any occurrences of them in the pattern synonym body, //we can throw the relevant APromotionErr error//.
OK. Now I understand what you're doing better. Here is how I see it:
The renamer really shouldn't bring any of the existentials into scope, as existentials in a pattern synonym type don't scope over the (entire) pattern synonym body.
But the renamer can't tell existential implicitly bound variables from universal ones.
So, the renamer brings into scope only the universals and all the implicitly bound ones. This brings more variables into scope than it should.
The pattern synonym body then is renamed with some extra variables in scope, so more uniques match between the body and the type than morally should. In addition, less implicit quantification happens in the body than morally should.
The type-checker must deal with this unfolding disaster by duplicating the renamer's strange behavior: it brings into scope implicitly-bound existentials, just so that weird out-of-scope errors don't happen in the body. But it arranges to error if these are encountered, regardless.
The program in this ticket observes that the difference in treatment between implicitly bound and explicitly bound is awkward.
Your proposed solution is just to bring all existentials into scope in both the renamer and the type-checker, so that treatment is uniform. This is done even though existentials really shouldn't scope over the body.
This ticket is all about uniformity. The behavior in both the explicit case and the implicit case is, by itself, correct. But it's awkward for GHC's behavior to depend on the user's choice of implicit vs explicit binding.
Is that a fair assessment?
If so, I advocate: do nothing. This problem goes away when type variables and kind variables are treated identically, because if the user writes a forall, they will have to bind the kind variables explicitly anyway. If the user does not write a forall, then no scoping of type variables happens, so there's no problem here.
And, the patch as written actually makes GHC's behavior worse, in that it's further from the ideal of "existentials do not scope". The only reason to do this patch is that we cannot achieve the ideal, and this patch does indeed (and correctly, as far as I can tell) make the behavior more uniform.
So I do think the best way to fix this problem is to ignore it and wait for it to go away. :)
If so, I advocate: do nothing. This problem goes away when type variables and kind variables are treated identically, because if the user writes a forall, they will have to bind the kind variables explicitly anyway. If the user does not write a forall, then no scoping of type variables happens, so there's no problem here.
You lost me here. The problem is that if you write out the kind variable in the original program explicitly:
Then GHC //accepts// it, contrary to the claims of Note [Pattern synonym existentials do not scope]. So no, this problem won't go away when type and kind variables are treated identically. (In fact, int-index had to specifically mark this test case as expect_broken in his patch to implement the type-kind-variable merger.)
OK. If I understand you correctly, then the original program with k uncommented should be accepted. (I think you were hinting at this all along, but it wasn't obvious to me until ticket:16315#comment:168712.) If that's the case, then it sounds like the proper course of action is to:
Proceed with !361 (merged), as it will get rid of the awkwardness brought about by implicitly quantified variables being brought into scope.