Skip to content

compiler: missing-deriving-strategies suggested fix

For #24955 (closed)

  • shouldn't break existing programs
  • commits are buildable
  • commit messages describe what they do
  • source comments
  • updated/added tests
  • updates the users guide if applicable

Given the following source:

{-# OPTIONS_GHC -Werror=missing-deriving-strategies #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE DeriveAnyClass #-}
module Example where

class C a b | b -> a
instance C Int Int

newtype N = N Int
  deriving (Show, Eq, Read, Ord)
  deriving (C Int)

data I e = I e
deriving instance Show e => Show (I e)

We would previously see:

Example.hs:12:3: error: [GHC-55631] [-Wmissing-deriving-strategies, Werror=missing-deriving-strategies]
    No deriving strategy specified. Did you want stock, newtype, or anyclass?
   |
12 |   deriving (Show, Eq, Read, Ord)
   |   ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

Example.hs:13:3: error: [GHC-55631] [-Wmissing-deriving-strategies, Werror=missing-deriving-strategies]
    No deriving strategy specified. Did you want stock, newtype, or anyclass?
   |
13 |   deriving (C Int)
   |   ^^^^^^^^^^^^^^^^

Example.hs:16:19: error: [GHC-55631] [-Wmissing-deriving-strategies, Werror=missing-deriving-strategies]
    No deriving strategy specified. Did you want stock, newtype, or anyclass?
   |
16 | deriving instance Show e => Show (I e)
   |                   ^^^^^^^^^^^^^^^^^^^^

We would now see:

Example.hs:12:12: error: [GHC-55631] [-Wmissing-deriving-strategies, Werror=missing-deriving-strategies]
    • No deriving strategy specified. Did you want stock, newtype, or anyclass?
    • In the newtype declaration for ‘N’
    Suggested fix:
      Use explicit deriving strategies:
        deriving stock (Show, Read)
        deriving newtype (Eq, Ord)
   |
12 |   deriving (Show, Eq, Read, Ord)
   |            ^^^^^^^^^^^^^^^^^^^^^

Example.hs:13:12: error: [GHC-55631] [-Wmissing-deriving-strategies, Werror=missing-deriving-strategies]
    • No deriving strategy specified. Did you want stock, newtype, or anyclass?
    • In the newtype declaration for ‘N’
    Suggested fix:
      Use explicit deriving strategies: deriving anyclass (C Int)
   |
13 |   deriving (C Int)
   |            ^^^^^^^

Example.hs:16:1: error: [GHC-55631] [-Wmissing-deriving-strategies, Werror=missing-deriving-strategies]
    • No deriving strategy specified. Did you want stock, newtype, or anyclass?
    • In the stand-alone deriving instance for ‘Show e => Show (I e)
    Suggested fix:
      Use explicit deriving strategies:
        deriving stock instance Show e => Show (I e)
   |
16 | deriving instance Show e => Show (I e)
   | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

Let me know if you actually want this / any changes. Thanks!

Edited by Liam Goodacre

Merge request reports