[GHC] #8953: Reifying poly-kinded type families misses kind annotations
GHC
ghc-devs at haskell.org
Thu Apr 3 17:52:52 UTC 2014
#8953: Reifying poly-kinded type families misses kind annotations
------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Template Haskell | Version: 7.9
Keywords: | Operating System: Unknown/Multiple
Architecture: Unknown/Multiple | Type of failure: None/Unknown
Difficulty: Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: |
------------------------------------+-------------------------------------
Consider the following two modules:
{{{
{-# LANGUAGE DataKinds, PolyKinds, TypeFamilies #-}
module A where
type family Poly (a :: k) :: *
type instance Poly (x :: Bool) = Int
type instance Poly (x :: Maybe k) = Double
}}}
{{{
{-# LANGUAGE TemplateHaskell #-}
module B where
import Language.Haskell.TH
import A
$( do info <- reify ''Poly
runIO $ putStrLn $ pprint info
return [] )
}}}
Compiling with HEAD yields this output:
{{{
type family A.Poly (a_0 :: k_1) :: *
type instance A.Poly x_2 = GHC.Types.Double
type instance A.Poly x_3 = GHC.Types.Int
}}}
The problem is that the type patterns in the reified instances are just
plain variables, without their kind annotations. This omission makes the
instance declarations unfaithful to the original meaning.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8953>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list