[GHC] #13885: Template Haskell doesn't freshen GADT kind variables properly when imported from another package

#13885: Template Haskell doesn't freshen GADT kind variables properly when imported from another package -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.0.1 Haskell | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect result Unknown/Multiple | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- A simple way to illustrate this bug is with this code: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeOperators #-} module Foo where import qualified Data.Type.Equality as DTE ((:~:)) import Language.Haskell.TH data a :~: b where Refl :: a :~: a $(return []) main :: IO () main = do putStrLn "Imported\n-----" putStrLn $(reify ''(DTE.:~:) >>= stringE . pprint) putStrLn "-----\n\nLocally defined\n-----" putStrLn $(reify ''(:~:) >>= stringE . pprint) putStrLn "-----" }}} Here, I'm pretty-printing the reified Template Haskell information about two datatypes: one that is imported from another package (`base`), and another that is defined locally. Aside from their definition sites, they are otherwise identical. However, when reifying them with Template Haskell, there is another distinction one can observe: {{{ $ /opt/ghc/8.2.1/bin/runghc Foo.hs Imported ----- data Data.Type.Equality.:~: (a_0 :: k_1) (b_2 :: k_1) where Data.Type.Equality.Refl :: forall (k_1 :: *) (a_0 :: k_1) . Data.Type.Equality.:~: a_0 a_0 ----- Locally defined ----- data Foo.:~: (a_0 :: k_1) (b_2 :: k_1) where Foo.Refl :: forall (k_3 :: *) (a_4 :: k_3) . Foo.:~: a_4 a_4 ----- }}} The locally defined information looks fine, but the one imported from `base` is suspicious. Namely, the `k_1` variable is used both in the datatype head and in the quantified variables for the constructor! To confirm this, you can print out more verbose info with `show` instead of `pprint`: {{{ Imported ----- TyConI (DataD [] Data.Type.Equality.:~: [KindedTV a_6989586621679026781 (VarT k_6989586621679026780),KindedTV b_6989586621679026782 (VarT k_6989586621679026780)] Nothing [ForallC [KindedTV k_6989586621679026780 StarT,KindedTV a_6989586621679026781 (VarT k_6989586621679026780)] [] (GadtC [Data.Type.Equality.Refl] [] (AppT (AppT (ConT Data.Type.Equality.:~:) (VarT a_6989586621679026781)) (VarT a_6989586621679026781)))] []) ----- Locally defined ----- TyConI (DataD [] Foo.:~: [KindedTV a_6989586621679016094 (VarT k_6989586621679016098),KindedTV b_6989586621679016095 (VarT k_6989586621679016098)] Nothing [ForallC [KindedTV k_6989586621679016108 StarT,KindedTV a_6989586621679016096 (VarT k_6989586621679016108)] [] (GadtC [Foo.Refl] [] (AppT (AppT (ConT Foo.:~:) (VarT a_6989586621679016096)) (VarT a_6989586621679016096)))] []) ----- }}} Sure enough, the variable `k_6989586621679026780` is used in both places. I would expect this not to happen, since the two sets of variables are scoped differently, and in practice, I have to work around this by freshening the type variables for the constructor, which is annoying. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13885 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13885: Template Haskell doesn't freshen GADT type variables properly -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Actually, it's not just kind variables, and you don't need to necessarily import them from another package. Another way to trigger this problem is to use `ExistentialQuantification` instead of `GADTs`: {{{#!hs {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} module Foo where import Language.Haskell.TH data a :~: b = a ~ b => Refl $(return []) main :: IO () main = putStrLn $(reify ''(:~:) >>= stringE . pprint) }}} {{{ $ /opt/ghc/8.2.1/bin/runghc Foo.hs data Foo.:~: (a_0 :: k_1) (b_2 :: k_1) where Foo.Refl :: forall (k_1 :: *) (a_0 :: k_1) (b_2 :: k_1) . Data.Type.Equality.~ a_0 b_2 => Foo.:~: a_0 b_2 }}} Now we are shadowing both the type variables `a_0` and `b_2`, as well as the kind variable `k_1`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13885#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13885: Template Haskell doesn't freshen GADT type variables properly -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Why does this matter? If I write {{{ data T a b where MkT :: [a] -> b -> x -> T x a }}} that's absolutely fine. The 'a' and 'b' in the `MkT` signature have nothing to do with the variables in the head. The latter do not scope over the constructors. Right? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13885#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13885: Template Haskell doesn't freshen GADT type variables properly -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Sure, I know that //conceptually//, they have different scopes. I would just find it convenient to have different uniques for differently scoped variables in the reified Template Haskell output, as it would greatly simplify some code that I'm developing that benefits from the assumption that TH ASTs are fully uniquified. It's a minor thing, but it would be a definite quality-of-life improvement. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13885#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13885: Template Haskell doesn't freshen GADT type variables properly -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): OK fine -- if someone wants to make this so it'd be fine by me. But please comment the code so we know it's for convenience for clients rather than correctness. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13885#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13885: Template Haskell doesn't freshen GADT type variables properly -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3867 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D3867 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13885#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13885: Template Haskell doesn't freshen GADT type variables properly
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Template Haskell | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect result | Unknown/Multiple
at runtime | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3867
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#13885: Template Haskell doesn't freshen GADT type variables properly -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Template Haskell | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: th/T13885 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3867 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * testcase: => th/T13885 * resolution: => fixed * milestone: => 8.4.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13885#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13885: Template Haskell doesn't freshen GADT type variables properly -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: th/T13885 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3867 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: closed => new * resolution: fixed => Comment: As I discovered in https://phabricator.haskell.org/D3867#108979, there's some cases that Phab:D3867 missed. Reopening. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13885#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13885: Template Haskell doesn't freshen GADT type variables properly -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Template Haskell | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: th/T13885 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3867 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => fixed Comment: Sorry, I think I was confused (see my comment in https://phabricator.haskell.org/D3867#108984 which clarifies my confusion). There's no bug remaining here, except for insufficient documentation (which I'll address separately). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13885#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13885: Template Haskell doesn't freshen GADT type variables properly
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: closed
Priority: normal | Milestone: 8.4.1
Component: Template Haskell | Version: 8.0.1
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect result | Unknown/Multiple
at runtime | Test Case: th/T13885
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3867
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott
participants (1)
-
GHC