[commit: ghc] master: Remove dead code for commandline parsing (c18b525)

git at git.haskell.org git at git.haskell.org
Tue Aug 28 10:53:12 UTC 2018


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/c18b525a6f226187a12ed907fa5d3b200daab914/ghc

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

commit c18b525a6f226187a12ed907fa5d3b200daab914
Author: Krzysztof Gogolewski <krz.gogolewski at gmail.com>
Date:   Tue Aug 28 12:52:47 2018 +0200

    Remove dead code for commandline parsing
    
    Summary:
    PrefixPred and AnySuffixPred are not used
    since static flags were removed in bbd3c399939.
    
    Test Plan: validate
    
    Reviewers: bgamari, tdammers
    
    Reviewed By: tdammers
    
    Subscribers: rwbarton, carter
    
    Differential Revision: https://phabricator.haskell.org/D5111


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

c18b525a6f226187a12ed907fa5d3b200daab914
 compiler/main/CmdLineParser.hs | 8 --------
 compiler/main/DynFlags.hs      | 9 +--------
 2 files changed, 1 insertion(+), 16 deletions(-)

diff --git a/compiler/main/CmdLineParser.hs b/compiler/main/CmdLineParser.hs
index c876f58..cb30b6f 100644
--- a/compiler/main/CmdLineParser.hs
+++ b/compiler/main/CmdLineParser.hs
@@ -79,8 +79,6 @@ data OptKind m                             -- Suppose the flag is -f
     | FloatSuffix (Float -> EwM m ())      -- -f or -f=n; pass n to fn
     | PassFlag  (String -> EwM m ())       -- -f; pass "-f" fn
     | AnySuffix (String -> EwM m ())       -- -f or -farg; pass entire "-farg" to fn
-    | PrefixPred    (String -> Bool) (String -> EwM m ())
-    | AnySuffixPred (String -> Bool) (String -> EwM m ())
 
 
 --------------------------------------------------------
@@ -246,9 +244,6 @@ processOneArg opt_kind rest arg args
         Prefix f | notNull rest_no_eq -> Right (f rest_no_eq, args)
                  | otherwise          -> missingArgErr  dash_arg
 
-        PrefixPred _ f | notNull rest_no_eq -> Right (f rest_no_eq, args)
-                       | otherwise          -> unknownFlagErr dash_arg
-
         PassFlag f  | notNull rest -> unknownFlagErr dash_arg
                     | otherwise    -> Right (f dash_arg, args)
 
@@ -264,7 +259,6 @@ processOneArg opt_kind rest arg args
 
         OptPrefix f       -> Right (f rest_no_eq, args)
         AnySuffix f       -> Right (f dash_arg, args)
-        AnySuffixPred _ f -> Right (f dash_arg, args)
 
 findArg :: [Flag m] -> String -> Maybe (String, OptKind m)
 findArg spec arg =
@@ -284,14 +278,12 @@ arg_ok (HasArg          _)  _    _   = True
 arg_ok (SepArg          _)  rest _   = null rest
 arg_ok (Prefix          _)  _    _   = True -- Missing argument checked for in processOneArg t
                                             -- to improve error message (Trac #12625)
-arg_ok (PrefixPred p    _)  rest _   = notNull rest && p (dropEq rest)
 arg_ok (OptIntSuffix    _)  _    _   = True
 arg_ok (IntSuffix       _)  _    _   = True
 arg_ok (FloatSuffix     _)  _    _   = True
 arg_ok (OptPrefix       _)  _    _   = True
 arg_ok (PassFlag        _)  rest _   = null rest
 arg_ok (AnySuffix       _)  _    _   = True
-arg_ok (AnySuffixPred p _)  _    arg = p arg
 
 -- | Parse an Int
 --
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index be14879..9f0ba57 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -2698,11 +2698,8 @@ allNonDeprecatedFlags = allFlagsDeps False
 allFlagsDeps :: Bool -> [String]
 allFlagsDeps keepDeprecated = [ '-':flagName flag
                               | (deprecated, flag) <- flagsAllDeps
-                              , ok (flagOptKind flag)
                               , keepDeprecated || not (isDeprecated deprecated)]
-  where ok (PrefixPred _ _) = False
-        ok _   = True
-        isDeprecated Deprecated = True
+  where isDeprecated Deprecated = True
         isDeprecated _ = False
 
 {-
@@ -2762,10 +2759,6 @@ add_dep_message (PassFlag f) message =
                                    PassFlag $ \s -> f s >> deprecate message
 add_dep_message (AnySuffix f) message =
                                   AnySuffix $ \s -> f s >> deprecate message
-add_dep_message (PrefixPred pred f) message =
-                            PrefixPred pred $ \s -> f s >> deprecate message
-add_dep_message (AnySuffixPred pred f) message =
-                         AnySuffixPred pred $ \s -> f s >> deprecate message
 
 ----------------------- The main flags themselves ------------------------------
 -- See Note [Updating flag description in the User's Guide]



More information about the ghc-commits mailing list