Cannot derive instance without constructors in scope [GHC-54540]

Deriving an instance of a typeclass for a type is only possible if the constructors of the type are in scope at the point where you want to derive the instance.

Examples

Cannot derive an instance for an abstract type

The Handle type is abstract and does not export its constructors. It is therefore not possible to derive an instance of a typeclass for the Handle type in another module. You can only derive an instance of a typeclass in the module where Handle is defined.

`messages/GHC-54540/constructorsNotInScope/before/ConstructorsNotInScope.hs:6:1: error: [GHC-54540] • Can't make a derived instance of ‘Eq Handle’: The data constructors of ‘Handle’ are not all in scope so you cannot derive an instance for it • In the stand-alone deriving instance for ‘Eq Handle’ | 6 | deriving instance Eq Handle | ^^^^^^^^^^^^^^^^^^^^^^^^^^^

ConstructorsNotInScope.hs
Before
{-# LANGUAGE StandaloneDeriving #-}
module ConstructorsNotInScope where

import System.IO( Handle )

deriving instance Eq Handle
After
{-# LANGUAGE StandaloneDeriving #-}
module ConstructorsNotInScope where

import System.IO( Handle )

-- It is not possible to derive an instance for the type class in this module.