From 8150f6546e6fd0006252e245d5697f13ffd8ce3e Mon Sep 17 00:00:00 2001
From: Sebastian Graf <sebastian.graf@kit.edu>
Date: Wed, 18 Nov 2020 10:29:25 +0100
Subject: [PATCH] PmCheck: Print types of uncovered patterns (#18932)
MIME-Version: 1.0
Content-Type: text/plain; charset=UTF-8
Content-Transfer-Encoding: 8bit

In order to avoid confusion as in #18932, we display the type of the
match variables in the non-exhaustiveness warning, e.g.

```
T18932.hs:14:1: warning: [-Wincomplete-patterns]
    Pattern match(es) are non-exhaustive
    In an equation for ‘g’:
        Patterns of type  ‘T a’, ‘T a’, ‘T a’ not matched:
            (MkT2 _) (MkT1 _) (MkT1 _)
            (MkT2 _) (MkT1 _) (MkT2 _)
            (MkT2 _) (MkT2 _) (MkT1 _)
            (MkT2 _) (MkT2 _) (MkT2 _)
            ...
   |
14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x
   | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
```

It also allows us to omit the type signature on wildcard matches which
we previously showed in only some situations, particularly
`-XEmptyCase`.

Fixes #18932.
---
 compiler/GHC/HsToCore/Pmc.hs                  |  5 ++++-
 compiler/GHC/HsToCore/Pmc/Ppr.hs              | 17 ++-------------
 .../should_compile/DsStrictWarn.stderr        |  2 +-
 .../deSugar/should_compile/GadtOverlap.stderr |  2 +-
 .../deSugar/should_compile/T14135.stderr      |  3 ++-
 .../deSugar/should_compile/T14546a.stderr     |  4 ++--
 .../deSugar/should_compile/T14546d.stderr     |  2 +-
 .../tests/deSugar/should_compile/T5455.stderr |  4 ++--
 .../should_compile/KindEqualities.stderr      |  2 +-
 testsuite/tests/driver/T8101.stderr           |  2 +-
 testsuite/tests/driver/T8101b.stderr          |  2 +-
 testsuite/tests/driver/werror.stderr          |  2 +-
 testsuite/tests/ghci/prog018/prog018.stdout   |  2 +-
 .../tests/parser/should_compile/T15139.stderr |  8 ++++---
 .../tests/pmcheck/complete_sigs/T13964.stderr |  3 ++-
 .../pmcheck/complete_sigs/T14059a.stderr      |  6 ++++--
 .../tests/pmcheck/complete_sigs/T17386.stderr |  4 ++--
 .../complete_sigs/completesig02.stderr        |  2 +-
 .../complete_sigs/completesig04.stderr        |  5 +++--
 .../complete_sigs/completesig06.stderr        | 10 ++++-----
 .../complete_sigs/completesig07.stderr        |  2 +-
 .../complete_sigs/completesig10.stderr        |  2 +-
 .../complete_sigs/completesig11.stderr        |  2 +-
 .../should_compile/EmptyCase001.stderr        |  6 +++---
 .../should_compile/EmptyCase002.stderr        | 11 ++++++----
 .../should_compile/EmptyCase003.stderr        |  6 +++---
 .../should_compile/EmptyCase004.stderr        | 14 ++++++-------
 .../should_compile/EmptyCase005.stderr        | 14 +++++++------
 .../should_compile/EmptyCase006.stderr        |  5 +++--
 .../should_compile/EmptyCase007.stderr        | 16 ++++++++------
 .../should_compile/EmptyCase008.stderr        | 11 ++++++----
 .../should_compile/EmptyCase009.stderr        |  8 ++++---
 .../should_compile/EmptyCase010.stderr        | 21 ++++++++++++-------
 .../pmcheck/should_compile/T10746.stderr      |  2 +-
 .../pmcheck/should_compile/T11336b.stderr     |  3 ++-
 .../pmcheck/should_compile/T11822.stderr      |  3 ++-
 .../pmcheck/should_compile/T15305.stderr      |  3 ++-
 .../pmcheck/should_compile/T15450.stderr      |  4 ++--
 .../pmcheck/should_compile/T17218.stderr      |  2 +-
 .../pmcheck/should_compile/T17729.stderr      |  3 ++-
 .../pmcheck/should_compile/T17836b.stderr     |  2 +-
 .../pmcheck/should_compile/T17977.stderr      |  3 ++-
 .../pmcheck/should_compile/T18572.stderr      |  3 ++-
 .../pmcheck/should_compile/T18670.stderr      |  3 ++-
 .../pmcheck/should_compile/T18708.stderr      |  2 +-
 .../tests/pmcheck/should_compile/T18932.hs    | 14 +++++++++++++
 .../pmcheck/should_compile/T18932.stderr      | 19 +++++++++++++++++
 .../tests/pmcheck/should_compile/T2204.stderr |  4 ++--
 .../pmcheck/should_compile/T9951b.stderr      |  2 +-
 .../should_compile/TooManyDeltas.stderr       |  2 +-
 testsuite/tests/pmcheck/should_compile/all.T  |  2 ++
 .../pmcheck/should_compile/pmc001.stderr      |  4 ++--
 .../pmcheck/should_compile/pmc005.stderr      |  3 ++-
 .../pmcheck/should_compile/pmc007.stderr      |  7 ++++---
 .../pmcheck/should_compile/pmc009.stderr      |  4 +++-
 .../warnings/should_fail/WerrorFail.stderr    |  3 ++-
 .../warnings/should_fail/WerrorFail2.stderr   |  2 +-
 57 files changed, 184 insertions(+), 120 deletions(-)
 create mode 100644 testsuite/tests/pmcheck/should_compile/T18932.hs
 create mode 100644 testsuite/tests/pmcheck/should_compile/T18932.stderr

diff --git a/compiler/GHC/HsToCore/Pmc.hs b/compiler/GHC/HsToCore/Pmc.hs
index 7af0d4605e09..651f37f90979 100644
--- a/compiler/GHC/HsToCore/Pmc.hs
+++ b/compiler/GHC/HsToCore/Pmc.hs
@@ -381,7 +381,10 @@ reportWarnings dflags ctx@(DsMatchContext kind loc) vars
       case vars of -- See #11245
            [] -> text "Guards do not cover entire pattern space"
            _  -> let us = map (\nabla -> pprUncovered nabla vars) nablas
-                 in  hang (text "Patterns not matched:") 4
+                     pp_tys = pprQuotedList $ map idType vars
+                 in  hang
+                       (text "Patterns of type" <+> pp_tys <+> text "not matched:")
+                       4
                        (vcat (take maxPatterns us) $$ dots maxPatterns us)
 
     approx_msg = vcat
diff --git a/compiler/GHC/HsToCore/Pmc/Ppr.hs b/compiler/GHC/HsToCore/Pmc/Ppr.hs
index fea1ecfe398e..3de6a14970ce 100644
--- a/compiler/GHC/HsToCore/Pmc/Ppr.hs
+++ b/compiler/GHC/HsToCore/Pmc/Ppr.hs
@@ -136,26 +136,13 @@ checkRefuts x = do
 
 -- | Pretty print a variable, but remember to prettify the names of the variables
 -- that refer to neg-literals. The ones that cannot be shown are printed as
--- underscores. Even with a type signature, if it's not too noisy.
+-- underscores.
 pprPmVar :: PprPrec -> Id -> PmPprM SDoc
--- Type signature is "too noisy" by my definition if it needs to parenthesize.
--- I like           "not matched: _ :: Proxy (DIdEnv (Id, SDoc))",
--- but I don't like "not matched: (_ :: stuff) (_:_) (_ :: Proxy (DIdEnv (Id, SDoc)))"
--- The useful information in the latter case is the constructor that we missed,
--- not the types of the wildcards in the places that aren't matched as a result.
 pprPmVar prec x = do
   nabla <- ask
   case lookupSolution nabla x of
     Just (PACA alt _tvs args) -> pprPmAltCon prec alt args
-    Nothing                   -> fromMaybe typed_wildcard <$> checkRefuts x
-      where
-        -- if we have no info about the parameter and would just print a
-        -- wildcard, also show its type.
-        typed_wildcard
-          | prec <= sigPrec
-          = underscore <+> text "::" <+> ppr (idType x)
-          | otherwise
-          = underscore
+    Nothing                   -> fromMaybe underscore <$> checkRefuts x
 
 pprPmAltCon :: PprPrec -> PmAltCon -> [Id] -> PmPprM SDoc
 pprPmAltCon _prec (PmAltLit l)      _    = pure (ppr l)
diff --git a/testsuite/tests/deSugar/should_compile/DsStrictWarn.stderr b/testsuite/tests/deSugar/should_compile/DsStrictWarn.stderr
index e5de14fda8ec..a7c76fff4470 100644
--- a/testsuite/tests/deSugar/should_compile/DsStrictWarn.stderr
+++ b/testsuite/tests/deSugar/should_compile/DsStrictWarn.stderr
@@ -1,4 +1,4 @@
 
 DsStrictWarn.hs:7:11: warning: [-Wincomplete-uni-patterns]
     Pattern match(es) are non-exhaustive
-    In a pattern binding: Patterns not matched: []
+    In a pattern binding: Patterns of type  ‘String’ not matched: []
diff --git a/testsuite/tests/deSugar/should_compile/GadtOverlap.stderr b/testsuite/tests/deSugar/should_compile/GadtOverlap.stderr
index 02f091ee3667..e618c45c0785 100644
--- a/testsuite/tests/deSugar/should_compile/GadtOverlap.stderr
+++ b/testsuite/tests/deSugar/should_compile/GadtOverlap.stderr
@@ -1,4 +1,4 @@
 
 GadtOverlap.hs:19:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘h’: Patterns not matched: T3
+    In an equation for ‘h’: Patterns of type  ‘T a’ not matched: T3
diff --git a/testsuite/tests/deSugar/should_compile/T14135.stderr b/testsuite/tests/deSugar/should_compile/T14135.stderr
index ec0a340bcc78..8674cbff6623 100644
--- a/testsuite/tests/deSugar/should_compile/T14135.stderr
+++ b/testsuite/tests/deSugar/should_compile/T14135.stderr
@@ -1,4 +1,5 @@
 
 T14135.hs:16:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘f’: Patterns not matched: Foo2 _
+    In an equation for ‘f’:
+        Patterns of type  ‘Foo a’ not matched: Foo2 _
diff --git a/testsuite/tests/deSugar/should_compile/T14546a.stderr b/testsuite/tests/deSugar/should_compile/T14546a.stderr
index 5918a45cc7f1..684501223e4b 100644
--- a/testsuite/tests/deSugar/should_compile/T14546a.stderr
+++ b/testsuite/tests/deSugar/should_compile/T14546a.stderr
@@ -33,7 +33,7 @@ T14546a.hs:21:7: warning: [-Woverlapping-patterns (in -Wdefault)]
 
 T14546a.hs:23:4: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: 0
+    In a case alternative: Patterns of type  ‘Integer’ not matched: 0
 
 T14546a.hs:24:7: warning: [-Woverlapping-patterns (in -Wdefault)]
     Pattern match is redundant
@@ -45,7 +45,7 @@ T14546a.hs:25:7: warning: [-Woverlapping-patterns (in -Wdefault)]
 
 T14546a.hs:27:4: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: 3
+    In a case alternative: Patterns of type  ‘Integer’ not matched: 3
 
 T14546a.hs:28:7: warning: [-Woverlapping-patterns (in -Wdefault)]
     Pattern match is redundant
diff --git a/testsuite/tests/deSugar/should_compile/T14546d.stderr b/testsuite/tests/deSugar/should_compile/T14546d.stderr
index db5b9ca28567..4e59e617dc71 100644
--- a/testsuite/tests/deSugar/should_compile/T14546d.stderr
+++ b/testsuite/tests/deSugar/should_compile/T14546d.stderr
@@ -6,4 +6,4 @@ T14546d.hs:3:10: warning: [-Wmissing-methods (in -Wdefault)]
 
 T14546d.hs:7:5: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: 3
+    In a case alternative: Patterns of type  ‘D’ not matched: 3
diff --git a/testsuite/tests/deSugar/should_compile/T5455.stderr b/testsuite/tests/deSugar/should_compile/T5455.stderr
index 9c43612ccaad..ff2b578c65db 100644
--- a/testsuite/tests/deSugar/should_compile/T5455.stderr
+++ b/testsuite/tests/deSugar/should_compile/T5455.stderr
@@ -1,8 +1,8 @@
 
 T5455.hs:8:11: warning: [-Wincomplete-uni-patterns]
     Pattern match(es) are non-exhaustive
-    In a pattern binding: Patterns not matched: []
+    In a pattern binding: Patterns of type  ‘String’ not matched: []
 
 T5455.hs:13:13: warning: [-Wincomplete-uni-patterns]
     Pattern match(es) are non-exhaustive
-    In a pattern binding: Patterns not matched: []
+    In a pattern binding: Patterns of type  ‘String’ not matched: []
diff --git a/testsuite/tests/dependent/should_compile/KindEqualities.stderr b/testsuite/tests/dependent/should_compile/KindEqualities.stderr
index c36ee98d91e1..2155dea76563 100644
--- a/testsuite/tests/dependent/should_compile/KindEqualities.stderr
+++ b/testsuite/tests/dependent/should_compile/KindEqualities.stderr
@@ -2,7 +2,7 @@
 KindEqualities.hs:25:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In an equation for ‘zero’:
-        Patterns not matched:
+        Patterns of type  ‘TyRep a’ not matched:
             TyApp (TyApp _ _) TyInt
             TyApp (TyApp _ _) TyBool
             TyApp (TyApp _ _) TyMaybe
diff --git a/testsuite/tests/driver/T8101.stderr b/testsuite/tests/driver/T8101.stderr
index a486f965e3ec..f9ede45f0b42 100644
--- a/testsuite/tests/driver/T8101.stderr
+++ b/testsuite/tests/driver/T8101.stderr
@@ -2,6 +2,6 @@
 T8101.hs:7:9: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In a case alternative:
-        Patterns not matched:
+        Patterns of type  ‘ABC’ not matched:
             B
             C
diff --git a/testsuite/tests/driver/T8101b.stderr b/testsuite/tests/driver/T8101b.stderr
index ea8bcf0c4dbc..ed93a3768066 100644
--- a/testsuite/tests/driver/T8101b.stderr
+++ b/testsuite/tests/driver/T8101b.stderr
@@ -3,6 +3,6 @@
 T8101b.hs:7:9: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In a case alternative:
-        Patterns not matched:
+        Patterns of type  ‘ABC’ not matched:
             B
             C
diff --git a/testsuite/tests/driver/werror.stderr b/testsuite/tests/driver/werror.stderr
index 2d9fd5324caf..791c74352b5e 100644
--- a/testsuite/tests/driver/werror.stderr
+++ b/testsuite/tests/driver/werror.stderr
@@ -21,7 +21,7 @@ werror.hs:10:1: error: [-Wmissing-signatures (in -Wall), -Werror=missing-signatu
 
 werror.hs:10:1: error: [-Wincomplete-patterns (in -Wextra), -Werror=incomplete-patterns]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘f’: Patterns not matched: (_:_)
+    In an equation for ‘f’: Patterns of type  ‘[a]’ not matched: (_:_)
 
 werror.hs:11:1: error: [-Woverlapping-patterns (in -Wdefault), -Werror=overlapping-patterns]
     Pattern match is redundant
diff --git a/testsuite/tests/ghci/prog018/prog018.stdout b/testsuite/tests/ghci/prog018/prog018.stdout
index ba8594dcf528..544ef8e67126 100644
--- a/testsuite/tests/ghci/prog018/prog018.stdout
+++ b/testsuite/tests/ghci/prog018/prog018.stdout
@@ -5,7 +5,7 @@
 A.hs:5:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In an equation for ‘incompletePattern’:
-        Patterns not matched: p where p is not one of {0}
+        Patterns of type ‘Int’ not matched: p where p is not one of {0}
 
 A.hs:8:15: warning: [-Wunused-matches (in -Wextra)]
     Defined but not used: ‘x’
diff --git a/testsuite/tests/parser/should_compile/T15139.stderr b/testsuite/tests/parser/should_compile/T15139.stderr
index 010bd7440c07..b42cb23d2762 100644
--- a/testsuite/tests/parser/should_compile/T15139.stderr
+++ b/testsuite/tests/parser/should_compile/T15139.stderr
@@ -1,21 +1,23 @@
 
 T15139.hs:11:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘f1’: Patterns not matched: False
+    In an equation for ‘f1’:
+        Patterns of type  ‘Bool’ not matched: False
    |
 11 | f1 True = case can'tHappen of {}
    | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
 
 T15139.hs:12:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘f2’: Patterns not matched: False
+    In an equation for ‘f2’:
+        Patterns of type  ‘Bool’ not matched: False
    |
 12 | f2 True = case can'tHappen of
    | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
 
 T15139.hs:13:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘g’: Patterns not matched: False
+    In an equation for ‘g’: Patterns of type  ‘Bool’ not matched: False
    |
 13 | g  True = case () of () -> True
    | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
diff --git a/testsuite/tests/pmcheck/complete_sigs/T13964.stderr b/testsuite/tests/pmcheck/complete_sigs/T13964.stderr
index 606756a78397..4005321236c9 100644
--- a/testsuite/tests/pmcheck/complete_sigs/T13964.stderr
+++ b/testsuite/tests/pmcheck/complete_sigs/T13964.stderr
@@ -1,4 +1,5 @@
 
 T13964.hs:18:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘catchAll’: Patterns not matched: T
+    In an equation for ‘catchAll’:
+        Patterns of type  ‘Boolean’ not matched: T
diff --git a/testsuite/tests/pmcheck/complete_sigs/T14059a.stderr b/testsuite/tests/pmcheck/complete_sigs/T14059a.stderr
index 4a52c97dfefe..47a92504fb17 100644
--- a/testsuite/tests/pmcheck/complete_sigs/T14059a.stderr
+++ b/testsuite/tests/pmcheck/complete_sigs/T14059a.stderr
@@ -1,8 +1,10 @@
 
 T14059a.hs:20:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘wibble’: Patterns not matched: SFalse
+    In an equation for ‘wibble’:
+        Patterns of type  ‘SBool z’ not matched: SFalse
 
 T14059a.hs:23:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘wobble’: Patterns not matched: SFalse
+    In an equation for ‘wobble’:
+        Patterns of type  ‘SBool z’ not matched: SFalse
diff --git a/testsuite/tests/pmcheck/complete_sigs/T17386.stderr b/testsuite/tests/pmcheck/complete_sigs/T17386.stderr
index 9b60c06636e5..6c60cf13c013 100644
--- a/testsuite/tests/pmcheck/complete_sigs/T17386.stderr
+++ b/testsuite/tests/pmcheck/complete_sigs/T17386.stderr
@@ -1,8 +1,8 @@
 
 T17386.hs:11:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘f’: Patterns not matched: F
+    In an equation for ‘f’: Patterns of type  ‘B’ not matched: F
 
 T17386.hs:18:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘g’: Patterns not matched: T
+    In an equation for ‘g’: Patterns of type  ‘B’ not matched: T
diff --git a/testsuite/tests/pmcheck/complete_sigs/completesig02.stderr b/testsuite/tests/pmcheck/complete_sigs/completesig02.stderr
index 6da127a67412..dc24b31e63b3 100644
--- a/testsuite/tests/pmcheck/complete_sigs/completesig02.stderr
+++ b/testsuite/tests/pmcheck/complete_sigs/completesig02.stderr
@@ -1,4 +1,4 @@
 
 completesig02.hs:10:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘a’: Patterns not matched: ()
+    In an equation for ‘a’: Patterns of type  ‘()’ not matched: ()
diff --git a/testsuite/tests/pmcheck/complete_sigs/completesig04.stderr b/testsuite/tests/pmcheck/complete_sigs/completesig04.stderr
index a114d0199ed9..e04c57039061 100644
--- a/testsuite/tests/pmcheck/complete_sigs/completesig04.stderr
+++ b/testsuite/tests/pmcheck/complete_sigs/completesig04.stderr
@@ -2,10 +2,11 @@
 completesig04.hs:10:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In an equation for ‘f’:
-        Patterns not matched:
+        Patterns of type  ‘T’ not matched:
             B
             C
 
 completesig04.hs:12:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘g’: Patterns not matched: Nothing
+    In an equation for ‘g’:
+        Patterns of type  ‘Maybe a’ not matched: Nothing
diff --git a/testsuite/tests/pmcheck/complete_sigs/completesig06.stderr b/testsuite/tests/pmcheck/complete_sigs/completesig06.stderr
index 8659a3b0aab5..b993966789a0 100644
--- a/testsuite/tests/pmcheck/complete_sigs/completesig06.stderr
+++ b/testsuite/tests/pmcheck/complete_sigs/completesig06.stderr
@@ -1,29 +1,29 @@
 
 completesig06.hs:13:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘m1’: Patterns not matched: B
+    In an equation for ‘m1’: Patterns of type  ‘T’ not matched: B
 
 completesig06.hs:16:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘m2’: Patterns not matched: A
+    In an equation for ‘m2’: Patterns of type  ‘T’ not matched: A
 
 completesig06.hs:20:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In an equation for ‘m3’:
-        Patterns not matched:
+        Patterns of type  ‘T’ not matched:
             A
             B
 
 completesig06.hs:23:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In an equation for ‘m4’:
-        Patterns not matched:
+        Patterns of type  ‘T’, ‘S’ not matched:
             A D
             B D
 
 completesig06.hs:29:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In an equation for ‘m5’:
-        Patterns not matched:
+        Patterns of type  ‘T’, ‘S’ not matched:
             A D
             B D
diff --git a/testsuite/tests/pmcheck/complete_sigs/completesig07.stderr b/testsuite/tests/pmcheck/complete_sigs/completesig07.stderr
index b8e56892c9dd..1145cb850eec 100644
--- a/testsuite/tests/pmcheck/complete_sigs/completesig07.stderr
+++ b/testsuite/tests/pmcheck/complete_sigs/completesig07.stderr
@@ -10,7 +10,7 @@ completesig07.hs:20:1: warning: [-Woverlapping-patterns (in -Wdefault)]
 completesig07.hs:23:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In an equation for ‘m3’:
-        Patterns not matched:
+        Patterns of type  ‘T’ not matched:
             A
             B
 
diff --git a/testsuite/tests/pmcheck/complete_sigs/completesig10.stderr b/testsuite/tests/pmcheck/complete_sigs/completesig10.stderr
index 36b367068c89..dfdd29dec9c7 100644
--- a/testsuite/tests/pmcheck/complete_sigs/completesig10.stderr
+++ b/testsuite/tests/pmcheck/complete_sigs/completesig10.stderr
@@ -9,4 +9,4 @@ completesig10.hs:16:1: warning: [-Woverlapping-patterns (in -Wdefault)]
 
 completesig10.hs:20:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘m2’: Patterns not matched: A
+    In an equation for ‘m2’: Patterns of type  ‘T’ not matched: A
diff --git a/testsuite/tests/pmcheck/complete_sigs/completesig11.stderr b/testsuite/tests/pmcheck/complete_sigs/completesig11.stderr
index d7bf2f3079ae..1f02774757c3 100644
--- a/testsuite/tests/pmcheck/complete_sigs/completesig11.stderr
+++ b/testsuite/tests/pmcheck/complete_sigs/completesig11.stderr
@@ -1,4 +1,4 @@
 
 completesig11.hs:14:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘m1’: Patterns not matched: B
+    In an equation for ‘m1’: Patterns of type  ‘T’ not matched: B
diff --git a/testsuite/tests/pmcheck/should_compile/EmptyCase001.stderr b/testsuite/tests/pmcheck/should_compile/EmptyCase001.stderr
index c3c294b4e7d4..e3794c04054e 100644
--- a/testsuite/tests/pmcheck/should_compile/EmptyCase001.stderr
+++ b/testsuite/tests/pmcheck/should_compile/EmptyCase001.stderr
@@ -1,15 +1,15 @@
 
 EmptyCase001.hs:9:6: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: _ :: Int
+    In a case alternative: Patterns of type  ‘Int’ not matched: _
 
 EmptyCase001.hs:14:8: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In a case alternative:
-        Patterns not matched:
+        Patterns of type  ‘String’ not matched:
             []
             (_:_)
 
 EmptyCase001.hs:18:8: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: _ :: Char
+    In a case alternative: Patterns of type  ‘Char’ not matched: _
diff --git a/testsuite/tests/pmcheck/should_compile/EmptyCase002.stderr b/testsuite/tests/pmcheck/should_compile/EmptyCase002.stderr
index d6c39ec4f7c2..af9411c6a392 100644
--- a/testsuite/tests/pmcheck/should_compile/EmptyCase002.stderr
+++ b/testsuite/tests/pmcheck/should_compile/EmptyCase002.stderr
@@ -1,22 +1,25 @@
 
 EmptyCase002.hs:16:6: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: MkT _
+    In a case alternative: Patterns of type  ‘T’ not matched: MkT _
 
 EmptyCase002.hs:43:6: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In a case alternative:
-        Patterns not matched:
+        Patterns of type  ‘T1 B’ not matched:
             MkT1 B1
             MkT1 B2
 
 EmptyCase002.hs:47:6: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In a case alternative:
-        Patterns not matched:
+        Patterns of type  ‘T1 (E Int)’ not matched:
             MkT1 False
             MkT1 True
 
 EmptyCase002.hs:51:6: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: MkT1 (MkT2 (MkT1 D2))
+    In a case alternative:
+        Patterns of type  ‘T1
+                             (T2 (T1 (D (E Int) (E (E Int)))))’ not matched:
+            MkT1 (MkT2 (MkT1 D2))
diff --git a/testsuite/tests/pmcheck/should_compile/EmptyCase003.stderr b/testsuite/tests/pmcheck/should_compile/EmptyCase003.stderr
index d30cc52590cb..e9f6e27cd316 100644
--- a/testsuite/tests/pmcheck/should_compile/EmptyCase003.stderr
+++ b/testsuite/tests/pmcheck/should_compile/EmptyCase003.stderr
@@ -1,12 +1,12 @@
 
 EmptyCase003.hs:15:6: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: _ :: A a
+    In a case alternative: Patterns of type  ‘A a’ not matched: _
 
 EmptyCase003.hs:32:6: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: _ :: C a
+    In a case alternative: Patterns of type  ‘C a’ not matched: _
 
 EmptyCase003.hs:37:6: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: _ :: C Int
+    In a case alternative: Patterns of type  ‘C Int’ not matched: _
diff --git a/testsuite/tests/pmcheck/should_compile/EmptyCase004.stderr b/testsuite/tests/pmcheck/should_compile/EmptyCase004.stderr
index d807b5178926..c80a391d98b6 100644
--- a/testsuite/tests/pmcheck/should_compile/EmptyCase004.stderr
+++ b/testsuite/tests/pmcheck/should_compile/EmptyCase004.stderr
@@ -1,37 +1,37 @@
 
 EmptyCase004.hs:15:6: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: A2
+    In a case alternative: Patterns of type  ‘A Bool’ not matched: A2
 
 EmptyCase004.hs:19:6: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In a case alternative:
-        Patterns not matched:
+        Patterns of type  ‘A a’ not matched:
             A1
             A2
 
 EmptyCase004.hs:31:8: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: B1 _
+    In a case alternative: Patterns of type  ‘B a a’ not matched: B1 _
 
 EmptyCase004.hs:35:6: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In a case alternative:
-        Patterns not matched:
+        Patterns of type  ‘B a b’ not matched:
             B1 _
             B2
 
 EmptyCase004.hs:47:6: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In a case alternative:
-        Patterns not matched:
+        Patterns of type  ‘A a’ not matched:
             A1
             A2
 
 EmptyCase004.hs:50:9: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: B2
+    In a case alternative: Patterns of type  ‘B a b’ not matched: B2
 
 EmptyCase004.hs:51:9: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: B1 _
+    In a case alternative: Patterns of type  ‘B a b’ not matched: B1 _
diff --git a/testsuite/tests/pmcheck/should_compile/EmptyCase005.stderr b/testsuite/tests/pmcheck/should_compile/EmptyCase005.stderr
index 9c346b9c8b37..97514f67be85 100644
--- a/testsuite/tests/pmcheck/should_compile/EmptyCase005.stderr
+++ b/testsuite/tests/pmcheck/should_compile/EmptyCase005.stderr
@@ -1,33 +1,35 @@
 
 EmptyCase005.hs:24:8: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: Void3 _
+    In a case alternative:
+        Patterns of type  ‘Void3’ not matched: Void3 _
 
 EmptyCase005.hs:67:8: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In a case alternative:
-        Patterns not matched:
+        Patterns of type  ‘T ()’ not matched:
             T1
             T2
 
 EmptyCase005.hs:73:8: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In a case alternative:
-        Patterns not matched:
+        Patterns of type  ‘T Bool’ not matched:
             MkTBool False
             MkTBool True
 
 EmptyCase005.hs:79:8: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: MkTInt _
+    In a case alternative:
+        Patterns of type  ‘T Int’ not matched: MkTInt _
 
 EmptyCase005.hs:91:8: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In a case alternative:
-        Patterns not matched:
+        Patterns of type  ‘G Int’ not matched:
             MkV False
             MkV True
 
 EmptyCase005.hs:101:8: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: _ :: H Int
+    In a case alternative: Patterns of type  ‘H Int’ not matched: _
diff --git a/testsuite/tests/pmcheck/should_compile/EmptyCase006.stderr b/testsuite/tests/pmcheck/should_compile/EmptyCase006.stderr
index e47e1eea47b4..a34d0f5e5ed5 100644
--- a/testsuite/tests/pmcheck/should_compile/EmptyCase006.stderr
+++ b/testsuite/tests/pmcheck/should_compile/EmptyCase006.stderr
@@ -1,12 +1,13 @@
 
 EmptyCase006.hs:18:7: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: Foo1 MkGA1
+    In a case alternative:
+        Patterns of type  ‘Foo1 Int’ not matched: Foo1 MkGA1
 
 EmptyCase006.hs:26:7: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In a case alternative:
-        Patterns not matched:
+        Patterns of type  ‘Foo1 a’ not matched:
             Foo1 MkGA1
             Foo1 (MkGA2 _)
             Foo1 MkGA3
diff --git a/testsuite/tests/pmcheck/should_compile/EmptyCase007.stderr b/testsuite/tests/pmcheck/should_compile/EmptyCase007.stderr
index 0ab13ca32112..6b60fd76ad18 100644
--- a/testsuite/tests/pmcheck/should_compile/EmptyCase007.stderr
+++ b/testsuite/tests/pmcheck/should_compile/EmptyCase007.stderr
@@ -1,27 +1,31 @@
 
 EmptyCase007.hs:21:7: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: Foo2 _
+    In a case alternative:
+        Patterns of type  ‘Foo2 a’ not matched: Foo2 _
 
 EmptyCase007.hs:25:7: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: Foo2 _
+    In a case alternative:
+        Patterns of type  ‘Foo2 (a, a)’ not matched: Foo2 _
 
 EmptyCase007.hs:33:7: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: Foo2 (_, _)
+    In a case alternative:
+        Patterns of type  ‘Foo2 Int’ not matched: Foo2 (_, _)
 
 EmptyCase007.hs:37:7: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: Foo2 _
+    In a case alternative:
+        Patterns of type  ‘Foo2 Char’ not matched: Foo2 _
 
 EmptyCase007.hs:44:17: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: _ :: FA Char
+    In a case alternative: Patterns of type  ‘FA Char’ not matched: _
 
 EmptyCase007.hs:48:7: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In a case alternative:
-        Patterns not matched:
+        Patterns of type  ‘Foo2 [Int]’ not matched:
             Foo2 []
             Foo2 (_:_)
diff --git a/testsuite/tests/pmcheck/should_compile/EmptyCase008.stderr b/testsuite/tests/pmcheck/should_compile/EmptyCase008.stderr
index 0d21dbfaca9c..5563a599b6e6 100644
--- a/testsuite/tests/pmcheck/should_compile/EmptyCase008.stderr
+++ b/testsuite/tests/pmcheck/should_compile/EmptyCase008.stderr
@@ -2,18 +2,21 @@
 EmptyCase008.hs:17:7: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In a case alternative:
-        Patterns not matched:
+        Patterns of type  ‘Foo3 Int’ not matched:
             Foo3 (MkDA1 _)
             Foo3 MkDA2
 
 EmptyCase008.hs:21:7: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: Foo3 _
+    In a case alternative:
+        Patterns of type  ‘Foo3 a’ not matched: Foo3 _
 
 EmptyCase008.hs:40:7: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: Foo4 MkDB1
+    In a case alternative:
+        Patterns of type  ‘Foo4 Int ()’ not matched: Foo4 MkDB1
 
 EmptyCase008.hs:48:7: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: Foo4 _
+    In a case alternative:
+        Patterns of type  ‘Foo4 a b’ not matched: Foo4 _
diff --git a/testsuite/tests/pmcheck/should_compile/EmptyCase009.stderr b/testsuite/tests/pmcheck/should_compile/EmptyCase009.stderr
index de68e6dae8aa..cd10631c6c1f 100644
--- a/testsuite/tests/pmcheck/should_compile/EmptyCase009.stderr
+++ b/testsuite/tests/pmcheck/should_compile/EmptyCase009.stderr
@@ -1,12 +1,14 @@
 
 EmptyCase009.hs:21:9: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: Bar _
+    In a case alternative: Patterns of type  ‘Bar f’ not matched: Bar _
 
 EmptyCase009.hs:33:7: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: Bar MkDB2_u
+    In a case alternative:
+        Patterns of type  ‘Bar (DB ())’ not matched: Bar MkDB2_u
 
 EmptyCase009.hs:42:7: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: Bar MkGB3
+    In a case alternative:
+        Patterns of type  ‘Bar GB’ not matched: Bar MkGB3
diff --git a/testsuite/tests/pmcheck/should_compile/EmptyCase010.stderr b/testsuite/tests/pmcheck/should_compile/EmptyCase010.stderr
index 4b374a0c24bf..9b4c65e4ac90 100644
--- a/testsuite/tests/pmcheck/should_compile/EmptyCase010.stderr
+++ b/testsuite/tests/pmcheck/should_compile/EmptyCase010.stderr
@@ -2,41 +2,46 @@
 EmptyCase010.hs:24:7: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In a case alternative:
-        Patterns not matched:
+        Patterns of type  ‘Baz GC a’ not matched:
             Baz MkGC1
             Baz (MkGC2 _)
 
 EmptyCase010.hs:28:7: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: Baz MkGC1
+    In a case alternative:
+        Patterns of type  ‘Baz GC 'T1’ not matched: Baz MkGC1
 
 EmptyCase010.hs:37:7: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In a case alternative:
-        Patterns not matched:
+        Patterns of type  ‘Baz GD Maybe’ not matched:
             Baz MkGD1
             Baz MkGD3
 
 EmptyCase010.hs:41:9: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: Baz MkGD3
+    In a case alternative:
+        Patterns of type  ‘Baz GD (Either Int)’ not matched: Baz MkGD3
 
 EmptyCase010.hs:45:7: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In a case alternative:
-        Patterns not matched:
+        Patterns of type  ‘Baz GD f’ not matched:
             Baz MkGD1
             Baz MkGD2
             Baz MkGD3
 
 EmptyCase010.hs:57:7: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: Baz _
+    In a case alternative:
+        Patterns of type  ‘Baz (DC ()) a’ not matched: Baz _
 
 EmptyCase010.hs:69:7: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: Baz MkDC2
+    In a case alternative:
+        Patterns of type  ‘Baz (DC Bool) [Int]’ not matched: Baz MkDC2
 
 EmptyCase010.hs:73:9: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: Baz _
+    In a case alternative:
+        Patterns of type  ‘Baz f a’ not matched: Baz _
diff --git a/testsuite/tests/pmcheck/should_compile/T10746.stderr b/testsuite/tests/pmcheck/should_compile/T10746.stderr
index deb25953e208..fab96e5fde91 100644
--- a/testsuite/tests/pmcheck/should_compile/T10746.stderr
+++ b/testsuite/tests/pmcheck/should_compile/T10746.stderr
@@ -2,6 +2,6 @@
 T10746.hs:9:10: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In a case alternative:
-        Patterns not matched:
+        Patterns of type  ‘Bool’ not matched:
             False
             True
diff --git a/testsuite/tests/pmcheck/should_compile/T11336b.stderr b/testsuite/tests/pmcheck/should_compile/T11336b.stderr
index f5fc88402ddc..4a6547d50956 100644
--- a/testsuite/tests/pmcheck/should_compile/T11336b.stderr
+++ b/testsuite/tests/pmcheck/should_compile/T11336b.stderr
@@ -1,4 +1,5 @@
 
 T11336b.hs:25:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘fun’: Patterns not matched: Proxy
+    In an equation for ‘fun’:
+        Patterns of type  ‘Proxy a’ not matched: Proxy
diff --git a/testsuite/tests/pmcheck/should_compile/T11822.stderr b/testsuite/tests/pmcheck/should_compile/T11822.stderr
index 569cc74e9964..e7472626bf42 100644
--- a/testsuite/tests/pmcheck/should_compile/T11822.stderr
+++ b/testsuite/tests/pmcheck/should_compile/T11822.stderr
@@ -9,7 +9,8 @@ T11822.hs:33:1: warning:
 T11822.hs:33:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In an equation for ‘mkTreeNode’:
-        Patterns not matched:
+        Patterns of type  ‘prefix’, ‘Seq SiblingDependencies’,
+                          ‘Set prefix’, ‘Depth’ not matched:
             _ (Data.Sequence.Internal.Seq Data.Sequence.Internal.EmptyT)
             (Data.Set.Internal.Bin _ _ _ _) (Depth _)
             _ (Data.Sequence.Internal.Seq Data.Sequence.Internal.EmptyT)
diff --git a/testsuite/tests/pmcheck/should_compile/T15305.stderr b/testsuite/tests/pmcheck/should_compile/T15305.stderr
index e760a2c884c5..de682464b72f 100644
--- a/testsuite/tests/pmcheck/should_compile/T15305.stderr
+++ b/testsuite/tests/pmcheck/should_compile/T15305.stderr
@@ -1,4 +1,5 @@
 
 T15305.hs:48:23: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: MkAbyss _
+    In a case alternative:
+        Patterns of type  ‘Abyss’ not matched: MkAbyss _
diff --git a/testsuite/tests/pmcheck/should_compile/T15450.stderr b/testsuite/tests/pmcheck/should_compile/T15450.stderr
index e9a320fb3cef..2ef488970d24 100644
--- a/testsuite/tests/pmcheck/should_compile/T15450.stderr
+++ b/testsuite/tests/pmcheck/should_compile/T15450.stderr
@@ -2,10 +2,10 @@
 T15450.hs:6:7: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In a case alternative:
-        Patterns not matched:
+        Patterns of type  ‘Bool’ not matched:
             False
             True
 
 T15450.hs:9:7: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: False
+    In a case alternative: Patterns of type  ‘Bool’ not matched: False
diff --git a/testsuite/tests/pmcheck/should_compile/T17218.stderr b/testsuite/tests/pmcheck/should_compile/T17218.stderr
index 25a74b536cf4..a8ac1b9ab8a2 100644
--- a/testsuite/tests/pmcheck/should_compile/T17218.stderr
+++ b/testsuite/tests/pmcheck/should_compile/T17218.stderr
@@ -1,4 +1,4 @@
 
 T17218.hs:11:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘f’: Patterns not matched: P
+    In an equation for ‘f’: Patterns of type  ‘T’ not matched: P
diff --git a/testsuite/tests/pmcheck/should_compile/T17729.stderr b/testsuite/tests/pmcheck/should_compile/T17729.stderr
index ac4f31fcfa28..edc7900388f8 100644
--- a/testsuite/tests/pmcheck/should_compile/T17729.stderr
+++ b/testsuite/tests/pmcheck/should_compile/T17729.stderr
@@ -1,4 +1,5 @@
 
 T17729.hs:5:17: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: ((Just _), ())
+    In a case alternative:
+        Patterns of type  ‘(Maybe a, ())’ not matched: ((Just _), ())
diff --git a/testsuite/tests/pmcheck/should_compile/T17836b.stderr b/testsuite/tests/pmcheck/should_compile/T17836b.stderr
index cad78da8da49..ba590aaf85ad 100644
--- a/testsuite/tests/pmcheck/should_compile/T17836b.stderr
+++ b/testsuite/tests/pmcheck/should_compile/T17836b.stderr
@@ -2,7 +2,7 @@
 T17836b.hs:11:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In an equation for ‘massive’:
-        Patterns not matched:
+        Patterns of type  ‘T recty’ not matched:
             T _
             P (T _)
             P (P (T _))
diff --git a/testsuite/tests/pmcheck/should_compile/T17977.stderr b/testsuite/tests/pmcheck/should_compile/T17977.stderr
index 43aaa6f735a4..f9cb656f4293 100644
--- a/testsuite/tests/pmcheck/should_compile/T17977.stderr
+++ b/testsuite/tests/pmcheck/should_compile/T17977.stderr
@@ -2,7 +2,8 @@
 T17977.hs:31:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In an equation for ‘f’:
-        Patterns not matched:
+        Patterns of type  ‘SNat m’, ‘SNat n’, ‘SNat o’,
+                          ‘R m n o’ not matched:
             SZ SZ SZ _
             SZ SZ (SS _) _
             SZ (SS _) SZ _
diff --git a/testsuite/tests/pmcheck/should_compile/T18572.stderr b/testsuite/tests/pmcheck/should_compile/T18572.stderr
index 15d9f7c5b50a..a5d14d5c33d0 100644
--- a/testsuite/tests/pmcheck/should_compile/T18572.stderr
+++ b/testsuite/tests/pmcheck/should_compile/T18572.stderr
@@ -13,4 +13,5 @@ T18572.hs:12:1: warning: [-Woverlapping-patterns (in -Wdefault)]
 
 T18572.hs:12:1: warning: [-Wincomplete-uni-patterns]
     Pattern match(es) are non-exhaustive
-    In a pattern binding: Patterns not matched: SFalse
+    In a pattern binding:
+        Patterns of type  ‘SBool 'False’ not matched: SFalse
diff --git a/testsuite/tests/pmcheck/should_compile/T18670.stderr b/testsuite/tests/pmcheck/should_compile/T18670.stderr
index 6b7f6cc20798..4929374740f9 100644
--- a/testsuite/tests/pmcheck/should_compile/T18670.stderr
+++ b/testsuite/tests/pmcheck/should_compile/T18670.stderr
@@ -1,4 +1,5 @@
 
 T18670.hs:16:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘f’: Patterns not matched: TBool _
+    In an equation for ‘f’:
+        Patterns of type  ‘T a’, ‘a :~: Int’ not matched: TBool _
diff --git a/testsuite/tests/pmcheck/should_compile/T18708.stderr b/testsuite/tests/pmcheck/should_compile/T18708.stderr
index 5949d929702a..ac838c365090 100644
--- a/testsuite/tests/pmcheck/should_compile/T18708.stderr
+++ b/testsuite/tests/pmcheck/should_compile/T18708.stderr
@@ -2,4 +2,4 @@
 T18708.hs:18:3: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In a case alternative:
-        Patterns not matched: p where p is not one of {"y"}
+        Patterns of type  ‘Text’ not matched: p where p is not one of {"y"}
diff --git a/testsuite/tests/pmcheck/should_compile/T18932.hs b/testsuite/tests/pmcheck/should_compile/T18932.hs
new file mode 100644
index 000000000000..ada977a23728
--- /dev/null
+++ b/testsuite/tests/pmcheck/should_compile/T18932.hs
@@ -0,0 +1,14 @@
+{-# OPTIONS_GHC -fforce-recomp -Wall -Wno-missing-signatures #-}
+
+module T18932 where
+
+import Data.Void
+
+data T a = MkT1 Int | MkT2 !a
+
+f (MkT1 x) = x
+f (MkT2 y) = absurd y
+
+f' (MkT1 x) = x
+
+g (MkT1 x) (MkT1 _) (MkT1 _) = x
diff --git a/testsuite/tests/pmcheck/should_compile/T18932.stderr b/testsuite/tests/pmcheck/should_compile/T18932.stderr
new file mode 100644
index 000000000000..7f6d813adaba
--- /dev/null
+++ b/testsuite/tests/pmcheck/should_compile/T18932.stderr
@@ -0,0 +1,19 @@
+
+T18932.hs:10:1: warning: [-Woverlapping-patterns (in -Wdefault)]
+    Pattern match is redundant
+    In an equation for ‘f’: f (MkT2 y) = ...
+
+T18932.hs:12:1: warning: [-Wincomplete-patterns (in -Wextra)]
+    Pattern match(es) are non-exhaustive
+    In an equation for ‘f'’:
+        Patterns of type  ‘T a’ not matched: MkT2 _
+
+T18932.hs:14:1: warning: [-Wincomplete-patterns (in -Wextra)]
+    Pattern match(es) are non-exhaustive
+    In an equation for ‘g’:
+        Patterns of type  ‘T a’, ‘T a’, ‘T a’ not matched:
+            (MkT2 _) (MkT1 _) (MkT1 _)
+            (MkT2 _) (MkT1 _) (MkT2 _)
+            (MkT2 _) (MkT2 _) (MkT1 _)
+            (MkT2 _) (MkT2 _) (MkT2 _)
+            ...
diff --git a/testsuite/tests/pmcheck/should_compile/T2204.stderr b/testsuite/tests/pmcheck/should_compile/T2204.stderr
index 7b5a2b52f7c9..82988e669ca5 100644
--- a/testsuite/tests/pmcheck/should_compile/T2204.stderr
+++ b/testsuite/tests/pmcheck/should_compile/T2204.stderr
@@ -2,7 +2,7 @@
 T2204.hs:6:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In an equation for ‘f’:
-        Patterns not matched:
+        Patterns of type  ‘String’ not matched:
             []
             [p] where p is not one of {'0'}
             (p:_:_) where p is not one of {'0'}
@@ -12,4 +12,4 @@ T2204.hs:6:1: warning: [-Wincomplete-patterns (in -Wextra)]
 T2204.hs:9:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In an equation for ‘g’:
-        Patterns not matched: p where p is not one of {0}
+        Patterns of type  ‘Int’ not matched: p where p is not one of {0}
diff --git a/testsuite/tests/pmcheck/should_compile/T9951b.stderr b/testsuite/tests/pmcheck/should_compile/T9951b.stderr
index c9536b3160cf..65198db65fca 100644
--- a/testsuite/tests/pmcheck/should_compile/T9951b.stderr
+++ b/testsuite/tests/pmcheck/should_compile/T9951b.stderr
@@ -2,7 +2,7 @@
 T9951b.hs:7:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In an equation for ‘f’:
-        Patterns not matched:
+        Patterns of type  ‘String’ not matched:
             []
             [p] where p is not one of {'a'}
             (p:_:_) where p is not one of {'a'}
diff --git a/testsuite/tests/pmcheck/should_compile/TooManyDeltas.stderr b/testsuite/tests/pmcheck/should_compile/TooManyDeltas.stderr
index 2fe93d32d917..e8c992b52784 100644
--- a/testsuite/tests/pmcheck/should_compile/TooManyDeltas.stderr
+++ b/testsuite/tests/pmcheck/should_compile/TooManyDeltas.stderr
@@ -9,7 +9,7 @@ TooManyDeltas.hs:14:1: warning:
 TooManyDeltas.hs:14:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In an equation for ‘f’:
-        Patterns not matched:
+        Patterns of type  ‘T’, ‘T’ not matched:
             A A
             A B
             B A
diff --git a/testsuite/tests/pmcheck/should_compile/all.T b/testsuite/tests/pmcheck/should_compile/all.T
index e7f3667ea736..40b59b2fd364 100644
--- a/testsuite/tests/pmcheck/should_compile/all.T
+++ b/testsuite/tests/pmcheck/should_compile/all.T
@@ -158,6 +158,8 @@ test('T18670', normal, compile,
      ['-fwarn-incomplete-patterns -fwarn-overlapping-patterns'])
 test('T18708', normal, compile,
      ['-fwarn-incomplete-patterns -fwarn-overlapping-patterns'])
+test('T18932', normal, compile,
+     ['-fwarn-incomplete-patterns -fwarn-overlapping-patterns'])
 
 # Other tests
 test('pmc001', [], compile,
diff --git a/testsuite/tests/pmcheck/should_compile/pmc001.stderr b/testsuite/tests/pmcheck/should_compile/pmc001.stderr
index 9cd2e255ce7c..6f154447771d 100644
--- a/testsuite/tests/pmcheck/should_compile/pmc001.stderr
+++ b/testsuite/tests/pmcheck/should_compile/pmc001.stderr
@@ -2,7 +2,7 @@
 pmc001.hs:14:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In an equation for ‘f’:
-        Patterns not matched:
+        Patterns of type  ‘T [a]’, ‘T [a]’ not matched:
             MkT1 MkT3
             (MkT2 _) MkT3
             MkT3 MkT1
@@ -11,7 +11,7 @@ pmc001.hs:14:1: warning: [-Wincomplete-patterns (in -Wextra)]
 pmc001.hs:19:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In an equation for ‘g’:
-        Patterns not matched:
+        Patterns of type  ‘T [a]’, ‘T [a]’ not matched:
             MkT1 MkT3
             (MkT2 _) MkT3
             MkT3 MkT1
diff --git a/testsuite/tests/pmcheck/should_compile/pmc005.stderr b/testsuite/tests/pmcheck/should_compile/pmc005.stderr
index b7b9cac5f3b8..8cc9eaffcb94 100644
--- a/testsuite/tests/pmcheck/should_compile/pmc005.stderr
+++ b/testsuite/tests/pmcheck/should_compile/pmc005.stderr
@@ -1,7 +1,8 @@
 
 pmc005.hs:11:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘foo’: Patterns not matched: TBool TBool
+    In an equation for ‘foo’:
+        Patterns of type  ‘T c’, ‘T c’ not matched: TBool TBool
 
 pmc005.hs:12:1: warning: [-Woverlapping-patterns (in -Wdefault)]
     Pattern match has inaccessible right hand side
diff --git a/testsuite/tests/pmcheck/should_compile/pmc007.stderr b/testsuite/tests/pmcheck/should_compile/pmc007.stderr
index 9a3fe6efdc68..1593f85f7fdc 100644
--- a/testsuite/tests/pmcheck/should_compile/pmc007.stderr
+++ b/testsuite/tests/pmcheck/should_compile/pmc007.stderr
@@ -2,12 +2,13 @@
 pmc007.hs:7:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In an equation for ‘f’:
-        Patterns not matched: p where p is not one of {"ab", "ac"}
+        Patterns of type  ‘a’ not matched:
+            p where p is not one of {"ab", "ac"}
 
 pmc007.hs:12:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In an equation for ‘g’:
-        Patterns not matched:
+        Patterns of type  ‘String’ not matched:
             []
             [p] where p is not one of {'a'}
             (p:_:_) where p is not one of {'a'}
@@ -17,7 +18,7 @@ pmc007.hs:12:1: warning: [-Wincomplete-patterns (in -Wextra)]
 pmc007.hs:18:11: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
     In a case alternative:
-        Patterns not matched:
+        Patterns of type  ‘String’ not matched:
             []
             [p] where p is not one of {'a'}
             (p:_:_) where p is not one of {'a'}
diff --git a/testsuite/tests/pmcheck/should_compile/pmc009.stderr b/testsuite/tests/pmcheck/should_compile/pmc009.stderr
index 9614f2497bce..6f1849a25fe3 100644
--- a/testsuite/tests/pmcheck/should_compile/pmc009.stderr
+++ b/testsuite/tests/pmcheck/should_compile/pmc009.stderr
@@ -1,4 +1,6 @@
 
 pmc009.hs:6:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘addPatSynSelector’: Patterns not matched: L _ _
+    In an equation for ‘addPatSynSelector’:
+        Patterns of type  ‘GenLocated l (HsBindLR idL idR)’ not matched:
+            L _ _
diff --git a/testsuite/tests/warnings/should_fail/WerrorFail.stderr b/testsuite/tests/warnings/should_fail/WerrorFail.stderr
index 8b96c483f7e4..03e93567bcea 100644
--- a/testsuite/tests/warnings/should_fail/WerrorFail.stderr
+++ b/testsuite/tests/warnings/should_fail/WerrorFail.stderr
@@ -1,4 +1,5 @@
 
 WerrorFail.hs:6:1: error: [-Wincomplete-patterns (in -Wextra), -Werror=incomplete-patterns]
     Pattern match(es) are non-exhaustive
-    In an equation for ‘foo’: Patterns not matched: Just _
+    In an equation for ‘foo’:
+        Patterns of type  ‘Maybe a’ not matched: Just _
diff --git a/testsuite/tests/warnings/should_fail/WerrorFail2.stderr b/testsuite/tests/warnings/should_fail/WerrorFail2.stderr
index afbcd6137496..66e99b9bbb83 100644
--- a/testsuite/tests/warnings/should_fail/WerrorFail2.stderr
+++ b/testsuite/tests/warnings/should_fail/WerrorFail2.stderr
@@ -4,7 +4,7 @@ WerrorFail2.hs:15:1: warning: [-Wmissing-signatures (in -Wall)]
 
 WerrorFail2.hs:15:10: error: [-Wincomplete-patterns (in -Wextra), -Werror=incomplete-patterns]
     Pattern match(es) are non-exhaustive
-    In a case alternative: Patterns not matched: C2 _
+    In a case alternative: Patterns of type  ‘S’ not matched: C2 _
 
 WerrorFail2.hs:19:1: warning: [-Wmissing-signatures (in -Wall)]
     Top-level binding with no type signature: printRec :: IO ()
-- 
GitLab