
#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): It should be noted that you don't need a type/kind variable explicitly named `k` to trigger this bug. You can also trigger it with an arbitrarily named variable like so: {{{#!hs {-# LANGUAGE CPP #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# OPTIONS_GHC -ddump-splices #-} module Regression2 where import Language.Haskell.TH data family T (a :: b) data instance T b class C a $(do FamilyI #if __GLASGOW_HASKELL__ >= 800 (DataFamilyD tName _ _) #else (FamilyD _ tName _ _) #endif [DataInstD [] _ [tyVar] #if __GLASGOW_HASKELL__ >= 800 _ #endif _ _] <- reify ''T d <- instanceD (cxt []) (conT ''C `appT` (conT tName `appT` return tyVar)) [] return [d]) }}} {{{ $ /opt/ghc/8.0.1/bin/ghc Regression2.hs [1 of 1] Compiling Regression2 ( Regression2.hs, Regression2.o ) Regression2.hs:(15,3)-(27,15): Splicing declarations do { FamilyI (DataFamilyD tName_a2RY _ _) [DataInstD [] _ [tyVar_a2RZ] _ _ _] <- reify ''T; d_a322 <- instanceD (cxt []) (conT ''C `appT` (conT tName_a2RY `appT` return tyVar_a2RZ)) []; return [d_a322] } ======> instance C (T (b_avD :: b_avO)) Regression2.hs:15:3: error: Variable ‘b_avD’ 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:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler