
#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