Skip to content

GitLab

  • Projects
  • Groups
  • Snippets
  • Help
    • Loading...
  • Help
    • Help
    • Support
    • Community forum
    • Submit feedback
  • Sign in / Register
GHC
GHC
  • Project overview
    • Project overview
    • Details
    • Activity
    • Releases
  • Repository
    • Repository
    • Files
    • Commits
    • Branches
    • Tags
    • Contributors
    • Graph
    • Compare
    • Locked Files
  • Issues 4,388
    • Issues 4,388
    • List
    • Boards
    • Labels
    • Service Desk
    • Milestones
    • Iterations
  • Merge Requests 374
    • Merge Requests 374
  • Requirements
    • Requirements
    • List
  • CI / CD
    • CI / CD
    • Pipelines
    • Jobs
    • Schedules
    • Test Cases
  • Operations
    • Operations
    • Incidents
    • Environments
  • Analytics
    • Analytics
    • CI / CD
    • Code Review
    • Insights
    • Issue
    • Repository
    • Value Stream
  • Wiki
    • Wiki
  • Snippets
    • Snippets
  • Members
    • Members
  • Activity
  • Graph
  • Create a new issue
  • Jobs
  • Commits
  • Issue Boards
Collapse sidebar
  • Glasgow Haskell Compiler
  • GHCGHC
  • Issues
  • #15434

Closed
Open
Opened Jul 24, 2018 by Hiromi Ishii@konnReporter

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
Assignee
Assign to
9.2.1
Milestone
9.2.1
Assign milestone
Time tracking
None
Due date
None
Reference: ghc/ghc#15434