Give a better deprecated message for INCLUDE pragmas; fixes #3933
[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(..), Deprecated(..),
16         errorsToGhcException
17   ) where
18
19 #include "HsVersions.h"
20
21 import Util
22 import Outputable
23 import Panic
24 import SrcLoc
25
26 import Data.List
27
28 data Flag m = Flag
29     {
30         flagName :: String,           -- flag, without the leading -
31         flagOptKind :: (OptKind m),   -- what to do if we see it
32         flagDeprecated :: Deprecated  -- is the flag deprecated?
33     }
34
35 data Deprecated = Supported
36                 | Deprecated String
37                 | DeprecatedFullText String
38
39 data OptKind m                      -- Suppose the flag is -f
40  = NoArg (m ())                     -- -f all by itself
41  | HasArg    (String -> m ())       -- -farg or -f arg
42  | SepArg    (String -> m ())       -- -f arg
43  | Prefix    (String -> m ())       -- -farg
44  | OptPrefix (String -> m ())       -- -f or -farg (i.e. the arg is optional)
45  | OptIntSuffix (Maybe Int -> m ()) -- -f or -f=n; pass n to fn
46  | IntSuffix (Int -> m ())          -- -f or -f=n; pass n to fn
47  | PassFlag  (String -> m ())       -- -f; pass "-f" fn
48  | AnySuffix (String -> m ())       -- -f or -farg; pass entire "-farg" to fn
49  | PrefixPred    (String -> Bool) (String -> m ())
50  | AnySuffixPred (String -> Bool) (String -> m ())
51
52 processArgs :: Monad m
53             => [Flag m] -- cmdline parser spec
54             -> [Located String]      -- args
55             -> m (
56                   [Located String],  -- spare args
57                   [Located String],  -- errors
58                   [Located String]   -- warnings
59                  )
60 processArgs spec args = process spec args [] [] []
61   where
62     process _spec [] spare errs warns =
63       return (reverse spare, reverse errs, reverse warns)
64
65     process spec (locArg@(L loc dash_arg@('-' : arg)) : args) spare errs warns =
66       case findArg spec arg of
67         Just (rest, action, deprecated) ->
68            let warns' = case deprecated of
69                         Deprecated warning ->
70                             L loc ("Warning: " ++ dash_arg ++ " is deprecated: " ++ warning) : warns
71                         DeprecatedFullText warning ->
72                             L loc ("Warning: " ++ warning) : warns
73                         Supported -> warns
74            in case processOneArg action rest arg args of
75               Left err            -> process spec args spare (L loc err : errs) warns'
76               Right (action,rest) -> do action
77                                         process spec rest spare errs warns'
78         Nothing -> process spec args (locArg : spare) errs warns
79
80     process spec (arg : args) spare errs warns =
81       process spec args (arg : spare) errs warns
82
83
84 processOneArg :: OptKind m -> String -> String -> [Located String]
85               -> Either String (m (), [Located String])
86 processOneArg action rest arg args
87   = let dash_arg = '-' : arg
88         rest_no_eq = dropEq rest
89     in case action of
90         NoArg  a -> ASSERT(null rest) Right (a, args)
91
92         HasArg f | notNull rest_no_eq -> Right (f rest_no_eq, args)
93                  | otherwise    -> case args of
94                                     [] -> missingArgErr dash_arg
95                                     (L _ arg1:args1) -> Right (f arg1, args1)
96
97         SepArg f -> case args of
98                         [] -> unknownFlagErr dash_arg
99                         (L _ arg1:args1) -> Right (f arg1, args1)
100
101         Prefix f | notNull rest_no_eq -> Right (f rest_no_eq, args)
102                  | otherwise  -> unknownFlagErr dash_arg
103
104         PrefixPred _ f | notNull rest_no_eq -> Right (f rest_no_eq, args)
105                        | otherwise          -> unknownFlagErr dash_arg
106
107         PassFlag f  | notNull rest -> unknownFlagErr dash_arg
108                     | otherwise    -> Right (f dash_arg, args)
109
110         OptIntSuffix f | null rest                     -> Right (f Nothing,  args)
111                        | Just n <- parseInt rest_no_eq -> Right (f (Just n), args)
112                        | otherwise -> Left ("malformed integer argument in " ++ dash_arg)
113
114         IntSuffix f | Just n <- parseInt rest_no_eq -> Right (f n, args)
115                     | otherwise -> Left ("malformed integer argument in " ++ dash_arg)
116
117         OptPrefix f       -> Right (f rest_no_eq, args)
118         AnySuffix f       -> Right (f dash_arg, args)
119         AnySuffixPred _ f -> Right (f dash_arg, args)
120
121
122 findArg :: [Flag m] -> String -> Maybe (String, OptKind m, Deprecated)
123 findArg spec arg
124   = case [ (removeSpaces rest, optKind, flagDeprecated flag)
125          | flag <- spec,
126            let optKind = flagOptKind flag,
127            Just rest <- [stripPrefix (flagName flag) arg],
128            arg_ok optKind rest arg ]
129     of
130         []      -> Nothing
131         (one:_) -> Just one
132
133 arg_ok :: OptKind t -> [Char] -> String -> Bool
134 arg_ok (NoArg _)            rest _   = null rest
135 arg_ok (HasArg _)           _    _   = True
136 arg_ok (SepArg _)           rest _   = null rest
137 arg_ok (Prefix _)           rest _   = notNull rest
138 arg_ok (PrefixPred p _)     rest _   = notNull rest && p (dropEq rest)
139 arg_ok (OptIntSuffix _)     _    _   = True
140 arg_ok (IntSuffix _)        _    _   = True
141 arg_ok (OptPrefix _)        _    _   = True
142 arg_ok (PassFlag _)         rest _   = null rest
143 arg_ok (AnySuffix _)        _    _   = True
144 arg_ok (AnySuffixPred p _)  _    arg = p arg
145
146 parseInt :: String -> Maybe Int
147 -- Looks for "433" or "=342", with no trailing gubbins
148 --   n or =n      => Just n
149 --   gibberish    => Nothing
150 parseInt s = case reads s of
151                 ((n,""):_) -> Just n
152                 _          -> Nothing
153
154 dropEq :: String -> String
155 -- Discards a leading equals sign
156 dropEq ('=' : s) = s
157 dropEq s         = s
158
159 unknownFlagErr :: String -> Either String a
160 unknownFlagErr f = Left ("unrecognised flag: " ++ f)
161
162 missingArgErr :: String -> Either String a
163 missingArgErr f = Left ("missing argument for flag: " ++ f)
164
165 -- -----------------------------------------------------------------------------
166 -- A state monad for use in the command-line parser
167
168 newtype CmdLineP s a = CmdLineP { runCmdLine :: s -> (a, s) }
169
170 instance Monad (CmdLineP s) where
171         return a = CmdLineP $ \s -> (a, s)
172         m >>= k  = CmdLineP $ \s -> let
173                 (a, s') = runCmdLine m s
174                 in runCmdLine (k a) s'
175
176 getCmdLineState :: CmdLineP s s
177 getCmdLineState   = CmdLineP $ \s -> (s,s)
178 putCmdLineState :: s -> CmdLineP s ()
179 putCmdLineState s = CmdLineP $ \_ -> ((),s)
180
181 -- ---------------------------------------------------------------------
182 -- Utils
183
184 errorsToGhcException :: [Located String] -> GhcException
185 errorsToGhcException errs =
186    let errors = vcat [ ppr l <> text ": " <> text e | L l e <- errs ]
187    in UsageError (showSDoc errors)
188