[GHC] #9081: Template Haskell gets confused with scoped kind variables in a class declaration

GHC ghc-devs at haskell.org
Tue May 6 17:23:51 UTC 2014


#9081: Template Haskell gets confused with scoped kind variables in a class
declaration
-------------------------------------+------------------------------------
        Reporter:  goldfire          |            Owner:
            Type:  bug               |           Status:  new
        Priority:  normal            |        Milestone:
       Component:  Template Haskell  |          Version:  7.8.2
      Resolution:                    |         Keywords:
Operating System:  Unknown/Multiple  |     Architecture:  Unknown/Multiple
 Type of failure:  None/Unknown      |       Difficulty:  Unknown
       Test Case:                    |       Blocked By:
        Blocking:                    |  Related Tickets:
-------------------------------------+------------------------------------

Comment (by goldfire):

 This problem came up in a slightly different context. Compiling this
 module

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

 module A where

 import Language.Haskell.TH

 $( do a <- newName "a"
       k <- newName "k"
       b <- newName "b"
       return [ ClassD [] (mkName "C") [KindedTV a (VarT k)] []
                [ FamilyD TypeFam (mkName "TF") [KindedTV b (VarT k)]
 Nothing ] ] )

 $(do infoC  <- reify ''C
      infoTF <- reify ''TF
      runIO $ do
        putStrLn (show infoC)
        putStrLn (show infoTF)
      return [])
 }}}

 produces

 {{{
 ClassI (ClassD [] A.C [KindedTV a_1627506463 (VarT k_1627506468)] [] [])
 []
 FamilyI (FamilyD TypeFam A.TF [KindedTV b_1627506465 (VarT k_1627506464)]
 (Just StarT)) []
 }}}

 Note that the uniques in the `k` variables in the output are different.

 It's possible that these are two separate bugs, but my hunch is that they
 are the same.

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


More information about the ghc-tickets mailing list