[GHC] #14710: GHC 8.4.1-alpha allows the use of kind polymorphism without PolyKinds

#14710: GHC 8.4.1-alpha allows the use of kind polymorphism without PolyKinds -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 8.4.1-alpha1 (Type checker) | Keywords: PolyKinds | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC accepts Unknown/Multiple | invalid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This program: {{{#!hs {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE ImpredicativeTypes #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} {-# OPTIONS_GHC -ddump-deriv #-} module Bug where import Data.Coerce import Data.Proxy class C a b where c :: Proxy (x :: a) -> b newtype I a = MkI a instance C x a => C x (Bug.I a) where c = coerce @(forall (z :: x). Proxy z -> a) @(forall (z :: x). Proxy z -> I a) c }}} is rightfully rejected by GHC 8.2.2: {{{ $ /opt/ghc/8.2.2/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:20:16: error: Unexpected kind variables Perhaps you intended to use PolyKinds In a type argument | 20 | c = coerce @(forall (z :: x). Proxy z -> a) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Bug.hs:21:16: error: Unexpected kind variables Perhaps you intended to use PolyKinds In a type argument | 21 | @(forall (z :: x). Proxy z -> I a) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ }}} But GHC 8.4.1-alpha2 actually //accepts// this program! {{{ $ /opt/ghc/8.4.1/bin/ghci Bug.hs GHCi, version 8.4.0.20180118: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Ok, one module loaded. }}} This is almost certainly bogus. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14710 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14710: GHC 8.4.1-alpha allows the use of kind polymorphism without PolyKinds -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.4.1-alpha1 checker) | Resolution: | Keywords: PolyKinds Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: simonpj (added) Comment: This regression was introduced in commit 0257dacf228024d0cc6ba247c707130637a25580 (`Refactor bindHsQTyVars and friends`). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14710#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14710: GHC 8.4.1-alpha allows the use of kind polymorphism without PolyKinds -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.4.1-alpha1 checker) | Resolution: | Keywords: PolyKinds Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Actually, this problem dates even further back than I imagined. Another problematic aspect of this code is that the definition of `C` alone is accepted: {{{#!hs {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# OPTIONS_GHC -ddump-deriv #-} module Bug where import Data.Coerce import Data.Proxy class C a b where c :: Proxy (x :: a) -> b }}} In fact, even GHC 8.0 accepts this! This appears to be a behavioral change from GHC 7.10.3, where this code is rejected: {{{ $ /opt/ghc/7.10.3/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:10:20: Type variable ‘a’ used in a kind In the kind ‘a’ In the type ‘Proxy (x :: a) -> b’ In the class declaration for ‘C’ }}} (My guess is that commit 6746549772c5cc0ac66c0fce562f297f4d4b80a2, `Add kind equalities to GHC.`, is responsible for this.) Really, defining `C` should require `PolyKinds` (or perhaps even `TypeInType`), as the type variable `a` is also used as a kind variable within the type of `c`. You don't even need type classes for this issue to surface. Here is another problematic definition that uses plain old functions: {{{#!hs {-# LANGUAGE KindSignatures #-} {-# LANGUAGE ScopedTypeVariables #-} module Bug where import Data.Proxy f :: forall a. a -> a f x = const x g where g :: Proxy (x :: a) g = Proxy }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14710#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14710: GHC 8.4.1-alpha allows the use of kind polymorphism without PolyKinds -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.4.1-alpha1 checker) | Resolution: | Keywords: PolyKinds Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): One way to summarize this issue in that at the moment, GHC believes it can spot any code that requires `PolyKinds` at the granularity of individual type variable telescopes (for instance, `forall (a :: k). <...>` would require `PolyKinds` since the telescope `forall (a :: k)` implicitly quantifies `k`). But really this isn't true—a type variable might seem perfectly normal //within// a telescope, but elsewhere in its body it might be used as a kind variable (as in the examples above)! So it feels like we should be validity checking //uses// of type variables as well, not just their binding sites. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14710#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14710: GHC 8.4.1-alpha allows the use of kind polymorphism without PolyKinds -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.4.1-alpha1 checker) | Resolution: | Keywords: PolyKinds Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Excellent diagnosis. This can't be too hard to fix, but I'm out of cycles. Happy to advise. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14710#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14710: GHC 8.4.1-alpha allows the use of kind polymorphism without PolyKinds -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.4.1-alpha1 checker) | Resolution: | Keywords: PolyKinds Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Well, I'd //like// to be able to fix this, but have no solid idea of where to start. My first inclination would be to insert a validity check into the `KindedTyVar` case of [http://git.haskell.org/ghc.git/blob/f00ddea96cc856654ac90fcf7d29556a758d6648... bindLHsTyVarBndrs]. I'd need to do roughly the following: * I'd need to figure out which variables are already bound in an enclosing scope (after all, those are the only sorts of type variables that exhibit this problem). * I'd need to partition them into type and kind variables (we only care about the kind variables). * Of those kind variables, I'd need to figure out which of them were originally bound as type variables. I'm afraid I don't know how to do any of those steps. Help? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14710#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14710: GHC 8.4.1-alpha allows the use of kind polymorphism without PolyKinds -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.4.1-alpha1 checker) | Resolution: | Keywords: PolyKinds Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Actually, if we decide to require the use of `TypeInType` (and not just `PolyKinds`) for this featurette, then checking binding sites wouldn't be enough. It turns out the GHC currently accepts this program without `TypeInType`: {{{#!hs {-# LANGUAGE PolyKinds #-} {-# LANGUAGE ScopedTypeVariables #-} module Bug where import Data.Proxy f :: forall k a. Proxy (a :: k) f = Proxy }}} But it seems like it shouldn't, since `k` is being quantified as a type variable but used as a kind variable. For comparison, if you tried this equivalent program: {{{#!hs {-# LANGUAGE PolyKinds #-} {-# LANGUAGE ScopedTypeVariables #-} module Bug where import Data.Proxy f :: forall k (a :: k). Proxy a f = Proxy }}} Then GHC will bleat about `TypeInType`: {{{ $ ghci Bug.hs GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:7:21: error: Type variable ‘k’ used in a kind. Did you mean to use TypeInType? the type signature for ‘f’ | 7 | f :: forall k (a :: k). Proxy a | ^ }}} So, in short: I'm even less sure about where to put this validity check :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14710#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14710: GHC 8.4.1-alpha allows the use of kind polymorphism without PolyKinds -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.4.1-alpha1 checker) | Resolution: | Keywords: PolyKinds Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): You'll need to make a few changes to fix this: - `TcHsType.tcLHsKindSig` should really call `checkValidType`. This was an oversight from likely long ago. - The `tc_infer_hs_type` case that deals with `HsKindSig` should, in turn, use `tcLHsKindSig`. - `checkValidType` will need to know whether it's checking a kind. If it is, and if `-XPolyKinds` isn't on (which is implied by `-XTypeInType`, so you don't need a separate `-XTypeInType` check), then complain about variables. Alternatively, you could conceivably catch this in the renamer. `RnTypes.rnHsTyKi` knows when it's renaming a kind (vs. a type). In the `HsTyVar` case, you could bleat with `-XNoPolyKinds` and spotting a variable whose name is in the type variable namespace (as opposed to a tycon, recalling tat `HsTyVar` includes both). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14710#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14710: GHC 8.4.1-alpha allows the use of kind polymorphism without PolyKinds -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.4.1-alpha1 checker) | Resolution: | Keywords: PolyKinds Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4554 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D4554 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14710#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14710: GHC 8.4.1-alpha allows the use of kind polymorphism without PolyKinds -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.4.1-alpha1 checker) | Resolution: | Keywords: PolyKinds Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4554 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Looks great. I've added a comment, but the new "Submit quietly" thing (which I dislike) means you may not see it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14710#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14710: GHC 8.4.1-alpha allows the use of kind polymorphism without PolyKinds
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: patch
Priority: high | Milestone: 8.4.1
Component: Compiler (Type | Version: 8.4.1-alpha1
checker) |
Resolution: | Keywords: PolyKinds
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC accepts | Unknown/Multiple
invalid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D4554
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#14710: GHC 8.4.1-alpha allows the use of kind polymorphism without PolyKinds -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: high | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.4.1-alpha1 checker) | Resolution: fixed | Keywords: PolyKinds Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC accepts | Test Case: invalid program | polykinds/T14710 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4554 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * testcase: => polykinds/T14710 * status: patch => closed * resolution: => fixed * milestone: 8.4.1 => 8.6.1 Comment: It's probably not wise to merge this into 8.4.2, since this technically causes `PolyKinds` to reject more programs than before (even if the programs it was erroneously accepting were only valid for a few GHC releases). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14710#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC