[commit: ghc] ghc-8.0: Implement -Wunrecognised-warning-flag (bbd9356)

git at git.haskell.org git at git.haskell.org
Mon Jan 25 21:41:38 UTC 2016


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

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

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

commit bbd935606422ca884a680afa806164d851fd5060
Author: Ben Gamari <bgamari.foss at gmail.com>
Date:   Mon Jan 25 17:14:49 2016 +0100

    Implement -Wunrecognised-warning-flag
    
    This allows the user to avoid warnings for warning flags that GHC
    doesn't recognise. See #11429 for details..
    
    Test Plan: Validate with T11429[abc] tests
    
    Reviewers: austin, hvr
    
    Reviewed By: hvr
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D1830
    
    GHC Trac Issues: #11429


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

bbd935606422ca884a680afa806164d851fd5060
 compiler/main/DynFlags.hs                          | 22 ++++++++++++++++++----
 docs/users_guide/using-warnings.rst                |  8 ++++++++
 .../{plugins/frontend01.hs => driver/T11429a.hs}   |  1 +
 testsuite/tests/driver/T11429a.stderr              |  2 ++
 .../{plugins/frontend01.hs => driver/T11429b.hs}   |  1 +
 .../{plugins/frontend01.hs => driver/T11429c.hs}   |  1 +
 testsuite/tests/driver/T11429c.stderr              |  5 +++++
 testsuite/tests/driver/all.T                       |  4 ++++
 utils/mkUserGuidePart/Options/Warnings.hs          |  7 +++++++
 9 files changed, 47 insertions(+), 4 deletions(-)

diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 7ce2a3d..3dce446 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -600,6 +600,7 @@ data WarningFlag =
    | Opt_WarnNonCanonicalMonadFailInstances -- since 8.0
    | Opt_WarnNonCanonicalMonoidInstances  -- since 8.0
    | Opt_WarnMissingPatSynSigs            -- since 8.0
+   | Opt_WarnUnrecognisedWarningFlags     -- since 8.0
    deriving (Eq, Show, Enum)
 
 data Language = Haskell98 | Haskell2010
@@ -2749,7 +2750,8 @@ dynamic_flags = [
  ++ map (mkFlag turnOff "XNo"       unSetExtensionFlag) xFlags
  ++ map (mkFlag turnOn  "X"         setLanguage       ) languageFlags
  ++ map (mkFlag turnOn  "X"         setSafeHaskell    ) safeHaskellFlags
- ++ [ defFlag "XGenerics"
+ ++ [ unrecognisedWarning
+    , defFlag "XGenerics"
         (NoArg (deprecate $
                   "it does nothing; look into -XDefaultSignatures " ++
                   "and -XDeriveGeneric for generic programming support."))
@@ -2758,6 +2760,16 @@ dynamic_flags = [
                   "it does nothing; look into -XDefaultSignatures and " ++
                   "-XDeriveGeneric for generic programming support.")) ]
 
+-- | This is where we handle unrecognised warning flags. We only issue a warning
+-- if -Wunrecognised-warning-flags is set. See Trac #11429 for context.
+unrecognisedWarning :: Flag (CmdLineP DynFlags)
+unrecognisedWarning = defFlag "W" (Prefix action)
+  where
+    action :: String -> EwM (CmdLineP DynFlags) ()
+    action flag = do
+      f <- wopt Opt_WarnUnrecognisedWarningFlags <$> liftEwM getCmdLineState
+      when f $ addWarn $ "unrecognised warning flag: -W"++flag
+
 -- See Note [Supporting CLI completion]
 package_flags :: [Flag (CmdLineP DynFlags)]
 package_flags = [
@@ -2970,7 +2982,8 @@ wWarningFlags = [
   flagSpec "unused-top-binds"            Opt_WarnUnusedTopBinds,
   flagSpec "warnings-deprecations"       Opt_WarnWarningsDeprecations,
   flagSpec "wrong-do-bind"               Opt_WarnWrongDoBind,
-  flagSpec "missing-pat-syn-sigs"        Opt_WarnMissingPatSynSigs]
+  flagSpec "missing-pat-syn-sigs"        Opt_WarnMissingPatSynSigs,
+  flagSpec "unrecognised-warning-flags"  Opt_WarnUnrecognisedWarningFlags ]
 
 -- | These @-\<blah\>@ flags can all be reversed with @-no-\<blah\>@
 negatableFlags :: [FlagSpec GeneralFlag]
@@ -3469,7 +3482,7 @@ optLevelFlags -- see Note [Documenting optimisation flags]
 -- please remember to update the User's Guide. The relevant file is:
 --
 --  * utils/mkUserGuidePart/
---  * docs/users_guide/using.rst
+--  * docs/users_guide/using-warnings.rst
 
 -- | Warnings enabled unless specified otherwise
 standardWarnings :: [WarningFlag]
@@ -3492,7 +3505,8 @@ standardWarnings -- see Note [Documenting warning flags]
         Opt_WarnInlineRuleShadowing,
         Opt_WarnAlternativeLayoutRuleTransitional,
         Opt_WarnUnsupportedLlvmVersion,
-        Opt_WarnTabs
+        Opt_WarnTabs,
+        Opt_WarnUnrecognisedWarningFlags
       ]
 
 -- | Things you get with -W
