1 -----------------------------------------------------------------------------
5 -- This is an abstract command-line parser used by both StaticFlags and
8 -- (c) The University of Glasgow 2005
10 -----------------------------------------------------------------------------
12 module CmdLineParser (
13 processArgs, OptKind(..),
14 CmdLineP(..), getCmdLineState, putCmdLineState,
15 Flag(..), Deprecated(..),
18 #include "HsVersions.h"
25 flagName :: String, -- flag, without the leading -
26 flagOptKind :: (OptKind m), -- what to do if we see it
27 flagDeprecated :: Deprecated -- is the flag deprecated?
30 data Deprecated = Supported | Deprecated String
32 data OptKind m -- Suppose the flag is -f
33 = NoArg (m ()) -- -f all by itself
34 | HasArg (String -> m ()) -- -farg or -f arg
35 | SepArg (String -> m ()) -- -f arg
36 | Prefix (String -> m ()) -- -farg
37 | OptPrefix (String -> m ()) -- -f or -farg (i.e. the arg is optional)
38 | OptIntSuffix (Maybe Int -> m ()) -- -f or -f=n; pass n to fn
39 | IntSuffix (Int -> m ()) -- -f or -f=n; pass n to fn
40 | PassFlag (String -> m ()) -- -f; pass "-f" fn
41 | AnySuffix (String -> m ()) -- -f or -farg; pass entire "-farg" to fn
42 | PrefixPred (String -> Bool) (String -> m ())
43 | AnySuffixPred (String -> Bool) (String -> m ())
45 processArgs :: Monad m
46 => [Flag m] -- cmdline parser spec
49 [String], -- spare args
53 processArgs spec args = process spec args [] [] []
55 process _spec [] spare errs warns =
56 return (reverse spare, reverse errs, reverse warns)
58 process spec (dash_arg@('-' : arg) : args) spare errs warns =
59 case findArg spec arg of
60 Just (rest, action, deprecated) ->
61 let warns' = case deprecated of
63 ("Warning: " ++ dash_arg ++ " is deprecated: " ++ warning) : warns
65 in case processOneArg action rest arg args of
66 Left err -> process spec args spare (err:errs) warns'
67 Right (action,rest) -> do action
68 process spec rest spare errs warns'
69 Nothing -> process spec args (dash_arg : spare) errs warns
71 process spec (arg : args) spare errs warns =
72 process spec args (arg : spare) errs warns
75 processOneArg :: OptKind m -> String -> String -> [String]
76 -> Either String (m (), [String])
77 processOneArg action rest arg args
78 = let dash_arg = '-' : arg
79 rest_no_eq = dropEq rest
81 NoArg a -> ASSERT(null rest) Right (a, args)
83 HasArg f | notNull rest_no_eq -> Right (f rest_no_eq, args)
84 | otherwise -> case args of
85 [] -> missingArgErr dash_arg
86 (arg1:args1) -> Right (f arg1, args1)
88 SepArg f -> case args of
89 [] -> unknownFlagErr dash_arg
90 (arg1:args1) -> Right (f arg1, args1)
92 Prefix f | notNull rest_no_eq -> Right (f rest_no_eq, args)
93 | otherwise -> unknownFlagErr dash_arg
95 PrefixPred _ f | notNull rest_no_eq -> Right (f rest_no_eq, args)
96 | otherwise -> unknownFlagErr dash_arg
98 PassFlag f | notNull rest -> unknownFlagErr dash_arg
99 | otherwise -> Right (f dash_arg, args)
101 OptIntSuffix f | null rest -> Right (f Nothing, args)
102 | Just n <- parseInt rest_no_eq -> Right (f (Just n), args)
103 | otherwise -> Left ("malformed integer argument in " ++ dash_arg)
105 IntSuffix f | Just n <- parseInt rest_no_eq -> Right (f n, args)
106 | otherwise -> Left ("malformed integer argument in " ++ dash_arg)
108 OptPrefix f -> Right (f rest_no_eq, args)
109 AnySuffix f -> Right (f dash_arg, args)
110 AnySuffixPred _ f -> Right (f dash_arg, args)
113 findArg :: [Flag m] -> String -> Maybe (String, OptKind m, Deprecated)
115 = case [ (removeSpaces rest, optKind, flagDeprecated flag)
117 let optKind = flagOptKind flag,
118 Just rest <- [maybePrefixMatch (flagName flag) arg],
119 arg_ok optKind rest arg ]
124 arg_ok :: OptKind t -> [Char] -> String -> Bool
125 arg_ok (NoArg _) rest _ = null rest
126 arg_ok (HasArg _) _ _ = True
127 arg_ok (SepArg _) rest _ = null rest
128 arg_ok (Prefix _) rest _ = notNull rest
129 arg_ok (PrefixPred p _) rest _ = notNull rest && p (dropEq rest)
130 arg_ok (OptIntSuffix _) _ _ = True
131 arg_ok (IntSuffix _) _ _ = True
132 arg_ok (OptPrefix _) _ _ = True
133 arg_ok (PassFlag _) rest _ = null rest
134 arg_ok (AnySuffix _) _ _ = True
135 arg_ok (AnySuffixPred p _) _ arg = p arg
137 parseInt :: String -> Maybe Int
138 -- Looks for "433" or "=342", with no trailing gubbins
140 -- gibberish => Nothing
141 parseInt s = case reads s of
145 dropEq :: String -> String
146 -- Discards a leading equals sign
150 unknownFlagErr :: String -> Either String a
151 unknownFlagErr f = Left ("unrecognised flag: " ++ f)
153 missingArgErr :: String -> Either String a
154 missingArgErr f = Left ("missing argument for flag: " ++ f)
156 -- -----------------------------------------------------------------------------
157 -- A state monad for use in the command-line parser
159 newtype CmdLineP s a = CmdLineP { runCmdLine :: s -> (a, s) }
161 instance Monad (CmdLineP s) where
162 return a = CmdLineP $ \s -> (a, s)
163 m >>= k = CmdLineP $ \s -> let
164 (a, s') = runCmdLine m s
165 in runCmdLine (k a) s'
167 getCmdLineState :: CmdLineP s s
168 getCmdLineState = CmdLineP $ \s -> (s,s)
169 putCmdLineState :: s -> CmdLineP s ()
170 putCmdLineState s = CmdLineP $ \_ -> ((),s)