DerivingVia (and perhaps even GND) works badly with DeriveGeneric
DerivingVia
together with DeriveGeneric
can generate wrong instances for Generic
.
Consider the following:
{-# 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
:
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:
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.
Trac metadata
Trac field | Value |
---|---|
Version | |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |