diff --git a/compiler/GHC/Builtin/Names.hs b/compiler/GHC/Builtin/Names.hs
index b7f54060b9ef45cd1aa6d4a035cb789c84ae2fe8..364d7a913d8d01c959393b8c1d82e4908b09ae17 100644
--- a/compiler/GHC/Builtin/Names.hs
+++ b/compiler/GHC/Builtin/Names.hs
@@ -2794,17 +2794,41 @@ interactiveClassKeys = map getUnique interactiveClassNames
 *                                                                      *
 ************************************************************************
 
-GHCi's :info command will usually filter out instances mentioning types whose
-names are not in scope. GHCi makes an exception for some commonly used names,
-such as Data.Kind.Type, which may not actually be in scope but should be
-treated as though they were in scope. The list in the definition of
-pretendNameIsInScope below contains these commonly used names.
+Note [pretendNameIsInScope]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~
+In general, we filter out instances that mention types whose names are
+not in scope. However, in the situations listed below, we make an exception
+for some commonly used names, such as Data.Kind.Type, which may not actually
+be in scope but should be treated as though they were in scope.
+This includes built-in names, as well as a few extra names such as
+'Type', 'TYPE', 'BoxedRep', etc.
 
+Situations in which we apply this special logic:
+
+  - GHCi's :info command, see GHC.Runtime.Eval.getInfo.
+    This fixes #1581.
+
+  - When reporting instance overlap errors. Not doing so could mean
+    that we would omit instances for typeclasses like
+
+      type Cls :: k -> Constraint
+      class Cls a
+
+    because BoxedRep/Lifted were not in scope.
+    See GHC.Tc.Errors.pprPotentials.
+    This fixes one of the issues reported in #20465.
 -}
 
+-- | Should this name be considered in-scope, even though it technically isn't?
+--
+-- This ensures that we don't filter out information because, e.g.,
+-- Data.Kind.Type isn't imported.
+--
+-- See Note [pretendNameIsInScope].
 pretendNameIsInScope :: Name -> Bool
 pretendNameIsInScope n
