[GHC] #10775: Enable PolyKinds in GHC.Generics

#10775: Enable PolyKinds in GHC.Generics -------------------------------------+------------------------------------- Reporter: | Owner: RyanGlScott | Type: feature | Status: new request | Priority: normal | Milestone: Component: | Version: 7.10.2 libraries/base | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- As suggested in [https://mail.haskell.org/pipermail/libraries/2015-July/025981.html this] Haskell libraries mailing list thread. Among other benefits, this would allow use of generic functions with `Proxy t` when `t` is of a kind other than `*`. There seem to be more changes required than just putting `{-# LANGUAGE PolyKinds #-}` in `GHC.Generics`, however, since I tried doing that myself and found myself unable to properly derive `Generic(1)` instances in `GHC.Generics`. Here is a snippet of the resulting error message: {{{ libraries/base/GHC/Generics.hs:826:1: error: Couldn't match type ‘M1 i0 c0 (M1 i1 c1 U1) p0’ with ‘M1 D x’ Expected type: Rep (Proxy t) x Actual type: M1 i0 c0 (M1 i1 c1 U1) p0 Relevant bindings include from :: Proxy t -> Rep (Proxy t) x (bound at libraries/base/GHC/Generics.hs:826:1) In the expression: M1 (M1 U1) In an equation for ‘from’: from Proxy = M1 (M1 U1) When typechecking the code for ‘from’ in a derived instance for ‘Generic (Proxy t)’: To see the code I am typechecking, use -ddump-deriv libraries/base/GHC/Generics.hs:826:1: error: Couldn't match type ‘M1 t0 t1 (M1 t3 t4 U1) t2’ with ‘M1 D x’ Expected type: Rep (Proxy t) x Actual type: M1 t0 t1 (M1 t3 t4 U1) t2 Relevant bindings include to :: Rep (Proxy t) x -> Proxy t (bound at libraries/base/GHC/Generics.hs:826:1) In the pattern: M1 (M1 U1) In an equation for ‘to’: to (M1 (M1 U1)) = Proxy When typechecking the code for ‘to’ in a derived instance for ‘Generic (Proxy t)’: To see the code I am typechecking, use -ddump-deriv In the instance declaration for ‘Generic (Proxy t)’ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10775 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10775: Enable PolyKinds in GHC.Generics -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by dreixel): I'm not entirely sure what's the goal here. To make `Generic1 :: k -> *` instead of its current `Generic1 :: * -> *` kind? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10775#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10775: Enable PolyKinds in GHC.Generics -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by RyanGlScott):
To make `Generic1 :: k -> *` instead of its current `Generic1 :: * -> *` kind?
No, my main motivation involves `Proxy` from `Data.Proxy`. Currently, `Proxy` is defined like so: {{{#!hs data Proxy (t :: k) = Proxy }}} using `PolyKinds`, but `Proxy` has a `Generic` instance defined in `GHC.Generics`, a module which doesn't have `PolyKinds` enabled. As a result, the resulting `Generic` instance is {{{#!hs instance Generic (Proxy (t :: *)) }}} This prevents you from using certain `Proxy` values with generic functions: {{{ $ ghci -XPolyKinds GHCi, version 7.10.2: http://www.haskell.org/ghc/ :? for help λ> import GHC.Generics λ> import Data.Proxy λ> from (Proxy :: Proxy Int) M1 {unM1 = M1 {unM1 = U1}} λ> from (Proxy :: Proxy Maybe) <interactive>:5:1: No instance for (Generic (Proxy Maybe)) (maybe you haven't applied enough arguments to a function?) arising from a use of ‘from’ In the expression: from (Proxy :: Proxy Maybe) In an equation for ‘it’: it = from (Proxy :: Proxy Maybe) }}} If `GHC.Generics` enabled `PolyKinds`, that would fix this issue. It would also make many data types in `GHC.Generics` poly-kinded as well, as an added bonus. (I had originally thought `Generic1`/`Rep1` could be poly-kinded, but upon further thought, I think the current GHC generics mechanism assumes that the last type parameter is always of kind `* -> *`.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10775#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10775: Enable PolyKinds in GHC.Generics -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Do you happen to have the output from `-ddump-deriv` available? I'm having a bit of difficulty seeing why this should just work (although I may be missing something obvious). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10775#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10775: Enable PolyKinds in GHC.Generics -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by dreixel): I think what you're after is a very small subset of the changes to GHC.Generics.hs here: https://phabricator.haskell.org/D493?vs=on&id=1690&whitespace=ignore- most#15796e19 Probably just adding the `:: *` kind signatures in the definitions of the representation types, I think. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10775#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10775: Enable PolyKinds in GHC.Generics -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by RyanGlScott): bgamari: The output of `-ddump-deriv` is extremely long, but here are the parts pertaining to `Proxy`: {{{ ==================== Derived instances ==================== Derived instances: instance forall (k_a21F :: BOX) (t_a21G :: k_a21F). GHC.Generics.Generic (Data.Proxy.Proxy t_a21G) where GHC.Generics.from Data.Proxy.Proxy = GHC.Generics.M1 (GHC.Generics.M1 GHC.Generics.U1) GHC.Generics.to (GHC.Generics.M1 (GHC.Generics.M1 GHC.Generics.U1)) = Data.Proxy.Proxy instance GHC.Generics.Datatype where GHC.Generics.datatypeName _ = "Proxy" GHC.Generics.moduleName _ = "Data.Proxy" GHC.Generics.packageName _ = "base" instance GHC.Generics.Constructor where GHC.Generics.conName _ = "Proxy" Generic representation: Generated datatypes for meta-information: GHC.Generics.D1Proxy GHC.Generics.C1_0Proxy Representation types: type GHC.Generics.Rep (Data.Proxy.Proxy t_a21E) = GHC.Generics.D1 }}} That definitely doesn't look right, especially since it should be that `Rep (Proxy t) = D1 D1Proxy (C1 C1_0Proxy U1)`. Luckily, this may be a moot issue. I wasn't aware of Phab:D493, which happens to enable `PolyKinds` in `GHC.Generics` as a happy coincidence. Therefore, this is probably a duplicate of #9766. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10775#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10775: Enable PolyKinds in GHC.Generics -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 9766 | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by RyanGlScott): * blockedby: => 9766 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10775#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10775: Enable PolyKinds in GHC.Generics -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by dreixel): * blockedby: 9766 => Comment: This doesn't need to depend on #9766. This is a small change that can be done on its own. Go for it, I'd say :-) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10775#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10775: Enable PolyKinds in GHC.Generics -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: | RyanGlScott Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1166 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * owner: => RyanGlScott * differential: => Phab:D1166 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10775#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10775: Enable PolyKinds in GHC.Generics
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
| RyanGlScott
Type: feature request | Status: new
Priority: normal | Milestone:
Component: libraries/base | Version: 7.10.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions: Phab:D1166
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#10775: Enable PolyKinds in GHC.Generics -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: | RyanGlScott Type: feature request | Status: closed Priority: normal | Milestone: Component: libraries/base | Version: 7.10.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1166 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: Merged. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10775#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10775: Enable PolyKinds in GHC.Generics -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: feature request | Status: closed Priority: normal | Milestone: 8.0.1 Component: libraries/base | Version: 7.10.2 Resolution: fixed | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1166 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => Generics -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10775#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10775: Enable PolyKinds in GHC.Generics -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: feature request | Status: closed Priority: normal | Milestone: 8.0.1 Component: libraries/base | Version: 7.10.2 Resolution: fixed | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10604 | Differential Rev(s): Phab:D1166 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #10604 Comment: See also #10604, which concerns making the definition of `Generic1` itself leverage `PolyKinds`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10775#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC