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

GHC ghc-devs at haskell.org
Tue Oct 21 13:45:54 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:              |
-------------------------------------+-------------------------------------

Comment (by goldfire):

 Urgh.

 This gets even worse. Look at this:

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

 import Language.Haskell.TH
 import Data.Proxy

 type family Silly :: k -> *
 type instance Silly = (Proxy :: * -> *)
 type instance Silly = (Proxy :: (* -> *) -> *)

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

 This produces

 {{{
 type family Main.Silly :: k_0 -> *
 type instance Main.Silly = Data.Proxy.Proxy
 type instance Main.Silly = Data.Proxy.Proxy
 }}}

 Now, there's no variables to annotate! I think the thing to do is to kind-
 annotate every poly-kinded tycon application, ''and'' every variable on
 the LHS whose kind includes a kind variable. I guess this conclusion is a
 bare-bones attempt at the "inference" described in comment:1, but it seems
 straightforward enough to implement.

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


More information about the ghc-tickets mailing list