-  = any (n `hasKey`)
+  = isBuiltInSyntax n
+  || any (n `hasKey`)
     [ liftedTypeKindTyConKey, unliftedTypeKindTyConKey
     , liftedDataConKey, unliftedDataConKey
     , tYPETyConKey
diff --git a/compiler/GHC/Runtime/Eval.hs b/compiler/GHC/Runtime/Eval.hs
index e28b2daebae6f86f5684bc86b2d898dc1f67cc1d..bceb9a415903ed2f734ea4fb00f0918d7a72dc30 100644
--- a/compiler/GHC/Runtime/Eval.hs
+++ b/compiler/GHC/Runtime/Eval.hs
@@ -81,7 +81,6 @@ import GHC.Tc.Types.Constraint
 import GHC.Tc.Types.Origin
 
 import GHC.Builtin.Names ( toDynName, pretendNameIsInScope )
-import GHC.Builtin.Types ( isCTupleTyConName )
 
 import GHC.Data.Maybe
 import GHC.Data.FastString
@@ -873,8 +872,7 @@ getInfo allInfo name
           ok n | n == name              = True
                        -- The one we looked for in the first place!
                | pretendNameIsInScope n = True
-               | isBuiltInSyntax n      = True
-               | isCTupleTyConName n    = True
+                   -- See Note [pretendNameIsInScope] in GHC.Builtin.Names
                | isExternalName n       = isJust (lookupGRE_Name rdr_env n)
                | otherwise              = True
 
diff --git a/compiler/GHC/Tc/Errors.hs b/compiler/GHC/Tc/Errors.hs
index 51ab0fca2a13c14f3b7d5814f5977d5bd7a431b9..e420bd1c23899074bdff1124d432fb9c34c4d937 100644
--- a/compiler/GHC/Tc/Errors.hs
+++ b/compiler/GHC/Tc/Errors.hs
@@ -50,7 +50,7 @@ import GHC.Types.Error
 import GHC.Rename.Unbound ( unknownNameSuggestions, WhatLooking(..) )
 import GHC.Unit.Module
 import GHC.Hs.Binds ( PatSynBind(..) )
-import GHC.Builtin.Names ( typeableClassName )
+import GHC.Builtin.Names ( typeableClassName, pretendNameIsInScope )
 import qualified GHC.LanguageExtensions as LangExt
 
 import GHC.Core.Predicate
@@ -58,7 +58,7 @@ import GHC.Core.Type
 import GHC.Core.Coercion
 import GHC.Core.TyCo.Rep
 import GHC.Core.TyCo.Ppr  ( pprTyVars, pprWithExplicitKindsWhen, pprSourceTyCon, pprWithTYPE )
-import GHC.Core.Unify     ( tcMatchTys, flattenTys )
+import GHC.Core.Unify     ( tcMatchTys )
 import GHC.Core.InstEnv
 import GHC.Core.TyCon
 import GHC.Core.Class
@@ -2420,8 +2420,7 @@ mkDictErr ctxt cts
       && (null unifiers || all (not . isAmbiguousTyVar) (tyCoVarsOfCtList ct))
 
     lookup_cls_inst inst_envs ct
-                -- Note [Flattening in error message generation]
-      = (ct, lookupInstEnv True inst_envs clas (flattenTys emptyInScopeSet tys))
+      = (ct, lookupInstEnv True inst_envs clas tys)
       where
         (clas, tys) = getClassPredTys (ctPred ct)
 
@@ -2862,8 +2861,8 @@ pprPotentials (PrintPotentialInstances show_potentials) sty herald insts
                              orphNamesOfTypes (is_tys cls_inst)
 
     name_in_scope name
-      | isBuiltInSyntax name
-      = True -- E.g. (->)
+      | pretendNameIsInScope name
+      = True -- E.g. (->); see Note [pretendNameIsInScope] in GHC.Builtin.Names
       | Just mod <- nameModule_maybe name
       = qual_in_scope (qualName sty mod (nameOccName name))
       | otherwise
@@ -2897,7 +2896,7 @@ we want to give it a bit of structure.  Here's the plan
   These are the ones most likely to be useful to the programmer.
 
 * Show at most n_show in-scope instances,
-  and summarise the rest ("plus 3 others")
+  and summarise the rest ("plus N others")
 
 * Summarise the not-in-scope instances ("plus 4 not in scope")
 
@@ -2906,18 +2905,6 @@ we want to give it a bit of structure.  Here's the plan
 -}
 
 {-
-Note [Flattening in error message generation]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Consider (C (Maybe (F x))), where F is a type function, and we have
-instances
-                C (Maybe Int) and C (Maybe a)
-Since (F x) might turn into Int, this is an overlap situation, and
-indeed the main solver will have refrained
-from solving.  But by the time we get to error message generation, we've
-un-flattened the constraint.  So we must *re*-flatten it before looking
-up in the instance environment, lest we only report one matching
-instance when in fact there are two.
-
 Note [Kind arguments in error messages]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 It can be terribly confusing to get an error message like (#9171)
diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py
index fba69533e0e87b4de70162eca177a894306db7e4..7a1fafbbd7f28f41d093262049204e9747fe4550 100644
--- a/testsuite/driver/testlib.py
+++ b/testsuite/driver/testlib.py
@@ -2232,9 +2232,11 @@ def normalise_errmsg(s: str) -> str:
     # Error messages sometimes contain ghc-bignum implementation package
     s = re.sub('ghc-bignum-[0-9.]+', 'ghc-bignum-<VERSION>', s)
 
-    # Error messages sometimes contain this blurb which can vary
+    # Error messages sometimes contain these blurbs which can vary
     # spuriously depending upon build configuration (e.g. based on bignum
     # backend)
+    s = re.sub('...plus ([a-z]+|[0-9]+) others',
+                 '...plus N others', s)
     s = re.sub('...plus ([a-z]+|[0-9]+) instances involving out-of-scope types',
                  '...plus N instances involving out-of-scope types', s)
 
diff --git a/testsuite/tests/ado/T13242a.stderr b/testsuite/tests/ado/T13242a.stderr
index f5dce341aca25a9716c8ebc4a6799b53cf239196..4ada4ecaedd4a24078669291afb58e1cc8596acb 100644
--- a/testsuite/tests/ado/T13242a.stderr
+++ b/testsuite/tests/ado/T13242a.stderr
@@ -29,8 +29,8 @@ T13242a.hs:13:13: error:
         instance Eq Ordering -- Defined in ‘GHC.Classes’
         instance Eq Integer -- Defined in ‘GHC.Num.Integer’
         instance Eq () -- Defined in ‘GHC.Classes’
-        ...plus 22 others
-        ...plus five instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In a stmt of a 'do' block: return (x == x)
       In the expression:
diff --git a/testsuite/tests/annotations/should_fail/annfail10.stderr b/testsuite/tests/annotations/should_fail/annfail10.stderr
index a6e767f9e57f6f1beb78ce5ca84554285a9e163a..bd28fb4b175db2df97b7c8021e9e9350729291c4 100644
--- a/testsuite/tests/annotations/should_fail/annfail10.stderr
+++ b/testsuite/tests/annotations/should_fail/annfail10.stderr
@@ -10,8 +10,8 @@ annfail10.hs:9:1: error:
         instance Data.Data.Data Ordering -- Defined in ‘Data.Data’
         instance Data.Data.Data a => Data.Data.Data (Maybe a)
           -- Defined in ‘Data.Data’
-        ...plus 16 others
-        ...plus 50 instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the annotation: {-# ANN f 1 #-}
 
@@ -23,7 +23,7 @@ annfail10.hs:9:11: error:
         instance Num Integer -- Defined in ‘GHC.Num’
         instance Num Double -- Defined in ‘GHC.Float’
         instance Num Float -- Defined in ‘GHC.Float’
-        ...plus two others
-        ...plus 19 instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the annotation: {-# ANN f 1 #-}
diff --git a/testsuite/tests/ghci.debugger/scripts/break006.stderr b/testsuite/tests/ghci.debugger/scripts/break006.stderr
index 1b97299d927c417053d089fbcfab13c7b09b2ef4..198bc0df497c65c00f0070c316062a78982e4db2 100644
--- a/testsuite/tests/ghci.debugger/scripts/break006.stderr
+++ b/testsuite/tests/ghci.debugger/scripts/break006.stderr
@@ -8,8 +8,8 @@
         instance Show Ordering -- Defined in ‘GHC.Show’
         instance Show a => Show (Maybe a) -- Defined in ‘GHC.Show’
         instance Show Integer -- Defined in ‘GHC.Show’
-        ...plus 23 others
-        ...plus 12 instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In a stmt of an interactive GHCi command: print it
 
@@ -22,7 +22,7 @@
         instance Show Ordering -- Defined in ‘GHC.Show’
         instance Show a => Show (Maybe a) -- Defined in ‘GHC.Show’
         instance Show Integer -- Defined in ‘GHC.Show’
-        ...plus 23 others
-        ...plus 12 instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In a stmt of an interactive GHCi command: print it
diff --git a/testsuite/tests/ghci.debugger/scripts/print019.stderr b/testsuite/tests/ghci.debugger/scripts/print019.stderr
index bac95541f44ac3d09bb787bb8694749249cd2c7a..09b1bfbd8cd3f05bd2b2c29b4924884cb9d38933 100644
--- a/testsuite/tests/ghci.debugger/scripts/print019.stderr
+++ b/testsuite/tests/ghci.debugger/scripts/print019.stderr
@@ -8,7 +8,7 @@
         instance Show Ordering -- Defined in ‘GHC.Show’
         instance Show TyCon -- Defined in ‘GHC.Show’
         instance Show a => Show (List1 a) -- Defined at Test.hs:11:12
-        ...plus 30 others
-        ...plus 13 instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In a stmt of an interactive GHCi command: print it
diff --git a/testsuite/tests/ghci/scripts/T10963.stderr b/testsuite/tests/ghci/scripts/T10963.stderr
index aa081391c413a3d2e70199d6686f5106ea66070e..7082d6e6cf8fc5cf9e31d2c19f7298aec3503827 100644
--- a/testsuite/tests/ghci/scripts/T10963.stderr
+++ b/testsuite/tests/ghci/scripts/T10963.stderr
@@ -7,7 +7,7 @@
         instance Num Integer -- Defined in ‘GHC.Num’
         instance Num Double -- Defined in ‘GHC.Float’
         instance Num Float -- Defined in ‘GHC.Float’
-        ...plus two others
-        ...plus 8 instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the expression: foo
diff --git a/testsuite/tests/ghci/scripts/T15325.stderr b/testsuite/tests/ghci/scripts/T15325.stderr
index c767528e2cba6ddb5ed6ba9cebeda112af417f08..99efb5585eda2a7339505fd77612701e0d58aeb1 100644
--- a/testsuite/tests/ghci/scripts/T15325.stderr
+++ b/testsuite/tests/ghci/scripts/T15325.stderr
@@ -12,7 +12,7 @@ T15325.hs:11:9: warning: [-Wdeferred-type-errors (in -Wdefault)]
         instance Num Integer -- Defined in ‘GHC.Num’
         instance Num Double -- Defined in ‘GHC.Float’
         instance Num Float -- Defined in ‘GHC.Float’
-        ...plus two others
+        ...plus N others
         ...plus one instance involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the first argument of ‘f’, namely ‘0’
diff --git a/testsuite/tests/indexed-types/should_fail/T12522a.stderr b/testsuite/tests/indexed-types/should_fail/T12522a.stderr
index a91c31c764e6693fe54c9485c590288ac740a420..7fc4787a5ccd27bf2f9240f556de7645a4b203b8 100644
--- a/testsuite/tests/indexed-types/should_fail/T12522a.stderr
+++ b/testsuite/tests/indexed-types/should_fail/T12522a.stderr
@@ -10,8 +10,8 @@ T12522a.hs:23:26: error:
         instance Show Ordering -- Defined in ‘GHC.Show’
         instance Show a => Show (Maybe a) -- Defined in ‘GHC.Show’
         instance Show Integer -- Defined in ‘GHC.Show’
-        ...plus 23 others
-        ...plus 12 instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the first argument of ‘(++)’, namely ‘show n’
       In the second argument of ‘($)’, namely ‘show n ++ s’
diff --git a/testsuite/tests/indexed-types/should_fail/T20465.hs b/testsuite/tests/indexed-types/should_fail/T20465.hs
new file mode 100644
index 0000000000000000000000000000000000000000..8ec790b619d4f0adeb0c810b0f317369a15e196e
--- /dev/null
+++ b/testsuite/tests/indexed-types/should_fail/T20465.hs
@@ -0,0 +1,17 @@
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE TypeFamilies #-}
+
+module T20465 where
+
+import Data.Kind
+import Data.Proxy
+
+class Cls (a :: (Type -> Constraint) -> Type)
+instance Cls a
+instance Cls Proxy
+foo :: Cls Proxy => Int
+foo = 42
+bar :: Int
+bar = foo
diff --git a/testsuite/tests/indexed-types/should_fail/T20465.stderr b/testsuite/tests/indexed-types/should_fail/T20465.stderr
new file mode 100644
index 0000000000000000000000000000000000000000..90e90c9f5747a8ce3a05651cd80ceb688e647101
--- /dev/null
+++ b/testsuite/tests/indexed-types/should_fail/T20465.stderr
@@ -0,0 +1,8 @@
+
+T20465.hs:17:7: error:
+    • Overlapping instances for Cls Proxy arising from a use of ‘foo’
+      Matching instances:
+        instance Cls a -- Defined at T20465.hs:12:10
+        instance Cls Proxy -- Defined at T20465.hs:13:10
+    • In the expression: foo
+      In an equation for ‘bar’: bar = foo
diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T
index 9d2c68f095fde1a176bb39f68b50617ca3217952..c97c8c56e447dac93675826ff2217f3dc67e5572 100644
--- a/testsuite/tests/indexed-types/should_fail/all.T
+++ b/testsuite/tests/indexed-types/should_fail/all.T
@@ -164,3 +164,4 @@ test('T13571', normal, compile_fail, [''])
 test('T13571a', normal, compile_fail, [''])
 test('T18648', normal, compile_fail, [''])
 test('ExpandTFs', normal, compile_fail, [''])
+test('T20465', normal, compile_fail, [''])
diff --git a/testsuite/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr b/testsuite/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr
index 6e759d7f2afa0bd89bd343d16834e41a3df7c09c..5d391c4d9e708da8c6edb12fc2a6836c4fb69b25 100644
--- a/testsuite/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr
+++ b/testsuite/tests/overloadedlists/should_fail/overloadedlistsfail01.stderr
@@ -7,8 +7,8 @@ overloadedlistsfail01.hs:5:8: error:
         instance Show Ordering -- Defined in ‘GHC.Show’
         instance Show a => Show (Maybe a) -- Defined in ‘GHC.Show’
         instance Show Integer -- Defined in ‘GHC.Show’
-        ...plus 23 others
-        ...plus 14 instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the expression: print [1]
       In an equation for ‘main’: main = print [1]
@@ -19,7 +19,7 @@ overloadedlistsfail01.hs:5:14: error:
       Probable fix: use a type annotation to specify what ‘a0’ should be.
       These potential instances exist:
         instance GHC.Exts.IsList [a] -- Defined in ‘GHC.Exts’
-        ...plus four instances involving out-of-scope types
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the first argument of ‘print’, namely ‘[1]’
       In the expression: print [1]
@@ -34,7 +34,7 @@ overloadedlistsfail01.hs:5:15: error:
         instance Num Integer -- Defined in ‘GHC.Num’
         instance Num Double -- Defined in ‘GHC.Float’
         instance Num Float -- Defined in ‘GHC.Float’
-        ...plus two others
+        ...plus N others
         ...plus one instance involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the expression: 1
diff --git a/testsuite/tests/parser/should_fail/RecordDotSyntaxFail11.stderr b/testsuite/tests/parser/should_fail/RecordDotSyntaxFail11.stderr
index 2378585a6a5a8017f3e07b71fca6578676ee040c..4c26d77b10afad9ccbe6e467297ec7ad40b3cad8 100644
--- a/testsuite/tests/parser/should_fail/RecordDotSyntaxFail11.stderr
+++ b/testsuite/tests/parser/should_fail/RecordDotSyntaxFail11.stderr
@@ -1,24 +1,25 @@
-RecordDotSyntaxFail11.hs:8:3:
-     Ambiguous type variable ‘a0’ arising from a use of ‘print’
+
+RecordDotSyntaxFail11.hs:8:3: error:
+    • Ambiguous type variable ‘a0’ arising from a use of ‘print’
       prevents the constraint ‘(Show a0)’ from being solved.
       Probable fix: use a type annotation to specify what ‘a0’ should be.
       These potential instances exist:
         instance Show Ordering -- Defined in ‘GHC.Show’
         instance Show a => Show (Maybe a) -- Defined in ‘GHC.Show’
         instance Show Integer -- Defined in ‘GHC.Show’
-        ...plus 23 others
+        ...plus N others
         ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
-     In the first argument of ‘($)’, namely ‘print’
+    • In the first argument of ‘($)’, namely ‘print’
       In a stmt of a 'do' block: print $ (.foo.bar.baz) a
       In the expression:
         do let a = ...
            print $ (.foo.bar.baz) a
 
-RecordDotSyntaxFail11.hs:8:11:
-     No instance for (GHC.Records.HasField "baz" Int a0)
+RecordDotSyntaxFail11.hs:8:11: error:
+    • No instance for (GHC.Records.HasField "baz" Int a0)
         arising from a use of ‘GHC.Records.getField’
-     In the second argument of ‘($)’, namely ‘(.foo.bar.baz) a’
+    • In the second argument of ‘($)’, namely ‘(.foo.bar.baz) a’
       In a stmt of a 'do' block: print $ (.foo.bar.baz) a
       In the expression:
         do let a = ...
diff --git a/testsuite/tests/parser/should_fail/RecordDotSyntaxFail8.stderr b/testsuite/tests/parser/should_fail/RecordDotSyntaxFail8.stderr
index 8bf921b79f32765936c4b56a204a3796a6effc21..e66a9dfb28f793fcfcb140a2d0e5125e1a0b12d1 100644
--- a/testsuite/tests/parser/should_fail/RecordDotSyntaxFail8.stderr
+++ b/testsuite/tests/parser/should_fail/RecordDotSyntaxFail8.stderr
@@ -1,24 +1,25 @@
-RecordDotSyntaxFail8.hs:37:3:
-     Ambiguous type variable ‘a0’ arising from a use of ‘print’
+
+RecordDotSyntaxFail8.hs:37:3: error:
+    • Ambiguous type variable ‘a0’ arising from a use of ‘print’
       prevents the constraint ‘(Show a0)’ from being solved.
       Probable fix: use a type annotation to specify what ‘a0’ should be.
       These potential instances exist:
         instance Show Ordering -- Defined in ‘GHC.Show’
         instance Show Bar -- Defined at RecordDotSyntaxFail8.hs:22:41
         instance Show Baz -- Defined at RecordDotSyntaxFail8.hs:27:42
-        ...plus 27 others
+        ...plus N others
         ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
-     In the first argument of ‘($)’, namely ‘print’
+    • In the first argument of ‘($)’, namely ‘print’
       In a stmt of a 'do' block: print $ ....baz.quux
       In the expression:
         do let a = ...
            print $ ....quux
 
-RecordDotSyntaxFail8.hs:37:11:
-     No instance for (HasField "quux" Quux a0)
+RecordDotSyntaxFail8.hs:37:11: error:
+    • No instance for (HasField "quux" Quux a0)
         arising from selecting the field ‘quux’
-     In the second argument of ‘($)’, namely ‘....baz.quux’
+    • In the second argument of ‘($)’, namely ‘....baz.quux’
       In a stmt of a 'do' block: print $ ....baz.quux
       In the expression:
         do let a = ...
diff --git a/testsuite/tests/partial-sigs/should_fail/T10999.stderr b/testsuite/tests/partial-sigs/should_fail/T10999.stderr
index 71bab83508ce63f2b112ad1c4d2e67a54a8314aa..22df588742d81d883e21bbe33a4418f82b564e18 100644
--- a/testsuite/tests/partial-sigs/should_fail/T10999.stderr
+++ b/testsuite/tests/partial-sigs/should_fail/T10999.stderr
@@ -25,8 +25,8 @@ T10999.hs:8:28: error:
         instance Ord a => Ord (Set.Set a) -- Defined in ‘Data.Set.Internal’
         instance Ord Ordering -- Defined in ‘GHC.Classes’
         instance Ord Integer -- Defined in ‘GHC.Num.Integer’
-        ...plus 23 others
-        ...plus two instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the second argument of ‘($)’, namely ‘f ()’
       In the second argument of ‘($)’, namely ‘Set.toList $ f ()’
diff --git a/testsuite/tests/polykinds/T13393.stderr b/testsuite/tests/polykinds/T13393.stderr
index a06aecff70df78d9516aaa923a9758652f34dbc5..759f3408b0546c2695ff16e39c2282c13413eb3c 100644
--- a/testsuite/tests/polykinds/T13393.stderr
+++ b/testsuite/tests/polykinds/T13393.stderr
@@ -7,8 +7,8 @@ T13393.hs:61:3: error:
         instance Traversable (Either a) -- Defined in ‘Data.Traversable’
         instance Traversable Identity -- Defined in ‘Data.Traversable’
         instance Traversable Maybe -- Defined in ‘Data.Traversable’
-        ...plus three others
-        ...plus 28 instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In a stmt of a 'do' block:
         mapM putBackLeftOverInputAndReturnOutput undefined
diff --git a/testsuite/tests/typecheck/should_compile/T14273.stderr b/testsuite/tests/typecheck/should_compile/T14273.stderr
index daff685704dfec074fd2aa26432c4344bcb7a276..7aa78d56a9369a99ea2241ef1a2e1de9956ea88b 100644
--- a/testsuite/tests/typecheck/should_compile/T14273.stderr
+++ b/testsuite/tests/typecheck/should_compile/T14273.stderr
@@ -11,8 +11,8 @@ T14273.hs:7:27: warning: [-Wdeferred-type-errors (in -Wdefault)]
           -- Defined in ‘Data.Either’
         instance Show Ordering -- Defined in ‘GHC.Show’
         instance Show a => Show (Maybe a) -- Defined in ‘GHC.Show’
-        ...plus 24 others
-        ...plus 70 instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the first argument of ‘Just’, namely ‘(show _a)’
       In the expression: Just (show _a)
@@ -65,8 +65,8 @@ T14273.hs:13:10: warning: [-Wdeferred-type-errors (in -Wdefault)]
           -- Defined in ‘Data.Either’
         instance Show Ordering -- Defined in ‘GHC.Show’
         instance Show a => Show (Maybe a) -- Defined in ‘GHC.Show’
-        ...plus 24 others
-        ...plus 70 instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the expression: show (_h ++ [])
       In an equation for ‘foo’: foo xs = show (_h ++ [])
diff --git a/testsuite/tests/typecheck/should_compile/holes2.stderr b/testsuite/tests/typecheck/should_compile/holes2.stderr
index 1e30e87882e614eca6db0512564428a44c7603a8..a88ea524e08b4bf22d66bc1c39c05414145edc09 100644
--- a/testsuite/tests/typecheck/should_compile/holes2.stderr
+++ b/testsuite/tests/typecheck/should_compile/holes2.stderr
@@ -8,8 +8,8 @@ holes2.hs:3:5: warning: [-Wdeferred-type-errors (in -Wdefault)]
           -- Defined in ‘Data.Either’
         instance Show Ordering -- Defined in ‘GHC.Show’
         instance Show a => Show (Maybe a) -- Defined in ‘GHC.Show’
-        ...plus 24 others
-        ...plus 70 instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the expression: show _
       In an equation for ‘f’: f = show _
diff --git a/testsuite/tests/typecheck/should_fail/T10971b.stderr b/testsuite/tests/typecheck/should_fail/T10971b.stderr
index 0947ab1b6f70e8c5528f285ac97b807fb47bd9c4..1a6104d501263b2af7dce8efac599ca044fea3e4 100644
--- a/testsuite/tests/typecheck/should_fail/T10971b.stderr
+++ b/testsuite/tests/typecheck/should_fail/T10971b.stderr
@@ -10,8 +10,8 @@ T10971b.hs:4:11: error:
         instance Foldable (Either a) -- Defined in ‘Data.Foldable’
         instance Foldable Maybe -- Defined in ‘Data.Foldable’
         instance Foldable ((,) a) -- Defined in ‘Data.Foldable’
-        ...plus two others
-        ...plus 29 instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the expression: length x
       In the expression: \ x -> length x
@@ -28,8 +28,8 @@ T10971b.hs:5:13: error:
         instance Traversable (Either a) -- Defined in ‘Data.Traversable’
         instance Traversable Maybe -- Defined in ‘Data.Traversable’
         instance Traversable ((,) a) -- Defined in ‘Data.Traversable’
-        ...plus two others
-        ...plus 29 instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the expression: fmapDefault f x
       In the expression: \ f x -> fmapDefault f x
@@ -46,8 +46,8 @@ T10971b.hs:6:14: error:
         instance Traversable (Either a) -- Defined in ‘Data.Traversable’
         instance Traversable Maybe -- Defined in ‘Data.Traversable’
         instance Traversable ((,) a) -- Defined in ‘Data.Traversable’
-        ...plus two others
-        ...plus 29 instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the expression: fmapDefault f x
       In the expression: (fmapDefault f x, length x)
@@ -64,8 +64,8 @@ T10971b.hs:6:31: error:
         instance Foldable (Either a) -- Defined in ‘Data.Foldable’
         instance Foldable Maybe -- Defined in ‘Data.Foldable’
         instance Foldable ((,) a) -- Defined in ‘Data.Foldable’
-        ...plus two others
-        ...plus 29 instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the expression: length x
       In the expression: (fmapDefault f x, length x)
diff --git a/testsuite/tests/typecheck/should_fail/T12921.stderr b/testsuite/tests/typecheck/should_fail/T12921.stderr
index 478d2f03c8acb39f56bb587e87bdbd67924a531f..b3de93e2f4f78388ac72a69487ee027679a3ef5a 100644
--- a/testsuite/tests/typecheck/should_fail/T12921.stderr
+++ b/testsuite/tests/typecheck/should_fail/T12921.stderr
@@ -10,8 +10,8 @@ T12921.hs:4:1: error:
         instance Data.Data.Data Ordering -- Defined in ‘Data.Data’
         instance Data.Data.Data a => Data.Data.Data (Maybe a)
           -- Defined in ‘Data.Data’
-        ...plus 16 others
-        ...plus 50 instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the annotation:
         {-# ANN module "HLint: ignore Reduce duplication" #-}
@@ -24,7 +24,7 @@ T12921.hs:4:16: error:
       These potential instances exist:
         instance (a ~ Char) => Data.String.IsString [a]
           -- Defined in ‘Data.String’
-        ...plus two instances involving out-of-scope types
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the annotation:
         {-# ANN module "HLint: ignore Reduce duplication" #-}
diff --git a/testsuite/tests/typecheck/should_fail/T13292.stderr b/testsuite/tests/typecheck/should_fail/T13292.stderr
index a3a7ba3baef2f7fcd7a927326b9483037eca042c..2cc7bb41c3ea4be2eeba06799554756ca6993a21 100644
--- a/testsuite/tests/typecheck/should_fail/T13292.stderr
+++ b/testsuite/tests/typecheck/should_fail/T13292.stderr
@@ -8,9 +8,9 @@ T13292a.hs:4:12: warning: [-Wdeferred-type-errors (in -Wdefault)]
       These potential instances exist:
         instance Monad IO -- Defined in ‘GHC.Base’
         instance Monad Maybe -- Defined in ‘GHC.Base’
-        instance Monoid a => Monad ((,) a) -- Defined in ‘GHC.Base’
-        ...plus four others
-        ...plus two instances involving out-of-scope types
+        instance Monad ((->) r) -- Defined in ‘GHC.Base’
+        ...plus N others
+        ...plus one instance involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the expression: return ()
       In an equation for ‘someFunc’: someFunc = return ()
diff --git a/testsuite/tests/typecheck/should_fail/T14884.stderr b/testsuite/tests/typecheck/should_fail/T14884.stderr
index 2c5abc33f0d9ebf97953c80f1fc6f7d9e25bea20..e28ad780bf86cc2c9117350723b7c53ff23723fe 100644
--- a/testsuite/tests/typecheck/should_fail/T14884.stderr
+++ b/testsuite/tests/typecheck/should_fail/T14884.stderr
@@ -40,8 +40,8 @@ T14884.hs:4:7: error:
           -- Defined in ‘Data.Either’
         instance Show Ordering -- Defined in ‘GHC.Show’
         instance Show a => Show (Maybe a) -- Defined in ‘GHC.Show’
-        ...plus 24 others
-        ...plus 67 instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the first argument of ‘_’, namely ‘print’
       In the expression: _ print "abc"
diff --git a/testsuite/tests/typecheck/should_fail/T5095.stderr b/testsuite/tests/typecheck/should_fail/T5095.stderr
index e30898f74f6fb9a43a5286ff370515d8233f292a..3641d18f3428475e19e571dfb9fa2ada90ec23f6 100644
--- a/testsuite/tests/typecheck/should_fail/T5095.stderr
+++ b/testsuite/tests/typecheck/should_fail/T5095.stderr
@@ -5,8 +5,8 @@ T5095.hs:9:11: error:
         instance [overlappable] Show a => Eq a -- Defined at T5095.hs:5:31
         instance Eq Ordering -- Defined in ‘GHC.Classes’
         instance Eq a => Eq (Maybe a) -- Defined in ‘GHC.Maybe’
-        ...plus 24 others
-        ...plus six instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
       (The choice depends on the instantiation of ‘a’
        To pick the first instance above, use IncoherentInstances
diff --git a/testsuite/tests/typecheck/should_fail/TyAppPat_PatternBindingExistential.stderr b/testsuite/tests/typecheck/should_fail/TyAppPat_PatternBindingExistential.stderr
index a05806e7bec6d4725de27381ca56c38094bf5aa1..e316f78fc61618311c6a7febecc68a70c273071e 100644
--- a/testsuite/tests/typecheck/should_fail/TyAppPat_PatternBindingExistential.stderr
+++ b/testsuite/tests/typecheck/should_fail/TyAppPat_PatternBindingExistential.stderr
@@ -24,8 +24,8 @@ TyAppPat_PatternBindingExistential.hs:13:3: error:
         instance Show Ordering -- Defined in ‘GHC.Show’
         instance Show a => Show (Maybe a) -- Defined in ‘GHC.Show’
         instance Show Integer -- Defined in ‘GHC.Show’
-        ...plus 23 others
-        ...plus 12 instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In a stmt of a 'do' block: print (x :: a)
       In the expression: do print (x :: a)
diff --git a/testsuite/tests/typecheck/should_fail/tcfail008.stderr b/testsuite/tests/typecheck/should_fail/tcfail008.stderr
index 1e7bc19585412f85e4e2b22cdebda56b7b20cd76..974eccb4854aeb013903131a2d7c66816e4a98ab 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail008.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail008.stderr
@@ -8,7 +8,7 @@ tcfail008.hs:3:5: error:
         instance Num Integer -- Defined in ‘GHC.Num’
         instance Num Double -- Defined in ‘GHC.Float’
         instance Num Float -- Defined in ‘GHC.Float’
-        ...plus two others
+        ...plus N others
         ...plus one instance involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the first argument of ‘(:)’, namely ‘1’
diff --git a/testsuite/tests/typecheck/should_fail/tcfail072.stderr b/testsuite/tests/typecheck/should_fail/tcfail072.stderr
index b91f96bf372d2eb3a092d31bc711a60071e33d9c..c916c92df135bfc58c6409afe33236c336659f92 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail072.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail072.stderr
@@ -10,8 +10,8 @@ tcfail072.hs:23:13: error:
         instance Ord Ordering -- Defined in ‘GHC.Classes’
         instance Ord Integer -- Defined in ‘GHC.Num.Integer’
         instance Ord () -- Defined in ‘GHC.Classes’
-        ...plus 22 others
-        ...plus two instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the expression: g A
       In an equation for ‘g’: g (B _ _) = g A
diff --git a/testsuite/tests/typecheck/should_fail/tcfail133.stderr b/testsuite/tests/typecheck/should_fail/tcfail133.stderr
index f5e2309a81498d98e93e4a004aaa45407b13bc52..004c06a28857a1fb4721e7c52de884c6a735dc32 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail133.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail133.stderr
@@ -11,8 +11,8 @@ tcfail133.hs:68:7: error:
         instance (Number a, Digit b, Show a, Show b) => Show (a :@ b)
           -- Defined at tcfail133.hs:11:54
         instance Show One -- Defined at tcfail133.hs:9:28
-        ...plus 26 others
-        ...plus 12 instances involving out-of-scope types
+        ...plus N others
+        ...plus N instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the first argument of ‘($)’, namely ‘show’
       In the expression: show $ add (One :@ Zero) (One :@ One)
diff --git a/testsuite/tests/typecheck/should_fail/tcfail181.stderr b/testsuite/tests/typecheck/should_fail/tcfail181.stderr
index c21214a6898a7dc17ddf9b09927e0cb944622f87..f87812394919c2e6805c8f21e2b8605fc4cd94d1 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail181.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail181.stderr
@@ -9,9 +9,9 @@ tcfail181.hs:17:9: error:
       These potential instances exist:
         instance Monad IO -- Defined in ‘GHC.Base’
         instance Monad Maybe -- Defined in ‘GHC.Base’
-        instance Monoid a => Monad ((,) a) -- Defined in ‘GHC.Base’
-        ...plus four others
-        ...plus two instances involving out-of-scope types
+        instance Monad ((->) r) -- Defined in ‘GHC.Base’
+        ...plus N others
+        ...plus one instance involving out-of-scope types
         (use -fprint-potential-instances to see them all)
     • In the expression: foo
       In the expression: foo {bar = return True}