[GHC] #10775: Enable PolyKinds in GHC.Generics
GHC
ghc-devs at haskell.org
Sat Aug 15 20:21:59 UTC 2015
#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
More information about the ghc-tickets
mailing list