[GHC] #14661: Cannot derive (newtype I a b = I (F a -> F b) deriving newtype Category) for type family F
GHC
ghc-devs at haskell.org
Thu Jan 11 19:17:00 UTC 2018
#14661: Cannot derive (newtype I a b = I (F a -> F b) deriving newtype Category)
for type family F
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.4.1-alpha1
Resolution: | Keywords:
| DerivingStrategies, deriving,
| TypeFamilies
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
Replying to [comment:1 simonpj]:
> Same thing happens with `data Interp a = I`.
Well sure—you can't use `GeneralizedNewtypeDeriving` on a non-newtype.
I agree that the type family is a red herring, though. Let's look at a
slightly simpler example:
{{{#!hs
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
import Control.Category
data Bar a
newtype Foo a b = MkFoo (Bar a -> Bar b)
deriving newtype Category
}}}
{{{
• Can't make a derived instance of
‘Category Foo’ with the newtype strategy:
cannot eta-reduce the representation type enough
• In the newtype declaration for ‘Foo’
|
9 | deriving newtype Category
| ^^^^^^^^
}}}
Why is this happening? As per the
[https://downloads.haskell.org/~ghc/8.2.2/docs/html/users_guide/glasgow_exts.html?highlight=generalizednewtypederiving#a
-more-precise-specification specification] of `GeneralizedNewtypeDeriving`
in the users' guide, GHC must be able to eta-convert `Foo`'s underlying
representation type (i.e., `Bar a -> Bar b`) in order to generate a
context. But you cannot eta-reduce the type variables `a` and `b` from
`Bar a -> Bar b`, try as you might.
-----
Returning to your original example, you claim that the instance you hand-
wrote "consists entirely of the right visible type application of `method:
method = coerce (method @a @b @..)`", but this isn't true. Look at your
`id` implementation, for instance:
{{{#!hs
id :: forall a. Ixed a a
id = coerce (id @(->) @(Interp a))
}}}
This is a good deal more clever than what `GeneralizedNewtypeDeriving`
currently does. GND would try to coerce from `id :: forall a. Ixed a a` to
`id :: forall a. ??? a a`, where `???` is the eta-reduced representation
type (that we were unable to obtain, as explained previously). But your
implementation tunnels down through `(->)` and exploits the fact that
`Interp` happens to be present on both sides of the arrow.
This insider knowledge would not be particularly simple to teach GHC—for
instance, what happens if you chance `Ixed` to be of type `(Interp ix ->
Maybe (Interp ix') -> (Ixed ix ix')`? Moreover, the kinds of tricks that
would work for `Category`/`(->)` would likely not be applicable for other
type class/type constructor combinations.
'''tl;dr''' I claim this is not a bug, but rather a misunderstanding of
how `GeneralizedNewtypeDeriving` works.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14661#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list