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

GHC ghc-devs at haskell.org
Tue May 6 16:28:45 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
       Keywords:                    |  Operating System:  Unknown/Multiple
   Architecture:  Unknown/Multiple  |   Type of failure:  None/Unknown
     Difficulty:  Unknown           |         Test Case:
     Blocked By:                    |          Blocking:
Related Tickets:                    |
------------------------------------+-------------------------------------
 When I say

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

 module Bug where

 import Data.Proxy

 $( [d|
   class kproxy ~ 'KProxy => C (kproxy :: KProxy a) where
     type TF (x :: a) :: Bool
   |])
 }}}

 I get

 {{{
 /Users/rae/temp/Bug.hs:7:4:
     Kind variable also used as type variable: ‘a_asJA’
     In the declaration for class C_asJy

 /Users/rae/temp/Bug.hs:7:4:
     The exact Name ‘kproxy_asJB’ is not in scope
       Probable cause: you used a unique Template Haskell name (NameU),
       perhaps via newName, but did not bind it
       If that's it, then -ddump-splices might be useful
 }}}

 The code in the TH quote compiles fine on its own.

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


More information about the ghc-tickets mailing list