Use a proper datatype, rather than pairs, for flags
[ghc-hetmet.git] / compiler / main / CmdLineParser.hs
1 -----------------------------------------------------------------------------
2 --
3 -- Command-line parser
4 --
5 -- This is an abstract command-line parser used by both StaticFlags and
6 -- DynFlags.
7 --
8 -- (c) The University of Glasgow 2005
9 --
10 -----------------------------------------------------------------------------
11
12 module CmdLineParser (
13         processArgs, OptKind(..),
14         CmdLineP(..), getCmdLineState, putCmdLineState,
15         Flag(..),
16   ) where
17
18 #include "HsVersions.h"
19
20 import Util
21 import Panic
22
23 data Flag m = Flag { flagName :: String,        -- flag, without the leading -
24                      flagOptKind :: (OptKind m) -- What to do if we see it
25                    }
26
27 data OptKind m                      -- Suppose the flag is -f
28  = NoArg (m ())                     -- -f all by itself
29  | HasArg    (String -> m ())       -- -farg or -f arg
30  | SepArg    (String -> m ())       -- -f arg
31  | Prefix    (String -> m ())       -- -farg
32  | OptPrefix (String -> m ())       -- -f or -farg (i.e. the arg is optional)
33  | OptIntSuffix (Maybe Int -> m ()) -- -f or -f=n; pass n to fn
34  | IntSuffix (Int -> m ())          -- -f or -f=n; pass n to fn
35  | PassFlag  (String -> m ())       -- -f; pass "-f" fn
36  | AnySuffix (String -> m ())       -- -f or -farg; pass entire "-farg" to fn
37  | PrefixPred    (String -> Bool) (String -> m ())
38  | AnySuffixPred (String -> Bool) (String -> m ())
39
40 processArgs :: Monad m
41             => [Flag m] -- cmdline parser spec
42             -> [String]              -- args
43             -> m (
44                   [String],  -- spare args
45                   [String]   -- errors
46                  )
47 processArgs spec args = process spec args [] []
48   where
49     process _spec [] spare errs =
50       return (reverse spare, reverse errs)
51
52     process spec (dash_arg@('-':arg):args) spare errs =
53       case findArg spec arg of
54         Just (rest,action) ->
55            case processOneArg action rest arg args of
56              Left err            -> process spec args spare (err:errs)
57              Right (action,rest) -> action >> process spec rest spare errs
58         Nothing -> process spec args (dash_arg:spare) errs
59
60     process spec (arg:args) spare errs =
61       process spec args (arg:spare) errs
62
63
64 processOneArg :: OptKind m -> String -> String -> [String]
65               -> Either String (m (), [String])
66 processOneArg action rest arg args
67   = let dash_arg = '-' : arg
68         rest_no_eq = dropEq rest
69     in case action of
70         NoArg  a -> ASSERT(null rest) Right (a, args)
71
72         HasArg f | notNull rest_no_eq -> Right (f rest_no_eq, args)
73                  | otherwise    -> case args of
74                                     [] -> missingArgErr dash_arg
75                                     (arg1:args1) -> Right (f arg1, args1)
76
77         SepArg f -> case args of
78                         [] -> unknownFlagErr dash_arg
79                         (arg1:args1) -> Right (f arg1, args1)
80
81         Prefix f | notNull rest_no_eq -> Right (f rest_no_eq, args)
82                  | otherwise  -> unknownFlagErr dash_arg
83
84         PrefixPred _ f | notNull rest_no_eq -> Right (f rest_no_eq, args)
85                        | otherwise          -> unknownFlagErr dash_arg
86
87         PassFlag f  | notNull rest -> unknownFlagErr dash_arg
88                     | otherwise    -> Right (f dash_arg, args)
89
90         OptIntSuffix f | null rest                     -> Right (f Nothing,  args)
91                        | Just n <- parseInt rest_no_eq -> Right (f (Just n), args)
92                        | otherwise -> Left ("malformed integer argument in " ++ dash_arg)
93
94         IntSuffix f | Just n <- parseInt rest_no_eq -> Right (f n, args)
95                     | otherwise -> Left ("malformed integer argument in " ++ dash_arg)
96
97         OptPrefix f       -> Right (f rest_no_eq, args)
98         AnySuffix f       -> Right (f dash_arg, args)
99         AnySuffixPred _ f -> Right (f dash_arg, args)
100
101
102 findArg :: [Flag m] -> String -> Maybe (String, OptKind m)
103 findArg spec arg
104   = case [ (removeSpaces rest, optKind)
105          | flag <- spec,
106            let optKind = flagOptKind flag,
107            Just rest <- [maybePrefixMatch (flagName flag) arg],
108            arg_ok optKind rest arg ]
109     of
110         []      -> Nothing
111         (one:_) -> Just one
112
113 arg_ok :: OptKind t -> [Char] -> String -> Bool
114 arg_ok (NoArg _)            rest _   = null rest
115 arg_ok (HasArg _)           _    _   = True
116 arg_ok (SepArg _)           rest _   = null rest
117 arg_ok (Prefix _)           rest _   = notNull rest
118 arg_ok (PrefixPred p _)     rest _   = notNull rest && p (dropEq rest)
119 arg_ok (OptIntSuffix _)     _    _   = True
120 arg_ok (IntSuffix _)        _    _   = True
121 arg_ok (OptPrefix _)        _    _   = True
122 arg_ok (PassFlag _)         rest _   = null rest
123 arg_ok (AnySuffix _)        _    _   = True
124 arg_ok (AnySuffixPred p _)  _    arg = p arg
125
126 parseInt :: String -> Maybe Int
127 -- Looks for "433" or "=342", with no trailing gubbins
128 --   n or =n      => Just n
129 --   gibberish    => Nothing
130 parseInt s = case reads s of
131                 ((n,""):_) -> Just n
132                 _          -> Nothing
133
134 dropEq :: String -> String
135 -- Discards a leading equals sign
136 dropEq ('=' : s) = s
137 dropEq s         = s
138
139 unknownFlagErr :: String -> Either String a
140 unknownFlagErr f = Left ("unrecognised flag: " ++ f)
141
142 missingArgErr :: String -> Either String a
143 missingArgErr f = Left ("missing argument for flag: " ++ f)
144
145 -- -----------------------------------------------------------------------------
146 -- A state monad for use in the command-line parser
147
148 newtype CmdLineP s a = CmdLineP { runCmdLine :: s -> (a, s) }
149
150 instance Monad (CmdLineP s) where
151         return a = CmdLineP $ \s -> (a, s)
152         m >>= k  = CmdLineP $ \s -> let
153                 (a, s') = runCmdLine m s
154                 in runCmdLine (k a) s'
155
156 getCmdLineState :: CmdLineP s s
157 getCmdLineState   = CmdLineP $ \s -> (s,s)
158 putCmdLineState :: s -> CmdLineP s ()
159 putCmdLineState s = CmdLineP $ \_ -> ((),s)