
#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