{-# LANGUAGE StandaloneKindSignatures #-}{-# LANGUAGE TypeFamilies #-}moduleMainwhereimportData.Kind(Constraint,Type)datafamilyPit::TypetypeFunctionSymbol::Type->TypetypeFunctionSymbolt=TypetypeIsSum::foralls.FunctionSymbols->ConstraintclassIsSum(sumf::FunctionSymbolt)wheresumConNames::Pit
crashes GHC like this:
generic-bug.hs:15:23: error: []8;;https://errors.haskell.org/messages/GHC-76329\GHC-76329]8;;\] • GHC internal error: ‘t’ is not in scope during type checking, but it passed the renamer tcl_env of environment: [ahc :-> Type variable ‘sumf’ = sumf :: FunctionSymbol s, awz :-> Type variable ‘s’ = s :: *, rh7 :-> ATcTyCon IsSum :: forall s. FunctionSymbol s -> Constraint] • In the first argument of ‘Pi’, namely ‘t’ In the type signature: sumConNames :: Pi t In the class declaration for ‘IsSum’ |15 | sumConNames :: Pi t | ^
HEAD, 9.8, 9.6, all of them!
Edited
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information
Child items
...
Show closed items
Linked items
0
Link issues together to show that they're related or that one is blocking others.
Learn more.
This is very awkward. Notice that FunctionSymbol is a phantom type synonym. So given the separate kind signature
type IsSum :: forall s. FunctionSymbol s -> Constraint
we don't have a way to match up the s in the signature with the t in
class IsSum (sumf :: FunctionSymbol t) where
because FunctionSymbol t is phantom. Indeed maybe you could say
class IsSum (sumf :: FunctionSymbol (p,q)) where
Yuk. This is very much a corner case. I rather think that we should error if a pattern-signature-bound type variable occurs only under a type synonym.
Perhaps that rule should apply more generally. Consider this
type FS t = Intf :: Int -> Boolf (x :: FS a) = True :: a
THis is actually accepted today. a is bound to a unification variable, wich ultimately turns out to be Bool. But that is pretty horrible. And in the context of kind-checking a class decl with a separaet kind signature, it is not easy to "just make it a unification variable".
For now I propose to make this situation (which occurs only with standalone kind signatures) error saying something like:
Type variable `t` is not determined by the standalone kind signature. (Perhaps it appears only under a type synonym.)
I'm somewhat surprised by this conclusion. I was under the impression that this:
classIsSum(sumf::FunctionSymbolt)where
Was syntactic sugar for this:
classIsSum@t(sumf::FunctionSymbolt)where
And GHC already knows how to match up the s in type IsSum :: forall s. ... with class IsSum @t .... In fact, this does work:
{-# LANGUAGE AllowAmbiguousTypes #-}{-# LANGUAGE TypeAbstractions #-}typeIsSum::foralls.FunctionSymbols->Constraint-- Note the explicit @tclassIsSum@t(sumf::FunctionSymbolt)wheresumConNames::Pit
class IsSum (sumf :: FunctionSymbol (Int,t)) where sumConNames :: Pi t
I'm not sure what to remark on here, other than to say that that should be syntactic sugar for:
classIsSum@t(sumf::FunctionSymbol(Int,t))where...
And now the same reasoning as above applies.
And what order would you like the variables in? Is
class IsSum (sumf :: FunctionSymbol (p,q)) where
short for
class IsSum @p @q (sumf :: FunctionSymbol (p,q)) where
or
class IsSum @q @p (sumf :: FunctionSymbol (p,q)) where
Rememeber, FunctionSymbol just tosses away its argument.
The specification in this section of the GHC User's Guide would suggest that the only correct answer is @p @q. The specification says nothing about "tossing away arguments", which I think is a good thing, since I think the order of type variables should be apparent with a simple syntactic traversal over the definition, without caring about things such as type synonym expansion.
And in fact, if you write this code without a standalone kind signature, i.e.,
{-# LANGUAGE AllowAmbiguousTypes #-}{-# LANGUAGE DataKinds #-}{-# LANGUAGE StandaloneKindSignatures #-}{-# LANGUAGE TypeFamilies #-}moduleFoowhereimportData.Kind(Constraint,Type)datafamilyPit::TypetypeFunctionSymbol::Type->TypetypeFunctionSymbolt=Type-- NB: No standalone kind signatureclassIsSum(sumf::FunctionSymbol(p,q))wheresumConNames::Pi(p,q)
And then ask GHCi what the order of type variables is, then it will give exactly the @p @q ordering:
λ> :set -fprint-explicit-kinds λ> :info IsSumtype IsSum :: forall p q. FunctionSymbol (p, q) -> Constraintclass IsSum @p @q sumf where sumConNames :: Pi (p, q) {-# MINIMAL sumConNames #-} -- Defined at Foo.hs:15:1
What's more, GHCi even tells you the kind of IsSum is inferred to be type IsSum :: forall p q. FunctionSymbol (p, q) -> Constraint, exactly as you would expect. This makes it even stranger that it you actually insert this standalone kind signature into the program:
Then GHC no longer accepts it. So now we have a situation where GHC has no difficulties inferring a type, but it cannot check the type. That seems very smelly.
type IsWombat :: forall q p. (p,q) -> Constraintclass IsSum (a :: (r,s)) where ...
Ah, that is a very compelling example. Indeed, I don't want to change the behavior of this program, and thinking about how to implement this, it's difficult to see how to implement this other than by unification. And if you use unification, then hiding the type variables behind a type synonym like FunctionSymbol would definitely wreak havoc.
In short, you've won me over to your side. I'm fine with rejecting the original example (even if it is a bit weird that it works without a standalone kind signature).
commit 6dbab1808bfbe484b3fb396aab1d105314f918d8Author: Simon Peyton Jones <simon.peytonjones@gmail.com>Date: Tue Nov 7 23:51:19 2023 +0100 Add an extra check in kcCheckDeclHeader_sig Fix #24083 by checking for a implicitly-scoped type variable that is not actually bound. See Note [Disconnected type variables] in GHC.Tc.Gen.HsType For some reason, on aarch64-darwin we saw a 2.8% decrease in compiler allocations for MultiLayerModulesTH_Make; but 0.0% on other architectures. Metric Decrease: MultiLayerModulesTH_Make compiler/GHC/Tc/Errors/Ppr.hs | 10 ++++++++++ compiler/GHC/Tc/Errors/Types.hs | 7 +++++++ compiler/GHC/Tc/Gen/HsType.hs | 66 +++++++++++++++++++++++++++++++++++++++++++++++++++++++++----- compiler/GHC/Types/Error/Codes.hs | 1 + compiler/GHC/Types/Hint.hs | 4 ++++ compiler/GHC/Types/Hint/Ppr.hs | 3 +++ testsuite/tests/polykinds/T24083.hs | 14 +++++++++++++ testsuite/tests/polykinds/T24083.stderr | 6 ++++++ testsuite/tests/polykinds/all.T | 1 + 9 files changed, 107 insertions(+), 5 deletions(-)
I'm not sure about backporting. Probably worth it, but it's very much a corner case. Hence re-opening @bgamari@wz1000