diff --git a/docs/users_guide/using-warnings.rst b/docs/users_guide/using-warnings.rst
index 4f9a741..10fc9df 100644
--- a/docs/users_guide/using-warnings.rst
+++ b/docs/users_guide/using-warnings.rst
@@ -31,6 +31,7 @@ generally likely to indicate bugs in your program. These are:
     * :ghc-flag:`-Winline-rule-shadowing`
     * :ghc-flag:`-Wunsupported-llvm-version`
     * :ghc-flag:`-Wtabs`
+    * :ghc-flag:`-Wunrecognised-warning-flags`
 
 The following flags are simple ways to select standard "packages" of warnings:
 
@@ -106,6 +107,13 @@ command line. For backwards compatibility with GHC versions prior to 8.0,
 all these warnings can still be controlled with ``-f(no-)warn-*`` instead
 of ``-W(no-)*``.
 
+.. ghc-flag:: -Wunrecognised-warning-flags
+
+    Enables warnings when the compiler encounters a ``-W...`` flag that is not
+    recognised.
+
+    This warning is on by default.
+
 .. ghc-flag:: -Wtyped-holes
 
     Determines whether the compiler reports typed holes warnings. Has no
diff --git a/testsuite/tests/plugins/frontend01.hs b/testsuite/tests/driver/T11429a.hs
similarity index 68%
copy from testsuite/tests/plugins/frontend01.hs
copy to testsuite/tests/driver/T11429a.hs
index db01456..c81fb82 100644
--- a/testsuite/tests/plugins/frontend01.hs
+++ b/testsuite/tests/driver/T11429a.hs
@@ -1 +1,2 @@
+main :: IO ()
 main = putStrLn "hello world"
diff --git a/testsuite/tests/driver/T11429a.stderr b/testsuite/tests/driver/T11429a.stderr
new file mode 100644
index 0000000..c52b89e
--- /dev/null
+++ b/testsuite/tests/driver/T11429a.stderr
@@ -0,0 +1,2 @@
+
+on the commandline: warning: unrecognised warning flag: -Wfoobar
diff --git a/testsuite/tests/plugins/frontend01.hs b/testsuite/tests/driver/T11429b.hs
similarity index 68%
copy from testsuite/tests/plugins/frontend01.hs
copy to testsuite/tests/driver/T11429b.hs
index db01456..c81fb82 100644
--- a/testsuite/tests/plugins/frontend01.hs
+++ b/testsuite/tests/driver/T11429b.hs
@@ -1 +1,2 @@
+main :: IO ()
 main = putStrLn "hello world"
diff --git a/testsuite/tests/plugins/frontend01.hs b/testsuite/tests/driver/T11429c.hs
similarity index 68%
copy from testsuite/tests/plugins/frontend01.hs
copy to testsuite/tests/driver/T11429c.hs
index db01456..c81fb82 100644
--- a/testsuite/tests/plugins/frontend01.hs
+++ b/testsuite/tests/driver/T11429c.hs
@@ -1 +1,2 @@
+main :: IO ()
 main = putStrLn "hello world"
diff --git a/testsuite/tests/driver/T11429c.stderr b/testsuite/tests/driver/T11429c.stderr
new file mode 100644
index 0000000..19e269b
--- /dev/null
+++ b/testsuite/tests/driver/T11429c.stderr
@@ -0,0 +1,5 @@
+
+<no location info>: error: 
+Failing due to -Werror.
+
+on the commandline: warning: unrecognised warning flag: -Wfoobar
diff --git a/testsuite/tests/driver/all.T b/testsuite/tests/driver/all.T
index 69d18d9..5a19366 100644
--- a/testsuite/tests/driver/all.T
+++ b/testsuite/tests/driver/all.T
@@ -467,3 +467,7 @@ test('T10970a', normal, compile_and_run, [''])
 test('T4931', normal, compile_and_run, [''])
 test('T11182', normal, compile_and_run, [''])
 test('T11381', normal, compile_fail, [''])
+test('T11429a', normal, compile, ['-Wunrecognised-warning-flags -Wfoobar'])
+test('T11429b', normal, compile, ['-Wno-unrecognised-warning-flags -Wfoobar'])
+test('T11429c', normal, compile_fail, ['-Wunrecognised-warning-flags -Werror -Wfoobar'])
+
diff --git a/utils/mkUserGuidePart/Options/Warnings.hs b/utils/mkUserGuidePart/Options/Warnings.hs
index 3c69de7..256d01f 100644
--- a/utils/mkUserGuidePart/Options/Warnings.hs
+++ b/utils/mkUserGuidePart/Options/Warnings.hs
@@ -36,6 +36,13 @@ warningsOptions =
          , flagType = DynamicFlag
          , flagReverse = "-Werror"
          }
+  , flag { flagName = "-Wunrecognised-warning-flags"
+         , flagDescription =
+           "throw a warning when an unreconised ``-W...`` flag is "++
+           "encountered on the command line."
+         , flagType = DynamicFlag
+         , flagReverse = "-Wno-unrecognised-warning-flags"
+         }
   , flag { flagName = "-fdefer-type-errors"
          , flagDescription =
            "Turn type errors into warnings, :ref:`deferring the error until "++



More information about the ghc-commits mailing list