[GHC] #16391: "Quantified type's kind mentions quantified type variable" error with fancy-kinded GADT

#16391: "Quantified type's kind mentions quantified type variable" error with fancy-kinded GADT -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 (Type checker) | Keywords: TypeInType | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Given the following: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TypeFamilies #-} import Data.Kind type Const (a :: Type) (b :: Type) = a }}} GHC happily accepts these definitions: {{{#!hs type family F :: Const Type a where F = Int type TS = (Int :: Const Type a) }}} However, the situation becomes murkier with data types. For some reason, GHC //rejects// this definition: {{{#!hs data T :: Const Type a where MkT :: T }}} {{{ $ /opt/ghc/8.6.3/bin/ghc Bug.hs [1 of 1] Compiling Main ( Bug.hs, Bug.o ) Bug.hs:14:3: error: • Quantified type's kind mentions quantified type variable (skolem escape) type: forall a1. T of kind: Const * a • In the definition of data constructor ‘MkT’ In the data type declaration for ‘T’ | 14 | MkT :: T | ^^^^^^^^ }}} I'm not quite sure how to interpret that error message, but it seems fishy to me. Even fishier is the fact that GHC //accepts// this slight modification of `T`: {{{#!hs data T2 :: Const Type a -> Type where MkT2 :: T2 b }}} Quite mysterious. ----- I briefly looked into where this error message is being thrown from. It turns out if you make this one-line change to GHC: {{{#!diff diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs index 218f539c68..c7925767f9 100644 --- a/compiler/typecheck/TcValidity.hs +++ b/compiler/typecheck/TcValidity.hs @@ -635,7 +635,7 @@ check_type ve@(ValidityEnv{ ve_tidy_env = env, ve_ctxt = ctxt ; check_type (ve{ve_tidy_env = env'}) tau -- Allow foralls to right of arrow - ; checkTcM (not (any (`elemVarSet` tyCoVarsOfType phi_kind) tvs)) + ; checkTcM (not (any (`elemVarSet` exactTyCoVarsOfType phi_kind) tvs)) (forAllEscapeErr env' ty tau_kind) } where }}} Then GHC will accept `T`. Whether this change is the right choice to make, I don't think I'm qualified to say. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16391 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16391: "Quantified type's kind mentions quantified type variable" error with fancy-kinded GADT -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.6.3 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Two things here. First, could you add this note in module `Type` {{{ Note [Phantom type variables in kinds] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider type K (r :: RuntimeRep) = Type -- Note 'r' is unused data T r :: K r -- T :: forall r -> K r foo :: forall r. T r The body of the forall in foo's type has kind (K r), and normally it would make no sense to have forall r. (ty :: K r) because the kind of the forall would escape the binding of 'r'. But in this case it's fine because (K r) exapands to Type, so we expliclity /permit/ the type forall r. T r To accommodate such a type, in typeKind (forall a.ty) we use occCheckExpand to expand any type synonyms in the kind of 'ty' to eliminate 'a'. See kinding rule (FORALL) in Note [Kinding rules for types] And in TcValidity.checkEscapingKind, we use also use occCheckExpand, for the same reason. }}} just after `Note [Kinding rules for types]`. And refer to the Note from the calls to `occCheckExpand` in `typeKind` and `tcTypeKind`. Then, in `TcValidity`, perhpas pull that entire check out intoa named function `checkEscapingKind`, and refer again to the same Note. And I think it'd be simpler to use `occCheckExpand` there too. (Your suggestion of `exactTyCoVarsOfType` is equivalent, but using the same function in all three places seems better.) Does that make sense? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16391#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16391: "Quantified type's kind mentions quantified type variable" error with fancy-kinded GADT -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.6.3 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): The other bad thing is that the error message is a mess, becuase it mentions 'a' in one place and 'a1' in the other. Very confusing. Reason: {{{ (forAllEscapeErr env' ty tau_kind) }}} we pass `env'` (the result of tidying tvs) to `forAllEscapeErr`, which then prints `ty` in this tidy-env, thereby tidying the same tyvars again. This would not be hard to clear up, perhpas not by printing `ty` afresh, but by passing `tvs'` and `phi` to `forAllEscapeErr`, and printing the foralls manually, as it were. Does that make sense? Also I wonder if if might be easier to understand if we said {{{ • Quantified type's kind mentions quantified type variable type: forall a1. T where the body of the forall has this kind T :: Const * a }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16391#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16391: "Quantified type's kind mentions quantified type variable" error with fancy-kinded GADT -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.6.3 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): PS: here is a test caes that is rightly rejected by the test in `TcFValidity`. {{{ type family T (r :: RuntimeRep) :: TYPE r foo :: T r foo = foo }}} It'd be good to add a note to `TcValidity` to show this example of how the test does something useful. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16391#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16391: "Quantified type's kind mentions quantified type variable" error with fancy-kinded GADT -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.6.3 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/503 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => https://gitlab.haskell.org/ghc/ghc/merge_requests/503 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16391#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16391: "Quantified type's kind mentions quantified type variable" error with fancy-kinded GADT -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.10.1 Component: Compiler (Type | Version: 8.6.3 checker) | Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | dependent/should_compile/T16391a, | dependent/should_fail/T16391b Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/503 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * testcase: => dependent/should_compile/T16391a, dependent/should_fail/T16391b * resolution: => fixed * milestone: => 8.10.1 Comment: Landed in [https://gitlab.haskell.org/ghc/ghc/commit/068b7e983f4a0b35f453aa5e609998efd0... 068b7e98]. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16391#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16391: "Quantified type's kind mentions quantified type variable" error with
fancy-kinded GADT
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: closed
Priority: normal | Milestone: 8.10.1
Component: Compiler (Type | Version: 8.6.3
checker) |
Resolution: fixed | Keywords: TypeInType
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: GHC rejects | Test Case:
valid program | dependent/should_compile/T16391a,
| dependent/should_fail/T16391b
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/503
-------------------------------------+-------------------------------------
Comment (by Marge Bot
participants (1)
-
GHC