[GHC] #11833: GHC can't derive instance of polykinded typeclass for newtype that requires a class constraint
GHC
ghc-devs at haskell.org
Mon May 2 16:36:15 UTC 2016
#11833: GHC can't derive instance of polykinded typeclass for newtype that requires
a class constraint
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: RyanGlScott
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.0.1
checker) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: #8865, #11837 | Differential Rev(s): Phab:D2112
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott <ryan.gl.scott@…>):
In [changeset:"fa86ac7c14b67f27017d795811265c3a9750024b/ghc"
fa86ac7c/ghc]:
{{{
#!CommitTicketReference repository="ghc"
revision="fa86ac7c14b67f27017d795811265c3a9750024b"
Make validDerivPred ignore non-visible arguments to a class type
constructor
Summary:
GHC choked when trying to derive the following:
```
{-# 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
```
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:
```
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.
The fix is to make `validDerivPred` ignore non-visible arguments to the
class
type constructor (e.g., ignore `*` is `Category * c`) by using
`filterOutInvisibleTypes`.
Fixes #11833.
Test Plan: ./validate
Reviewers: goldfire, hvr, simonpj, austin, bgamari
Reviewed By: bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D2112
GHC Trac Issues: #11833
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11833#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list