[GHC] #15434: DerivingVia (and perhaps even GND) works badly with DeriveGeneric

#15434: DerivingVia (and perhaps even GND) works badly with DeriveGeneric -------------------------------------+------------------------------------- Reporter: konn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- `DerivingVia` together with `DeriveGeneric` can generate wrong instances for `Generic`. Consider the following: {{{#!haskell {-# LANGUAGE DeriveGeneric, DerivingStrategies, DerivingVia, GADTs #-} {-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies, UndecidableInstances #-} module Data.Foldable.Bad where import GHC.Generics newtype Bad a = Bad a deriving (Generic) data Foo = Foo Int deriving (Read, Show, Eq, Ord) deriving (Generic) via Bad Foo }}} which gives the following representation, which is considered to be wrong for `Foo`: {{{#!haskell ghci> from $ Foo 12 M1 {unM1 = M1 {unM1 = M1 {unM1 = K1 {unK1 = Foo 12}}}} ghci> :t it it :: D1 ('MetaData "Bad" "Data.Foldable.Bad" "main" 'True) (C1 ('MetaCons "Bad" 'PrefixI 'False) (S1 ('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Foo))) x }}} Also, `DerivingStrategies` + GND + `DeriveGeneric` already can generate wrong instance: {{{#!haskell newtype Bad2 = Bad2 Bool deriving newtype (Generic) {- ghci> from $ Bad2 False M1 {unM1 = L1 (M1 {unM1 = U1})} ghci> :t it it :: D1 ('MetaData "Bool" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "False" 'PrefixI 'False) U1 :+: C1 ('MetaCons "True" 'PrefixI 'False) U1) x -} }}} I tested this against GHC 8.6.1-alpha1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15434 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15434: DerivingVia (and perhaps even GND) works badly with DeriveGeneric -------------------------------------+------------------------------------- Reporter: konn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => deriving Comment: I'm not sure what the bug is here. You're explicitly requesting that you reuse the `Generic` instance for `Bad Foo`, and lo and behold, GHC gives you it. If you don't like this behavior, don't combine `DerivingVia` with `Generic`—the former wasn't meant to be combined with the latter (indeed, this code will give an error if combined with the `Safe` extension). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15434#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15434: DerivingVia (and perhaps even GND) works badly with DeriveGeneric -------------------------------------+------------------------------------- Reporter: konn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: Resolution: | Keywords: deriving 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 konn):
You're explicitly requesting that you reuse the Generic instance for Bad Foo, and lo and behold, GHC gives you it. I can't imagine the situation where `Generic` should give the different information than its true structure.
Although the code above is simple enough, I think it might be error-prone to allow writing Generic in DerivingVia-clause. As for GND, deriving strategy `newtype` is used as a prefix for the deriving clause, so one can easily notice the mistake; but as for DerivingVia, since `via`-clause is placed after constraints, one can easily overlook that the current deriving strategy.
this code will give an error if combined with the Safe extension
Hence, I think this behaviour should be enabled by default, even without `Safe` extension. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15434#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15434: DerivingVia (and perhaps even GND) works badly with DeriveGeneric -------------------------------------+------------------------------------- Reporter: konn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: dfeuer (added) Comment: As a counterpoint, I quite dislike the idea of GHC demanding that users write instances a certain way. In fact, one of the very reasons I authored `DerivingStrategies` in the first place was because one couldn't derive classes like `Read` or `Show` by any means except `stock` deriving. True, 90% of the time, this is what you want, but for the other 10%, having explicit control through `DerivingStrategies` is quite handy. Replying to [comment:2 konn]:
I can't imagine the situation where `Generic` should give the different information than its true structure.
There are folks out there who write `Generic` instances which differ from what `stock` deriving would give you for various reasons. One reason is that some people like to define data types abstractly and only allow creating/matching on values of that data type through pattern synonyms. While I don't have any examples of people `newtype`/`via`-deriving `Generic` instances on hand, it's not inconceivable that folks might want to do this.
Hence, I think this behaviour should be enabled by default, even without `Safe` extension.
I [https://ghc.haskell.org/trac/ghc/ticket/13065 used to share this opinion], but I no longer do. I don't think GHC (or `Safe`) should be in the business of enforcing the structure of `Generic` instances. You'll never segfault from using a hand-written `Generic` instance (unlike, say, `Typeable`). I think what you want is for GHC to be able to verify that a particular `Generic` instance's structure actually matches the data type it was derived for. This is a reasonable desire, since there are certain properties about data types that can easily be discerned from a `Rep` instance, but only if you have confidence that the `Rep` instance isn't "lying". dfeuer (cc'd) has toyed with some ideas for how this could be achieved in GHC—perhaps he could chime in here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15434#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15434: DerivingVia (and perhaps even GND) works badly with DeriveGeneric -------------------------------------+------------------------------------- Reporter: konn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: Resolution: | Keywords: deriving 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 konn): Replying to [comment:3 RyanGlScott]:
True, 90% of the time, this is what you want, but for the other 10%, having explicit control through `DerivingStrategies` is quite handy.
I agree. In general, it is desirable to have the flexibility on the choice of a deriving strategy.
There are folks out there who write `Generic` instances which differ from what `stock` deriving would give you for various reasons. One reason is that some people like to define data types abstractly and only allow creating/matching on values of that data type through pattern synonyms.
I think what you want is for GHC to be able to verify that a particular `Generic` instance's structure actually matches the data type it was derived for. This is a reasonable desire, since there are certain
I've just taken a simple survey searching `instance Generic` in codes on GitHub and count how many custom instances for `Generic` are defined, using [https://github.com/konn/crawl-github this code]. It reported that there are 2 out of 892 modules with custom `Generic` instance and have 12 custom instances as a total; it turns out that `Generic` instances in one of the modules are not related to GHC's Generics. One instance is something like mapping the Rep of `Map k v` to that of `[(k, v)]`. Since there are some modules that cannot be parsed by `haskell-src-exts` and not counted in my survey, there might be more custom instances. Anyway, there is at least one use-case and there might be other custom instances doing the similar things. properties about data types that can easily be discerned from a `Rep` instance, but only if you have confidence that the `Rep` instance isn't "lying". dfeuer (cc'd) has toyed with some ideas for how this could be achieved in GHC—perhaps he could chime in here. I find this option is reasonable. If GHC can warn that one can avoid unintended derived instance, and if one really wants to write custom instance, then one can turn off that warning. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15434#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC