[commit: ghc] ghc-8.0: Annotate `[-Wredundant-constraints]` in warnings (re #10752) (94b2681)

git at git.haskell.org git at git.haskell.org
Sun Feb 28 18:40:28 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : ghc-8.0
Link       : http://ghc.haskell.org/trac/ghc/changeset/94b2681507db793359b101b945c710e504971556/ghc

>---------------------------------------------------------------

commit 94b2681507db793359b101b945c710e504971556
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Sat Feb 27 18:26:32 2016 +0100

    Annotate `[-Wredundant-constraints]` in warnings (re #10752)
    
    This was missed in bb5afd3c274011c5ea302210b4c290ec1f83209c
    
    (cherry picked from commit 82f200b74ac1ea8c5593e2909c0033eb251eeaf2)


>---------------------------------------------------------------

94b2681507db793359b101b945c710e504971556
 compiler/typecheck/TcErrors.hs                         | 4 ++--
 testsuite/tests/typecheck/should_compile/T10632.stderr | 2 +-
 testsuite/tests/typecheck/should_compile/T9939.stderr  | 8 ++++----
 testsuite/tests/warnings/should_compile/PluralS.stderr | 4 ++--
 4 files changed, 9 insertions(+), 9 deletions(-)

diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs
index 63def64..ee2ea0f 100644
--- a/compiler/typecheck/TcErrors.hs
+++ b/compiler/typecheck/TcErrors.hs
@@ -336,13 +336,13 @@ warnRedundantConstraints ctxt env info ev_vars
    addErrCtxt (text "In" <+> ppr info) $
    do { env <- getLclEnv
       ; msg <- mkErrorReport ctxt env (important doc)
-      ; reportWarning NoReason msg }
+      ; reportWarning (Reason Opt_WarnRedundantConstraints) msg }
 
  | otherwise  -- But for InstSkol there already *is* a surrounding
               -- "In the instance declaration for Eq [a]" context
               -- and we don't want to say it twice. Seems a bit ad-hoc
  = do { msg <- mkErrorReport ctxt env (important doc)
-      ; reportWarning NoReason msg }
+      ; reportWarning (Reason Opt_WarnRedundantConstraints) msg }
  where
    doc = text "Redundant constraint" <> plural redundant_evs <> colon
          <+> pprEvVarTheta redundant_evs
diff --git a/testsuite/tests/typecheck/should_compile/T10632.stderr b/testsuite/tests/typecheck/should_compile/T10632.stderr
index 8e72f42..211972d 100644
--- a/testsuite/tests/typecheck/should_compile/T10632.stderr
+++ b/testsuite/tests/typecheck/should_compile/T10632.stderr
@@ -1,5 +1,5 @@
 
-T10632.hs:3:1: warning:
+T10632.hs:3:1: warning: [-Wredundant-constraints]
     • Redundant constraint: ?file1::String
     • In the type signature for:
            f :: (?file1::String) => IO ()
diff --git a/testsuite/tests/typecheck/should_compile/T9939.stderr b/testsuite/tests/typecheck/should_compile/T9939.stderr
index 106335e..a10066b 100644
--- a/testsuite/tests/typecheck/should_compile/T9939.stderr
+++ b/testsuite/tests/typecheck/should_compile/T9939.stderr
@@ -1,20 +1,20 @@
 
-T9939.hs:5:1: warning:
+T9939.hs:5:1: warning: [-Wredundant-constraints]
     • Redundant constraint: Eq a
     • In the type signature for:
            f1 :: (Eq a, Ord a) => a -> a -> Bool
 
-T9939.hs:9:1: warning:
+T9939.hs:9:1: warning: [-Wredundant-constraints]
     • Redundant constraint: Eq a
     • In the type signature for:
            f2 :: (Eq a, Ord a) => a -> a -> Bool
 
-T9939.hs:13:1: warning:
+T9939.hs:13:1: warning: [-Wredundant-constraints]
     • Redundant constraint: Eq b
     • In the type signature for:
            f3 :: (Eq a, a ~ b, Eq b) => a -> b -> Bool
 
-T9939.hs:20:1: warning:
+T9939.hs:20:1: warning: [-Wredundant-constraints]
     • Redundant constraint: Eq a
     • In the type signature for:
            f4 :: (Eq a, Eq b) => a -> b -> Equal a b -> Bool
diff --git a/testsuite/tests/warnings/should_compile/PluralS.stderr b/testsuite/tests/warnings/should_compile/PluralS.stderr
index a06ab5e..9289a0b 100644
--- a/testsuite/tests/warnings/should_compile/PluralS.stderr
+++ b/testsuite/tests/warnings/should_compile/PluralS.stderr
@@ -15,12 +15,12 @@ PluralS.hs:17:29: warning: [-Wtype-defaults (in -Wall)]
       In an equation for ‘defaultingNumAndShow’:
           defaultingNumAndShow = show 123
 
-PluralS.hs:23:1: warning:
+PluralS.hs:23:1: warning: [-Wredundant-constraints]
     • Redundant constraint: Num a
     • In the type signature for:
            redundantNum :: (Num a, Num a) => a
 
-PluralS.hs:26:1: warning:
+PluralS.hs:26:1: warning: [-Wredundant-constraints]
     • Redundant constraints: (Show a, Num a, Eq a, Eq a)
     • In the type signature for:
            redundantMultiple :: (Num a, Show a, Num a, Eq a, Eq a) => a



More information about the ghc-commits mailing list