[GHC] #11833: GHC can't derive polykinded instance of polykinded typeclass for newtype that requires a class constraint
GHC
ghc-devs at haskell.org
Thu Apr 14 01:24:47 UTC 2016
#11833: GHC can't derive polykinded instance of polykinded typeclass for newtype
that requires a class constraint
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: RyanGlScott
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: #8865
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
GHC chokes when trying to derive the following:
{{{#!hs
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE PolyKinds #-}
module Example where
class Category (cat :: k -> k -> *) where
catId :: cat a a
catComp :: cat b c -> cat a b -> cat a c
newtype T (c :: * -> * -> *) a b = MkT (c a b) deriving Category
}}}
with the following error:
{{{
$ /opt/ghc/8.0.1/bin/ghc Example.hs -fprint-explicit-kinds
[1 of 1] Compiling Example ( Example.hs, Example.o )
Example.hs:9:57: error:
• No instance for (Category * c)
arising from the 'deriving' clause of a data type declaration
Possible fix:
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
• When deriving the instance for (Category * (T c))
}}}
I know what is happening. Unlike in #8865, where we were deriving
`Category` for a concrete type like `Either`, in the above example we are
attempting to derive an instance of the form:
{{{#!hs
instance Category * c => Category (T * c) where ...
}}}
(using `-fprint-explicit-kinds` syntax). But `validDerivPred` is checking
if `sizePred (Category * c)` equals the number of free type variables in
`Category * c`. But note that `sizePred` counts both type variables
//and// type constructors, and `*` is a type constructor! So
`validDerivPred` erroneously rejects the above instance.
To fix this behavior, I think we just need to change `validDerivPred` to
only consider the //visible// arguments of `Category` (i.e., only `c`).
This should be a pretty easy fix - patch incoming.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11833>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list