[GHC] #14579: GeneralizedNewtypeDeriving produces ambiguously-kinded code
GHC
ghc-devs at haskell.org
Wed Oct 17 20:36:45 UTC 2018
#14579: GeneralizedNewtypeDeriving produces ambiguously-kinded code
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.8.1
Component: Compiler (Type | Version: 8.2.2
checker) |
Resolution: | Keywords: deriving
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: GHC rejects | Test Case:
valid program | deriving/should_compile/T14579
Blocked By: 12045 | Blocking:
Related Tickets: | Differential Rev(s): Phab:D4264
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):
* status: closed => new
* resolution: fixed =>
* blockedby: => 12045
* milestone: 8.4.1 => 8.8.1
Comment:
I wonder if the hack we implemented to fix this issue originally could be
made substantially simpler with visible kind applications (which should
[https://phabricator.haskell.org/D5229 be available soon-ish]). With VKAs,
we could instead generate the following code:
{{{#!hs
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeInType #-}
module Bug where
import Data.Kind
import Data.Proxy
newtype Wat (x :: Proxy (a :: Type)) = MkWat (Maybe a)
deriving Eq
newtype Glurp a = MkGlurp (Wat ('Proxy :: Proxy a))
instance Eq a => Eq (Glurp a) where
(==) = coerce @(Wat ('Proxy @a) -> Wat ('Proxy @a) -> Bool)
@(Glurp a -> Glurp a -> Bool)
(==)
}}}
I'll reopen this ticket to keep track of this idea.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14579#comment:12>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list