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

#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

#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

#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): Confirmed reproducible in HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9081#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9081: Template Haskell gets confused with scoped kind variables in a class declaration -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Template | Version: 7.8.2 Haskell | Keywords: Resolution: duplicate | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * resolution: => duplicate Comment: Not reproducible anymore, in HEAD or in 7.8.3. I guess it's fixed now. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9081#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9081: Template Haskell gets confused with scoped kind variables in a class declaration -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Template | Version: 7.8.2 Haskell | Keywords: Resolution: duplicate | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: th/T9081 | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => th/T9081 Comment: I'll add it as a regression test though. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9081#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9081: Template Haskell gets confused with scoped kind variables in a class
declaration
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Template | Version: 7.8.2
Haskell | Keywords:
Resolution: duplicate | Architecture: Unknown/Multiple
Operating System: | Difficulty: Unknown
Unknown/Multiple | Blocked By:
Type of failure: | Related Tickets:
None/Unknown |
Test Case: th/T9081 |
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones
participants (1)
-
GHC