Class kind signatures need to be constraints [GHC-80768]

Similarly to how type families are not allowed in data type return kinds, type families are not allowed in class return kinds. Usually, GHC compares types and kinds up to type family reductions, but not in these two cases.

Examples

Kind signatures on classes must end with Constraint unobscured by type families

The problem here is the usage of the type family Id in the standalone kind signature for the typeclass C. Kind signatures for classes must literally end in Constraint rather than in a kind that is equivalent to it.

Error Message

ClassKindNotConstraint.hs:14:1: error: [GHC-80768]
    • Kind signature on a class must end with Constraint
      unobscured by type families
    • In the class declaration for ‘C’
   |
14 | class C a
   | ^^^^^^^^^
ClassKindNotConstraint.hs
Before
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE TypeFamilies #-}

module ClassKindNotConstraint where

import Data.Kind

type family Id (x :: Type) :: Type where
  Id x = x

type C :: Type -> Id Constraint
class C a
After
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE StandaloneKindSignatures #-}

module ClassKindNotConstraint where

import Data.Kind

type C :: Type -> Constraint
class C a