[GHC] #8953: Reifying poly-kinded type families misses kind annotations

GHC ghc-devs at haskell.org
Tue Oct 21 13:39:59 UTC 2014


#8953: Reifying poly-kinded type families misses kind annotations
-------------------------------------+-------------------------------------
              Reporter:  goldfire    |            Owner:  goldfire
                  Type:  bug         |           Status:  new
              Priority:  normal      |        Milestone:
             Component:  Template    |          Version:  7.9
  Haskell                            |         Keywords:
            Resolution:              |     Architecture:  Unknown/Multiple
      Operating System:              |       Difficulty:  Unknown
  Unknown/Multiple                   |       Blocked By:
       Type of failure:              |  Related Tickets:
  None/Unknown                       |
             Test Case:              |
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------

Old description:

> 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.

New description:

 Consider the following:

 {{{
 {-# LANGUAGE DataKinds, PolyKinds, TypeFamilies, TemplateHaskell #-}

 import Language.Haskell.TH

 type family Poly (a :: k) :: *
 type instance Poly (x :: Bool) = Int
 type instance Poly (x :: Maybe k) = Double

 $( do info <- reify ''Poly
       runIO $ putStrLn $ pprint info
       return [] )
 }}}

 Compiling with HEAD yields this output:

 {{{
 type family Main.Poly (a_0 :: k_1) :: *
 type instance Main.Poly x_2 = GHC.Types.Double
 type instance Main.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.

--

Comment (by goldfire):

 Only one module is required. Previous bug description had two.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8953#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list