Type equality not in scope [GHC-12003]

Flag: -Wtype-equality-out-of-scope
Enabled by: -Wcompat

In versions of GHC prior to 9.4.1, the type equality operator ~ was built-in syntax. In more recent versions, it is an ordinary operator that is part of the Prelude and of Data.Type.Equality. Restricting imports from Prelude can result in ~ not being imported, as can the use of a custom prelude that has not been updated to export ~. For now, GHC has a compatibility warning to help migrate old code. In a future version of GHC, this warning will be an error.

Examples

Type equality not imported from Prelude

Warning

TypeEqNotImported.hs:7:9: warning: [-Wtype-equality-out-of-scope] [GHC-12003]
    • The ‘~’ operator is out of scope.
      Assuming it to stand for an equality constraint.
    • NB: ‘~’ used to be built-in syntax but now is a regular type operator
          exported from Data.Type.Equality and Prelude.
      If you are using a custom Prelude, consider re-exporting it.
    • This will become an error in a future GHC release.
  |
7 | f :: (a ~ b) => a -> b
  |         ^

Explanation

In this example, the type equality operator was not imported from the Prelude. To remove the warning, it must be imported.

TypeEqNotImported.hs
Before

{-# OPTIONS -Wcompat #-}
module TypeEqNotImported where

import Prelude (id)

f :: (a ~ b) => a -> b
f = id
After
{-# LANGUAGE ExplicitNamespaces #-}
{-# OPTIONS -Wcompat #-}
module TypeEqNotImported where

import Prelude (id, type (~))

f :: (a ~ b) => a -> b
f = id