
#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: | -------------------------------------+------------------------------------- Comment (by mnguyen):
{{{#!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 try this with my current VKA and it fails {{{#!hs T14579a.hs:15:32: error: Not in scope: type variable ‘a’ T14579a.hs:15:51: error: Not in scope: type variable ‘a’ T14579a.hs:16:25: error: Not in scope: type variable ‘a’ T14579a.hs:16:44: error: Not in scope: type variable ‘a’ }}} ??? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14579#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler