[GHC] #13813: DeriveFunctor spuriously rejects existential context with type synonym mentioning the last type variable
GHC
ghc-devs at haskell.org
Sat Jun 10 22:21:30 UTC 2017
#13813: DeriveFunctor spuriously rejects existential context with type synonym
mentioning the last type variable
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
(Type checker) |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: GHC rejects
Unknown/Multiple | valid program
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
This code does not compile:
{{{#!hs
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE StandaloneDeriving #-}
module Bug where
import GHC.Exts (Constraint)
type C (a :: Constraint) b = a
data T a b = C (Show a) b => MkT b
deriving instance Functor (T a)
}}}
{{{
GHCi, version 8.2.0.20170523: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug ( Bug.hs, interpreted )
Bug.hs:13:1: error:
• Can't make a derived instance of ‘Functor (T a)’:
Constructor ‘MkT’ must be truly polymorphic in the last argument
of the data type
• In the stand-alone deriving instance for ‘Functor (T a)’
|
13 | deriving instance Functor (T a)
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
}}}
But it should, since if you expand `C (Show a) b`, you're left with `Show
a`, which doesn't mention the last type variable `b` at all.
Fix incoming.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13813>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list