[GHC] #13065: Prohibit user-defined Generic and Generic1 instances
GHC
ghc-devs at haskell.org
Sun Jan 8 00:06:02 UTC 2017
#13065: Prohibit user-defined Generic and Generic1 instances
-------------------------------------+-------------------------------------
Reporter: dfeuer | Owner:
Type: feature request | Status: new
Priority: normal | Milestone: 8.4.1
Component: Compiler | Version: 8.0.1
Resolution: | Keywords: Generics
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: Other | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by dfeuer):
One place I think we still can't derive (seemingly reasonable) `Generic`
instances is with GADTs. For example, today I can write
{{{#!hs
{-# LANGUAGE DeriveGeneric, StandaloneDeriving, GADTs, DataKinds,
KindSignatures,
FlexibleInstances, TypeFamilies #-}
module GenGADT where
import GHC.Generics
data Foo :: Bool -> * -> * where
X :: a -> Foo 'False a
Y :: a -> Foo 'True a
instance Generic (Foo 'False a) where
type Rep (Foo 'False a) =
D1 ('MetaData "Foo 'False" "GenGADT" "" 'False)
(C1 ('MetaCons "X" 'PrefixI 'False)
(Rec0 a))
to (M1 (M1 (K1 a))) = X a
from (X a) = M1 (M1 (K1 a))
instance Generic (Foo 'True a) where
type Rep (Foo 'True a) =
D1 ('MetaData "Foo 'True" "GenGADT" "" 'False)
(C1 ('MetaCons "Y" 'PrefixI 'False)
(Rec0 a))
to (M1 (M1 (K1 a))) = Y a
from (Y a) = M1 (M1 (K1 a))
}}}
but I don't think GHC is able to derive such instances.
I'm more concerned about backwards compatibility issues, though. As soon
as a library chooses to derive a `Generic` instance for a type, that
instance becomes part of the library API. Users may well come to rely on
the existence of that instance, and also some of its details. If we
prohibit custom instances, won't that strongly discourage libraries from
deriving `Generic` for any but the most trivial exposed types? Let me get
back to pattern synonyms. Suppose we have
{{{#!hs
data Tree a = Tree a [Tree a] deriving Generic
}}}
and we decide we want to play around with bifunctors, so we redefine this
as
{{{#!hs
--newtype Fix p a = In {out :: p (Fix p a) a}
--instance Bifunctor p => Functor (Fix p) where ...
data TreeF t a = TreeF a [t]
instance Bifunctor TreeF where ...
newtype Tree a = Tree (Fix Tree) deriving Functor
-- et cetera
}}}
We can recover most of the original interface using bidirectional pattern
synonyms to work around the newtypes. But if we can't write our own
`Generic` instance, we'll break everything. Existing library users won't
define instances for `TreeF`, so their `Generic`-derived instances for
`Tree` will no longer pass the type checker. Ouch. A recent `containers`
version added `Generic` and `Generic1` for `Data.Tree`; had the
prohibition been under discussion at the time, I'd have thought twice and
thrice about whether that was wise.
I don't think this issue was quite as significant before the rise of
pattern synonyms; in that era, any structural change to an exported
transparent datatype was necessarily a breaking one. With pattern
synonyms, there are more places we ''can'' change representations, and
therefore more reasons to avoid preventing such changes.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13065#comment:6>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list