User-specified instance is not allowed [GHC-97044]

There are several special type classes in base which require special treatment from the compiler. For this reason they don’t permit user-specified instances.

An attempt to provide an explicit instance declaration in your library / application code, e.g.

instance Coercible A B where ...

will lead to this error being reported.

The instances for these type classes are automatically created by GHC on an as-needed basis.

This restriction applies to the following type classes:

Examples

Attempts to create hand-written instances for special type classes

Since these type classes don’t allow hand-written instances, you’ll get the following errors if you try to implement them. To fix the errors, just remove the instance declarations - GHC will provide them for you automatically.

Error Message

UserSpecifiedInstances.hs:9:10: error: [GHC-97044]
    • Class ‘Coercible’ does not support user-specified instances.
    • In the instance declaration for ‘Coercible Foo ()’
  |
9 | instance Coercible Foo ()
  |          ^^^^^^^^^^^^^^^^

UserSpecifiedInstances.hs:11:10: error: [GHC-97044]
    • Class ‘Typeable’ does not support user-specified instances.
    • In the instance declaration for ‘Typeable Foo’
   |
11 | instance Typeable Foo
   |          ^^^^^^^^^^^^

UserSpecifiedInstances.hs:13:10: error: [GHC-97044]
    • Class ‘~’ does not support user-specified instances.
    • In the instance declaration for ‘Foo ~ Foo’
   |
13 | instance Foo ~ Foo
   |          ^^^^^^^^^
UserSpecifiedInstances.hs
Before
module Main where

import Data.Coerce (Coercible, coerce)
import Type.Reflection (Typeable(..))
import Data.Type.Equality

newtype Foo = Foo { unFoo :: () }

instance Coercible Foo ()

instance Typeable Foo

instance Foo ~ Foo

main :: IO ()
main = do
    let foo = Foo ()
    print (coerce foo:: ())
    print (typeOf foo)
    print (Refl :: Foo :~: Foo)
After
module Main where

import Data.Coerce
import Data.Type.Equality
import Type.Reflection

newtype Foo = Foo { unFoo :: () }

main :: IO ()
main = do
    let foo = Foo ()
    print (coerce foo:: ())
    print (typeOf foo)
    print (Refl :: Foo :~: Foo)