Illegal typeclass instance [GHC-93557]

Using the language version Haskell 2010, only certain types are allowed as instances of a type class. Every type class instance in Haskell 2010 has the following form:

instance C t where

Here, C is the name of a type class, such as Eq, Show, Read or Functor, and t is a type. But only a subset of types t is allowed to appear in typeclass instances. These types must all have the form T or T a ... b, where T has to be the name of a type introduced by a data or newtype declaration, and the arguments a to b all have to be type variables. For example, Maybe a is allowed as a type in an instance, because the data type Maybe instantiates T and a is a type variable, butMaybe Intis not allowed, sinceInt` is not a type variable.

Examples

Cannot implement a typeclass for type synonyms by default

The programmer defined a data type RGB, and a type synonym T, and then tried to implement an instance of the type class Eq for T. In the language version Haskell 2010 this is not allowed, since all type class instances have to start with a type constructor. This problem can be fixed by implementing the typeclass instance directly for the type RGB instead of the type synonym T.

messages/GHC-93557/illegalSynonymInstance/before/IllegalSynonymInstance.hs:8:10: error: [GHC-93557]
    • Illegal instance declaration for ‘Eq T’:
        All instance types must be of the form (T t1 ... tn)
        where T is not a synonym.
    • In the instance declaration for ‘Eq T’
    Suggested fix: Perhaps you intended to use TypeSynonymInstances
  |
8 | instance Eq T where
  |          ^^^^
IllegalSynonymInstance.hs
Before
{-# LANGUAGE Haskell2010 #-}
module IllegalSynonymInstance where

data RGB = R | G | B

type T = RGB

instance Eq T where
    R == R = True
    G == G = True
    B == B = True
    _ == _ = False
After
{-# LANGUAGE Haskell2010 #-}
module IllegalSynonymInstance where

data RGB = R | G | B

instance Eq RGB where
    R == R = True
    G == G = True
    B == B = True
    _ == _ = False