
#12503: Template Haskell regression: GHC erroneously thinks a type variable is also a kind -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Template Haskell | Version: 8.0.1 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 RyanGlScott): The above program might seem somewhat contrived, but I actually ran into this problem in real code. The `generic-deriving` library does something very similar to derive `Generic1` instances using Template Haskell (that is, it re-uses the kind information it gets from `reify`). Here's some code that triggers the same error: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE PackageImports #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# OPTIONS_GHC -ddump-splices #-} module Regression where -- Using generic-deriving-1.11 import "generic-deriving" Generics.Deriving.TH data T k a $(deriveAll1 ''T) }}} {{{ $ /opt/ghc/8.0.1/bin/ghc Regression.hs [1 of 1] Compiling Regression ( Regression.hs, Regression.o ) Regression.hs:13:3-16: Splicing declarations deriveAll1 ''T ======> instance GHC.Generics.Generic1 (T (k_avv :: k_avx) :: GHC.Types.Type -> GHC.Types.Type) where type GHC.Generics.Rep1 (T (k_avv :: k_avx) :: GHC.Types.Type -> GHC.Types.Type) = GHC.Generics.D1 (GHC.Generics.MetaData "T" "Regression" "main" False) GHC.Generics.V1 GHC.Generics.from1 = \ val_a3ph -> case val_a3ph of { y_a3pi -> GHC.Generics.M1 (case y_a3pi of { _ -> error "No generic representation for empty datatype T" }) } GHC.Generics.to1 = \ val_a3pj -> case val_a3pj of { GHC.Generics.M1 y_a3pk -> case y_a3pk of { _ -> error "No values for empty datatype T" } } Regression.hs:13:3: error: Variable ‘k_avv’ used as both a kind and a type Did you intend to use TypeInType? Regression.hs:13:3: error: Variable ‘k_avv’ used as both a kind and a type Did you intend to use TypeInType? }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12503#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler