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

#8953: Reifying poly-kinded type families misses kind annotations ------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.9 Keywords: | Operating System: Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: None/Unknown Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ------------------------------------+------------------------------------- Consider the following two modules: {{{ {-# LANGUAGE DataKinds, PolyKinds, TypeFamilies #-} module A where type family Poly (a :: k) :: * type instance Poly (x :: Bool) = Int type instance Poly (x :: Maybe k) = Double }}} {{{ {-# LANGUAGE TemplateHaskell #-} module B where import Language.Haskell.TH import A $( do info <- reify ''Poly runIO $ putStrLn $ pprint info return [] ) }}} Compiling with HEAD yields this output: {{{ type family A.Poly (a_0 :: k_1) :: * type instance A.Poly x_2 = GHC.Types.Double type instance A.Poly x_3 = GHC.Types.Int }}} The problem is that the type patterns in the reified instances are just plain variables, without their kind annotations. This omission makes the instance declarations unfaithful to the original meaning. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8953 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8953: Reifying poly-kinded type families misses kind annotations -------------------------------------+------------------------------------ Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by goldfire): * owner: => goldfire Comment: Unfortunately, I think the solution is to include kind annotations on ''every'' variable being reified in this context. The problem is that the declarations above do ''not'' come from source Haskell -- the declarations are reconstructed from Core. In Core, every variable has a known kind, so kind annotations do not exist. Although I can imagine some big, complicated inference algorithm that would detect exactly when the annotation is necessary in user code. I don't see a simple way to do this. And, I think the complicated thing has a very wrong power-to-weight ratio. Of course, adding in all the kind annotations is a breaking change that will likely break existing code that reifies type families. Happily, the implementation is easy. If no one objects to this change, I'll put it in in due course. (Not for 7.8!) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8953#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: | -------------------------------------+------------------------------------- Old description:
Consider the following two modules:
{{{ {-# LANGUAGE DataKinds, PolyKinds, TypeFamilies #-}
module A where
type family Poly (a :: k) :: * type instance Poly (x :: Bool) = Int type instance Poly (x :: Maybe k) = Double }}}
{{{ {-# LANGUAGE TemplateHaskell #-}
module B where
import Language.Haskell.TH import A
$( do info <- reify ''Poly runIO $ putStrLn $ pprint info return [] ) }}}
Compiling with HEAD yields this output:
{{{ type family A.Poly (a_0 :: k_1) :: * type instance A.Poly x_2 = GHC.Types.Double type instance A.Poly x_3 = GHC.Types.Int }}}
The problem is that the type patterns in the reified instances are just plain variables, without their kind annotations. This omission makes the instance declarations unfaithful to the original meaning.
New description: Consider the following: {{{ {-# LANGUAGE DataKinds, PolyKinds, TypeFamilies, TemplateHaskell #-} import Language.Haskell.TH type family Poly (a :: k) :: * type instance Poly (x :: Bool) = Int type instance Poly (x :: Maybe k) = Double $( do info <- reify ''Poly runIO $ putStrLn $ pprint info return [] ) }}} Compiling with HEAD yields this output: {{{ type family Main.Poly (a_0 :: k_1) :: * type instance Main.Poly x_2 = GHC.Types.Double type instance Main.Poly x_3 = GHC.Types.Int }}} The problem is that the type patterns in the reified instances are just plain variables, without their kind annotations. This omission makes the instance declarations unfaithful to the original meaning. -- Comment (by goldfire): Only one module is required. Previous bug description had two. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8953#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#8953: Reification drops necessary 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): Still getting worse! Now, look at this: {{{ a :: Proxy (Proxy :: * -> *) a = undefined b :: Proxy (Proxy :: (* -> *) -> *) b = undefined $( do info_a <- reify 'a info_b <- reify 'b runIO $ mapM putStrLn $ map pprint [info_a, info_b] return [] ) }}} produces {{{ Main.a :: Data.Proxy.Proxy Data.Proxy.Proxy Main.b :: Data.Proxy.Proxy Data.Proxy.Proxy }}} Yet, the types of `a` and `b` are ''not'' the same, and assigning one to the other rightly results in a type error. Furthermore, we really need to give the kind of ''every'' type variable binder. Consider {{{ type StarProxy (a :: *) = Proxy a }}} Reifying tyvar binders omits any kinds that are `*`, yet the kind annotation here is very relevant (if `-XPolyKinds` is on). Oh, and the original problem (not reifying kind annotation on type variable patterns) can affect ''class'' instances, too, not just ''type'' instances. So, new plan: 1. Never reify a tyvar binder into a `PlainTV`. Always use `KindedTV`. 2. Include a kind annotation (`SigT`) wrapping every use of a poly-kinded tycon. This wrapping will wrap around any arguments the tycon is applied to. 3. If a class or family tyvar is polykinded, include a kind annotation on any pattern used to specialize this tyvar in instance declarations. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8953#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8953: Reification drops necessary 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): And, while I'm at it, much like in #8884, reified class instances include kind patterns. This needs to be fixed, too. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8953#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8953: Reification drops necessary 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: Phab:D387 | -------------------------------------+------------------------------------- Changes (by goldfire): * differential: => Phab:D387 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8953#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8953: Reification drops necessary 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: Phab:D387 |
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg

#8953: Reification drops necessary 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: Phab:D387 |
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg

#8953: Reification drops necessary 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: Phab:D387 |
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg

#8953: Reification drops necessary 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: Phab:D387 |
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg

#8953: Reification drops necessary 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: Phab:D387 |
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg

#8953: Reification drops necessary 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: Phab:D387 |
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg

#8953: Reification drops necessary kind annotations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: Component: Template | Version: 7.9 Haskell | Keywords: Resolution: fixed | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: th/T8953 | Blocking: | Differential Revisions: Phab:D387 | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * testcase: => th/T8953 * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8953#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8953: Reification drops necessary kind annotations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T8953 Related Tickets: | Blocking: | Differential Revisions: Phab:D387 -------------------------------------+------------------------------------- Changes (by goldfire): * owner: goldfire => * status: closed => new * version: 7.9 => 7.10.1 * resolution: fixed => * milestone: => 7.12.1 Comment: Embarrassingly, this patch misses closed type families. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8953#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8953: Reification drops necessary kind annotations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T8953 Related Tickets: | Blocking: | Differential Revisions: Phab:D387 -------------------------------------+------------------------------------- Changes (by goldfire): * owner: => goldfire -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8953#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8953: Reification drops necessary kind annotations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: th/T8953 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D387 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.2.1 => Comment: This won't be happening for 8.2. If you would like to see this happen please do pick it up! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8953#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8953: Reification drops necessary kind annotations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: th/T8953 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D387, Wiki Page: | Phab:D2795 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: Phab:D387 => Phab:D387, Phab:D2795 * milestone: => 8.2.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8953#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8953: Reification drops necessary kind annotations
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner: goldfire
Type: bug | Status: patch
Priority: normal | Milestone: 8.2.1
Component: Template Haskell | Version: 7.10.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case: th/T8953
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D387,
Wiki Page: | Phab:D2795
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#8953: Reification drops necessary kind annotations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Template Haskell | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: th/T8953 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D387, Wiki Page: | Phab:D2795 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8953#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC