[project @ 2004-10-18 18:24:59 by igloo]
[ghc-hetmet.git] / ghc / compiler / main / DriverFlags.hs
1 -----------------------------------------------------------------------------
2 --
3 -- Driver flags
4 --
5 -- (c) The University of Glasgow 2000-2003
6 --
7 -----------------------------------------------------------------------------
8
9 module DriverFlags ( 
10         processArgs, OptKind(..), static_flags, dynamic_flags, 
11         addCmdlineHCInclude,
12         buildStaticHscOpts, 
13         machdepCCOpts
14   ) where
15
16 #include "HsVersions.h"
17 #include "../includes/ghcconfig.h"
18
19 import MkIface          ( showIface )
20 import DriverState
21 import DriverPhases
22 import DriverUtil
23 import SysTools
24 import CmdLineOpts
25 import Config
26 import Util
27 import Panic
28
29 import EXCEPTION
30 import DATA_IOREF       ( readIORef, writeIORef )
31
32 import System           ( exitWith, ExitCode(..) )
33 import IO
34 import Maybe
35 import Monad
36 import Char
37
38 -----------------------------------------------------------------------------
39 -- Flags
40
41 -- Flag parsing is now done in stages:
42 --
43 --     * parse the initial list of flags and remove any flags understood
44 --       by the driver only.  Determine whether we're in multi-compilation
45 --       or single-compilation mode (done in Main.main).
46 --
47 --     * gather the list of "static" hsc flags, and assign them to the global
48 --       static hsc flags variable.
49 --
50 --     * build the inital DynFlags from the remaining flags.
51 --
52 --     * complain if we've got any flags left over.
53 --
54 --     * for each source file: grab the OPTIONS, and build a new DynFlags
55 --       to pass to the compiler.
56
57 -----------------------------------------------------------------------------
58 -- Process command-line  
59
60 data OptKind
61         = NoArg (IO ())                     -- flag with no argument
62         | HasArg (String -> IO ())          -- flag has an argument (maybe prefix)
63         | SepArg (String -> IO ())          -- flag has a separate argument
64         | Prefix (String -> IO ())          -- flag is a prefix only
65         | OptPrefix (String -> IO ())       -- flag may be a prefix
66         | AnySuffix (String -> IO ())       -- flag is a prefix, pass whole arg to fn
67         | PassFlag  (String -> IO ())       -- flag with no arg, pass flag to fn
68         | PrefixPred (String -> Bool) (String -> IO ())
69         | AnySuffixPred (String -> Bool) (String -> IO ())
70
71 processArgs :: [(String,OptKind)] -> [String] -> [String]
72             -> IO [String]  -- returns spare args
73 processArgs _spec [] spare = return (reverse spare)
74
75 processArgs spec args@(('-':arg):args') spare = do
76   case findArg spec arg of
77     Just (rest,action) -> do args' <- processOneArg action rest args
78                              processArgs spec args' spare
79     Nothing            -> processArgs spec args' (('-':arg):spare)
80
81 processArgs spec (arg:args) spare = 
82   processArgs spec args (arg:spare)
83
84 processOneArg :: OptKind -> String -> [String] -> IO [String]
85 processOneArg action rest (dash_arg@('-':arg):args) =
86   case action of
87         NoArg  io -> 
88                 if rest == ""
89                         then io >> return args
90                         else unknownFlagErr dash_arg
91
92         HasArg fio -> 
93                 if rest /= "" 
94                         then fio rest >> return args
95                         else case args of
96                                 [] -> missingArgErr dash_arg
97                                 (arg1:args1) -> fio arg1 >> return args1
98
99         SepArg fio -> 
100                 case args of
101                         [] -> unknownFlagErr dash_arg
102                         (arg1:args1) -> fio arg1 >> return args1
103
104         Prefix fio -> 
105                 if rest /= ""
106                         then fio rest >> return args
107                         else unknownFlagErr dash_arg
108         
109         PrefixPred p fio -> 
110                 if rest /= ""
111                         then fio rest >> return args
112                         else unknownFlagErr dash_arg
113         
114         OptPrefix fio       -> fio rest >> return args
115
116         AnySuffix fio       -> fio dash_arg >> return args
117
118         AnySuffixPred p fio -> fio dash_arg >> return args
119
120         PassFlag fio  -> 
121                 if rest /= ""
122                         then unknownFlagErr dash_arg
123                         else fio dash_arg >> return args
124
125 findArg :: [(String,OptKind)] -> String -> Maybe (String,OptKind)
126 findArg spec arg
127   = case [ (remove_spaces rest, k) 
128          | (pat,k)   <- spec, 
129            Just rest <- [maybePrefixMatch pat arg],
130            arg_ok k rest arg ] 
131     of
132         []      -> Nothing
133         (one:_) -> Just one
134
135 arg_ok (NoArg _)            rest arg = null rest
136 arg_ok (HasArg _)           rest arg = True
137 arg_ok (SepArg _)           rest arg = null rest
138 arg_ok (Prefix _)           rest arg = notNull rest
139 arg_ok (PrefixPred p _)     rest arg = notNull rest && p rest
140 arg_ok (OptPrefix _)        rest arg = True
141 arg_ok (PassFlag _)         rest arg = null rest 
142 arg_ok (AnySuffix _)        rest arg = True
143 arg_ok (AnySuffixPred p _)  rest arg = p arg
144
145 -----------------------------------------------------------------------------
146 -- Static flags
147
148 -- note that ordering is important in the following list: any flag which
149 -- is a prefix flag (i.e. HasArg, Prefix, OptPrefix, AnySuffix) will override
150 -- flags further down the list with the same prefix.
151
152 static_flags = 
153   [  ------- help / version ----------------------------------------------
154      ( "?"               , NoArg showGhcUsage)
155   ,  ( "-help"           , NoArg showGhcUsage)
156   ,  ( "-print-libdir"   , NoArg (do getTopDir >>= putStrLn
157                                      exitWith ExitSuccess))  
158   ,  ( "V"               , NoArg showVersion)
159   ,  ( "-version"        , NoArg showVersion)
160   ,  ( "-numeric-version", NoArg (do putStrLn cProjectVersion
161                                      exitWith ExitSuccess))
162
163       ------- interfaces ----------------------------------------------------
164   ,  ( "-show-iface"     , HasArg (\f -> do showIface f
165                                             exitWith ExitSuccess))
166
167       ------- verbosity ----------------------------------------------------
168   ,  ( "n"              , NoArg setDryRun )
169
170       ------- primary modes ------------------------------------------------
171   ,  ( "M"              , PassFlag (setMode DoMkDependHS))
172   ,  ( "E"              , PassFlag (setMode (StopBefore Hsc)))
173   ,  ( "C"              , PassFlag (\f -> do setMode (StopBefore HCc) f
174                                              setLang HscC))
175   ,  ( "S"              , PassFlag (setMode (StopBefore As)))
176   ,  ( "c"              , PassFlag (setMode (StopBefore Ln)))
177   ,  ( "-make"          , PassFlag (setMode DoMake))
178   ,  ( "-interactive"   , PassFlag (setMode DoInteractive))
179   ,  ( "-mk-dll"        , PassFlag (setMode DoMkDLL))
180   ,  ( "e"              , HasArg   (\s -> setMode (DoEval s) "-e"))
181
182         -- -fno-code says to stop after Hsc but don't generate any code.
183   ,  ( "fno-code"       , PassFlag (\f -> do setMode (StopBefore HCc) f
184                                              setLang HscNothing
185                                              writeIORef v_Recomp False))
186
187         ------- GHCi -------------------------------------------------------
188   ,  ( "ignore-dot-ghci", NoArg (writeIORef v_Read_DotGHCi False) )
189   ,  ( "read-dot-ghci"  , NoArg (writeIORef v_Read_DotGHCi True) )
190
191         ------- recompilation checker --------------------------------------
192   ,  ( "recomp"         , NoArg (writeIORef v_Recomp True) )
193   ,  ( "no-recomp"      , NoArg (writeIORef v_Recomp False) )
194
195         ------- ways --------------------------------------------------------
196   ,  ( "prof"           , NoArg (addNoDups v_Ways       WayProf) )
197   ,  ( "unreg"          , NoArg (addNoDups v_Ways       WayUnreg) )
198   ,  ( "ticky"          , NoArg (addNoDups v_Ways       WayTicky) )
199   ,  ( "parallel"       , NoArg (addNoDups v_Ways       WayPar) )
200   ,  ( "gransim"        , NoArg (addNoDups v_Ways       WayGran) )
201   ,  ( "smp"            , NoArg (addNoDups v_Ways       WaySMP) )
202   ,  ( "debug"          , NoArg (addNoDups v_Ways       WayDebug) )
203   ,  ( "ndp"            , NoArg (addNoDups v_Ways       WayNDP) )
204   ,  ( "threaded"       , NoArg (addNoDups v_Ways       WayThreaded) )
205         -- ToDo: user ways
206
207         ------ RTS ways -----------------------------------------------------
208
209         ------ Debugging ----------------------------------------------------
210   ,  ( "dppr-noprags",     PassFlag (add v_Opt_C) )
211   ,  ( "dppr-debug",       PassFlag (add v_Opt_C) )
212   ,  ( "dppr-user-length", AnySuffix (add v_Opt_C) )
213       -- rest of the debugging flags are dynamic
214
215         --------- Profiling --------------------------------------------------
216   ,  ( "auto-dicts"     , NoArg (add v_Opt_C "-fauto-sccs-on-dicts") )
217   ,  ( "auto-all"       , NoArg (add v_Opt_C "-fauto-sccs-on-all-toplevs") )
218   ,  ( "auto"           , NoArg (add v_Opt_C "-fauto-sccs-on-exported-toplevs") )
219   ,  ( "caf-all"        , NoArg (add v_Opt_C "-fauto-sccs-on-individual-cafs") )
220          -- "ignore-sccs"  doesn't work  (ToDo)
221
222   ,  ( "no-auto-dicts"  , NoArg (add v_Anti_opt_C "-fauto-sccs-on-dicts") )
223   ,  ( "no-auto-all"    , NoArg (add v_Anti_opt_C "-fauto-sccs-on-all-toplevs") )
224   ,  ( "no-auto"        , NoArg (add v_Anti_opt_C "-fauto-sccs-on-exported-toplevs") )
225   ,  ( "no-caf-all"     , NoArg (add v_Anti_opt_C "-fauto-sccs-on-individual-cafs") )
226
227         ------- Miscellaneous -----------------------------------------------
228   ,  ( "no-link-chk"    , NoArg (return ()) ) -- ignored for backwards compat
229   ,  ( "no-hs-main"     , NoArg (writeIORef v_NoHsMain True) )
230   ,  ( "main-is"        , SepArg setMainIs )
231
232         ------- Output Redirection ------------------------------------------
233   ,  ( "odir"           , HasArg (writeIORef v_Output_dir  . Just) )
234   ,  ( "o"              , SepArg (writeIORef v_Output_file . Just) )
235   ,  ( "osuf"           , HasArg (writeIORef v_Object_suf) )
236   ,  ( "hcsuf"          , HasArg (writeIORef v_HC_suf      . Just) )
237   ,  ( "hisuf"          , HasArg (writeIORef v_Hi_suf) )
238   ,  ( "hidir"          , HasArg (writeIORef v_Hi_dir . Just) )
239   ,  ( "buildtag"       , HasArg (writeIORef v_Build_tag) )
240   ,  ( "tmpdir"         , HasArg setTmpDir)
241   ,  ( "ohi"            , HasArg (writeIORef v_Output_hi   . Just) )
242         -- -odump?
243
244   ,  ( "keep-hc-file"   , AnySuffix (\_ -> writeIORef v_Keep_hc_files True) )
245   ,  ( "keep-s-file"    , AnySuffix (\_ -> writeIORef v_Keep_s_files  True) )
246   ,  ( "keep-raw-s-file", AnySuffix (\_ -> writeIORef v_Keep_raw_s_files  True) )
247 #ifdef ILX
248   ,  ( "keep-il-file"   , AnySuffix (\_ -> writeIORef v_Keep_il_files True) )
249   ,  ( "keep-ilx-file"  , AnySuffix (\_ -> writeIORef v_Keep_ilx_files True) )
250 #endif
251   ,  ( "keep-tmp-files" , AnySuffix (\_ -> writeIORef v_Keep_tmp_files True) )
252
253   ,  ( "split-objs"     , NoArg (if can_split
254                                     then do writeIORef v_Split_object_files True
255                                             add v_Opt_C "-fglobalise-toplev-names"
256                                     else hPutStrLn stderr
257                                             "warning: don't know how to split object files on this architecture"
258                                 ) )
259
260         ------- Include/Import Paths ----------------------------------------
261   ,  ( "i"              , OptPrefix (addToOrDeleteDirList v_Import_paths) )
262   ,  ( "I"              , Prefix    (addToDirList v_Include_paths) )
263
264         ------- Libraries ---------------------------------------------------
265   ,  ( "L"              , Prefix (addToDirList v_Library_paths) )
266   ,  ( "l"              , AnySuffix (\s -> add v_Opt_l s >> add v_Opt_dll s) )
267
268 #ifdef darwin_TARGET_OS
269         ------- Frameworks --------------------------------------------------
270         -- -framework-path should really be -F ...
271   ,  ( "framework-path" , HasArg (addToDirList v_Framework_paths) )
272   ,  ( "framework"      , HasArg (add v_Cmdline_frameworks) )
273 #endif
274         ------- Packages ----------------------------------------------------
275   ,  ( "package-name"   , HasArg (\s -> add v_Opt_C ("-inpackage="++s)) )
276
277   ,  ( "package-conf"   , HasArg (readPackageConf) )
278   ,  ( "package"        , HasArg (addPackage) )
279   ,  ( "syslib"         , HasArg (addPackage) ) -- for compatibility w/ old vsns
280
281         ------- Specific phases  --------------------------------------------
282   ,  ( "pgmL"           , HasArg setPgmL )
283   ,  ( "pgmP"           , HasArg setPgmP )
284   ,  ( "pgmF"           , HasArg setPgmF )
285   ,  ( "pgmc"           , HasArg setPgmc )
286   ,  ( "pgmm"           , HasArg setPgmm )
287   ,  ( "pgms"           , HasArg setPgms )
288   ,  ( "pgma"           , HasArg setPgma )
289   ,  ( "pgml"           , HasArg setPgml )
290   ,  ( "pgmdll"         , HasArg setPgmDLL )
291 #ifdef ILX
292   ,  ( "pgmI"           , HasArg setPgmI )
293   ,  ( "pgmi"           , HasArg setPgmi )
294 #endif
295
296   ,  ( "optdep"         , HasArg (add v_Opt_dep) )
297   ,  ( "optl"           , HasArg (add v_Opt_l) )
298   ,  ( "optdll"         , HasArg (add v_Opt_dll) )
299
300         ----- Linker --------------------------------------------------------
301   ,  ( "no-link"        , NoArg (writeIORef v_NoLink True) )
302   ,  ( "static"         , NoArg (writeIORef v_Static True) )
303   ,  ( "dynamic"        , NoArg (writeIORef v_Static False) )
304   ,  ( "rdynamic"       , NoArg (return ()) ) -- ignored for compat w/ gcc
305
306         ----- RTS opts ------------------------------------------------------
307   ,  ( "H"                 , HasArg (setHeapSize . fromIntegral . decodeSize) )
308   ,  ( "Rghc-timing"       , NoArg  (enableTimingStats) )
309
310         ------ Compiler flags -----------------------------------------------
311   ,  ( "fno-asm-mangling"  , NoArg (writeIORef v_Do_asm_mangling False) )
312
313   ,  ( "fexcess-precision" , NoArg (do writeIORef v_Excess_precision True
314                                        add v_Opt_C "-fexcess-precision"))
315
316         -- All other "-fno-<blah>" options cancel out "-f<blah>" on the hsc cmdline
317   ,  ( "fno-",                  PrefixPred (\s -> isStaticHscFlag ("f"++s))
318                                     (\s -> add v_Anti_opt_C ("-f"++s)) )
319
320         -- Pass all remaining "-f<blah>" options to hsc
321   ,  ( "f",                     AnySuffixPred (isStaticHscFlag) (add v_Opt_C) )
322   ]
323
324 dynamic_flags = [
325
326      ( "cpp",           NoArg  (updDynFlags (\s -> s{ cppFlag = True })) )
327   ,  ( "F",             NoArg  (updDynFlags (\s -> s{ ppFlag = True })) )
328   ,  ( "#include",      HasArg (addCmdlineHCInclude) )
329
330   ,  ( "v",             OptPrefix (setVerbosity) )
331
332   ,  ( "optL",          HasArg (addOpt_L) )
333   ,  ( "optP",          HasArg (addOpt_P) )
334   ,  ( "optF",          HasArg (addOpt_F) )
335   ,  ( "optc",          HasArg (addOpt_c) )
336   ,  ( "optm",          HasArg (addOpt_m) )
337   ,  ( "opta",          HasArg (addOpt_a) )
338 #ifdef ILX
339   ,  ( "optI",          HasArg (addOpt_I) )
340   ,  ( "opti",          HasArg (addOpt_i) )
341 #endif
342
343         ------ HsCpp opts ---------------------------------------------------
344   ,  ( "D",             AnySuffix addOpt_P )
345   ,  ( "U",             AnySuffix addOpt_P )
346
347         ------ Debugging ----------------------------------------------------
348   ,  ( "dstg-stats",    NoArg (writeIORef v_StgStats True) )
349
350   ,  ( "ddump-cmm",              NoArg (setDynFlag Opt_D_dump_cmm) )
351   ,  ( "ddump-asm",              NoArg (setDynFlag Opt_D_dump_asm) )
352   ,  ( "ddump-cpranal",          NoArg (setDynFlag Opt_D_dump_cpranal) )
353   ,  ( "ddump-deriv",            NoArg (setDynFlag Opt_D_dump_deriv) )
354   ,  ( "ddump-ds",               NoArg (setDynFlag Opt_D_dump_ds) )
355   ,  ( "ddump-flatC",            NoArg (setDynFlag Opt_D_dump_flatC) )
356   ,  ( "ddump-foreign",          NoArg (setDynFlag Opt_D_dump_foreign) )
357   ,  ( "ddump-inlinings",        NoArg (setDynFlag Opt_D_dump_inlinings) )
358   ,  ( "ddump-occur-anal",       NoArg (setDynFlag Opt_D_dump_occur_anal) )
359   ,  ( "ddump-parsed",           NoArg (setDynFlag Opt_D_dump_parsed) )
360   ,  ( "ddump-rn",               NoArg (setDynFlag Opt_D_dump_rn) )
361   ,  ( "ddump-simpl",            NoArg (setDynFlag Opt_D_dump_simpl) )
362   ,  ( "ddump-simpl-iterations", NoArg (setDynFlag Opt_D_dump_simpl_iterations) )
363   ,  ( "ddump-spec",             NoArg (setDynFlag Opt_D_dump_spec) )
364   ,  ( "ddump-prep",             NoArg (setDynFlag Opt_D_dump_prep) )
365   ,  ( "ddump-stg",              NoArg (setDynFlag Opt_D_dump_stg) )
366   ,  ( "ddump-stranal",          NoArg (setDynFlag Opt_D_dump_stranal) )
367   ,  ( "ddump-tc",               NoArg (setDynFlag Opt_D_dump_tc) )
368   ,  ( "ddump-types",            NoArg (setDynFlag Opt_D_dump_types) )
369   ,  ( "ddump-rules",            NoArg (setDynFlag Opt_D_dump_rules) )
370   ,  ( "ddump-cse",              NoArg (setDynFlag Opt_D_dump_cse) )
371   ,  ( "ddump-worker-wrapper",   NoArg (setDynFlag Opt_D_dump_worker_wrapper) )
372   ,  ( "dshow-passes",           NoArg (setVerbosity "2") )
373   ,  ( "ddump-rn-trace",         NoArg (setDynFlag Opt_D_dump_rn_trace) )
374   ,  ( "ddump-if-trace",         NoArg (setDynFlag Opt_D_dump_if_trace) )
375   ,  ( "ddump-tc-trace",         NoArg (setDynFlag Opt_D_dump_tc_trace) )
376   ,  ( "ddump-splices",          NoArg (setDynFlag Opt_D_dump_splices) )
377   ,  ( "ddump-rn-stats",         NoArg (setDynFlag Opt_D_dump_rn_stats) )
378   ,  ( "ddump-opt-cmm",          NoArg (setDynFlag Opt_D_dump_opt_cmm) )
379   ,  ( "ddump-simpl-stats",      NoArg (setDynFlag Opt_D_dump_simpl_stats) )
380   ,  ( "ddump-bcos",             NoArg (setDynFlag Opt_D_dump_BCOs) )
381   ,  ( "dsource-stats",          NoArg (setDynFlag Opt_D_source_stats) )
382   ,  ( "dverbose-core2core",     NoArg (setDynFlag Opt_D_verbose_core2core) )
383   ,  ( "dverbose-stg2stg",       NoArg (setDynFlag Opt_D_verbose_stg2stg) )
384   ,  ( "ddump-hi-diffs",         NoArg (setDynFlag Opt_D_dump_hi_diffs) )
385   ,  ( "ddump-hi",               NoArg (setDynFlag Opt_D_dump_hi) )
386   ,  ( "ddump-minimal-imports",  NoArg (setDynFlag Opt_D_dump_minimal_imports) )
387   ,  ( "ddump-vect",             NoArg (setDynFlag Opt_D_dump_vect) )
388   ,  ( "dcore-lint",             NoArg (setDynFlag Opt_DoCoreLinting) )
389   ,  ( "dstg-lint",              NoArg (setDynFlag Opt_DoStgLinting) )
390   ,  ( "dcmm-lint",              NoArg (setDynFlag Opt_DoCmmLinting) )
391
392         ------ Machine dependant (-m<blah>) stuff ---------------------------
393
394   ,  ( "monly-2-regs",  NoArg (updDynFlags (\s -> s{stolen_x86_regs = 2}) ))
395   ,  ( "monly-3-regs",  NoArg (updDynFlags (\s -> s{stolen_x86_regs = 3}) ))
396   ,  ( "monly-4-regs",  NoArg (updDynFlags (\s -> s{stolen_x86_regs = 4}) ))
397
398         ------ Warning opts -------------------------------------------------
399   ,  ( "W"              , NoArg (mapM_ setDynFlag   minusWOpts)    )
400   ,  ( "Werror"         , NoArg (setDynFlag         Opt_WarnIsError) )
401   ,  ( "Wall"           , NoArg (mapM_ setDynFlag   minusWallOpts) )
402   ,  ( "Wnot"           , NoArg (mapM_ unSetDynFlag minusWallOpts) ) /* DEPREC */
403   ,  ( "w"              , NoArg (mapM_ unSetDynFlag minusWallOpts) )
404
405         ------ Optimisation flags ------------------------------------------
406   ,  ( "O"                 , NoArg (setOptLevel 1))
407   ,  ( "Onot"              , NoArg (setOptLevel 0))
408   ,  ( "O"                 , PrefixPred (all isDigit) (setOptLevel . read))
409
410   ,  ( "fmax-simplifier-iterations", 
411                 PrefixPred (all isDigit) 
412                   (\n -> updDynFlags (\dfs -> 
413                         dfs{ maxSimplIterations = read n })) )
414
415   ,  ( "frule-check", 
416                 SepArg (\s -> updDynFlags (\dfs -> dfs{ ruleCheck = Just s })))
417
418         ------ Compiler flags -----------------------------------------------
419
420   ,  ( "fasm",          AnySuffix (\_ -> setLang HscAsm) )
421   ,  ( "fvia-c",        NoArg (setLang HscC) )
422   ,  ( "fvia-C",        NoArg (setLang HscC) )
423   ,  ( "filx",          NoArg (setLang HscILX) )
424
425   ,  ( "fglasgow-exts",    NoArg (mapM_ setDynFlag   glasgowExtsFlags) )
426   ,  ( "fno-glasgow-exts", NoArg (mapM_ unSetDynFlag glasgowExtsFlags) )
427
428         -- "active negatives"
429   ,  ( "fno-implicit-prelude",  NoArg (setDynFlag Opt_NoImplicitPrelude) )
430   ,  ( "fno-monomorphism-restriction",  
431                         NoArg (setDynFlag Opt_NoMonomorphismRestriction) )
432
433         -- the rest of the -f* and -fno-* flags
434   ,  ( "fno-",          PrefixPred (\f -> isFFlag f) (\f -> unSetDynFlag (getFFlag f)) )
435   ,  ( "f",             PrefixPred (\f -> isFFlag f) (\f -> setDynFlag (getFFlag f)) )
436  ]
437
438 -- these -f<blah> flags can all be reversed with -fno-<blah>
439
440 fFlags = [
441   ( "warn-duplicate-exports",           Opt_WarnDuplicateExports ),
442   ( "warn-hi-shadowing",                Opt_WarnHiShadows ),
443   ( "warn-incomplete-patterns",         Opt_WarnIncompletePatterns ),
444   ( "warn-incomplete-record-updates",   Opt_WarnIncompletePatternsRecUpd ),
445   ( "warn-missing-fields",              Opt_WarnMissingFields ),
446   ( "warn-missing-methods",             Opt_WarnMissingMethods ),
447   ( "warn-missing-signatures",          Opt_WarnMissingSigs ),
448   ( "warn-name-shadowing",              Opt_WarnNameShadowing ),
449   ( "warn-overlapping-patterns",        Opt_WarnOverlappingPatterns ),
450   ( "warn-simple-patterns",             Opt_WarnSimplePatterns ),
451   ( "warn-type-defaults",               Opt_WarnTypeDefaults ),
452   ( "warn-unused-binds",                Opt_WarnUnusedBinds ),
453   ( "warn-unused-imports",              Opt_WarnUnusedImports ),
454   ( "warn-unused-matches",              Opt_WarnUnusedMatches ),
455   ( "warn-deprecations",                Opt_WarnDeprecations ),
456   ( "fi",                               Opt_FFI ),  -- support `-ffi'...
457   ( "ffi",                              Opt_FFI ),  -- ...and also `-fffi'
458   ( "arrows",                           Opt_Arrows ), -- arrow syntax
459   ( "parr",                             Opt_PArr ),
460   ( "th",                               Opt_TH ),
461   ( "implicit-params",                  Opt_ImplicitParams ),
462   ( "allow-overlapping-instances",      Opt_AllowOverlappingInstances ),
463   ( "allow-undecidable-instances",      Opt_AllowUndecidableInstances ),
464   ( "allow-incoherent-instances",       Opt_AllowIncoherentInstances ),
465   ( "generics",                         Opt_Generics ),
466   ( "strictness",                       Opt_Strictness ),
467   ( "full-laziness",                    Opt_FullLaziness ),
468   ( "cse",                              Opt_CSE ),
469   ( "ignore-interface-pragmas",         Opt_IgnoreInterfacePragmas ),
470   ( "omit-interface-pragmas",           Opt_OmitInterfacePragmas ),
471   ( "do-lambda-eta-expansion",          Opt_DoLambdaEtaExpansion ),
472   ( "ignore-asserts",                   Opt_IgnoreAsserts ),
473   ( "do-eta-reduction",                 Opt_DoEtaReduction ),
474   ( "case-merge",                       Opt_CaseMerge ),
475   ( "unbox-strict-fields",              Opt_UnboxStrictFields )
476   ]
477
478 glasgowExtsFlags = [ Opt_GlasgowExts, Opt_FFI, Opt_TH, Opt_ImplicitParams ]
479
480 isFFlag f = f `elem` (map fst fFlags)
481 getFFlag f = fromJust (lookup f fFlags)
482
483 -----------------------------------------------------------------------------
484 -- convert sizes like "3.5M" into integers
485
486 decodeSize :: String -> Integer
487 decodeSize str
488   | c == ""              = truncate n
489   | c == "K" || c == "k" = truncate (n * 1000)
490   | c == "M" || c == "m" = truncate (n * 1000 * 1000)
491   | c == "G" || c == "g" = truncate (n * 1000 * 1000 * 1000)
492   | otherwise            = throwDyn (CmdLineError ("can't decode size: " ++ str))
493   where (m, c) = span pred str
494         n      = read m  :: Double
495         pred c = isDigit c || c == '.'
496
497
498 -----------------------------------------------------------------------------
499 -- RTS Hooks
500
501 #if __GLASGOW_HASKELL__ >= 504
502 foreign import ccall unsafe "setHeapSize"       setHeapSize       :: Int -> IO ()
503 foreign import ccall unsafe "enableTimingStats" enableTimingStats :: IO ()
504 #else
505 foreign import "setHeapSize"       unsafe setHeapSize       :: Int -> IO ()
506 foreign import "enableTimingStats" unsafe enableTimingStats :: IO ()
507 #endif
508
509 -----------------------------------------------------------------------------
510 -- Build the Hsc static command line opts
511
512 buildStaticHscOpts :: IO [String]
513 buildStaticHscOpts = do
514
515   opt_C_ <- getStaticOpts v_Opt_C       -- misc hsc opts from the command line
516
517         -- take into account -fno-* flags by removing the equivalent -f*
518         -- flag from our list.
519   anti_flags <- getStaticOpts v_Anti_opt_C
520   let basic_opts = opt_C_
521       filtered_opts = filter (`notElem` anti_flags) basic_opts
522
523   static <- (do s <- readIORef v_Static; if s then return "-static" 
524                                               else return "")
525
526   return ( static : filtered_opts )
527
528 setMainIs :: String -> IO ()
529 setMainIs arg
530   | not (null main_mod)         -- The arg looked like "Foo.baz"
531   = do { writeIORef v_MainFunIs (Just main_fn) ;
532          writeIORef v_MainModIs (Just main_mod) }
533
534   | isUpper (head main_fn)      -- The arg looked like "Foo"
535   = writeIORef v_MainModIs (Just main_fn)
536   
537   | otherwise                   -- The arg looked like "baz"
538   = writeIORef v_MainFunIs (Just main_fn)
539   where
540     (main_mod, main_fn) = split_longest_prefix arg (== '.')
541   
542
543 -----------------------------------------------------------------------------
544 -- Via-C compilation stuff
545
546 -- flags returned are: ( all C compilations
547 --                     , registerised HC compilations
548 --                     )
549
550 machdepCCOpts 
551    | prefixMatch "alpha"   cTARGETPLATFORM  
552         = return ( ["-static", "-w", "-mieee"
553 #ifdef HAVE_THREADED_RTS_SUPPORT
554                     , "-D_REENTRANT"
555 #endif
556                    ], [] )
557         -- For now, to suppress the gcc warning "call-clobbered
558         -- register used for global register variable", we simply
559         -- disable all warnings altogether using the -w flag. Oh well.
560
561    | prefixMatch "hppa"    cTARGETPLATFORM  
562         -- ___HPUX_SOURCE, not _HPUX_SOURCE, is #defined if -ansi!
563         -- (very nice, but too bad the HP /usr/include files don't agree.)
564         = return ( ["-static", "-D_HPUX_SOURCE"], [] )
565
566    | prefixMatch "m68k"    cTARGETPLATFORM
567       -- -fno-defer-pop : for the .hc files, we want all the pushing/
568       --    popping of args to routines to be explicit; if we let things
569       --    be deferred 'til after an STGJUMP, imminent death is certain!
570       --
571       -- -fomit-frame-pointer : *don't*
572       --     It's better to have a6 completely tied up being a frame pointer
573       --     rather than let GCC pick random things to do with it.
574       --     (If we want to steal a6, then we would try to do things
575       --     as on iX86, where we *do* steal the frame pointer [%ebp].)
576         = return ( [], ["-fno-defer-pop", "-fno-omit-frame-pointer"] )
577
578    | prefixMatch "i386"    cTARGETPLATFORM  
579       -- -fno-defer-pop : basically the same game as for m68k
580       --
581       -- -fomit-frame-pointer : *must* in .hc files; because we're stealing
582       --   the fp (%ebp) for our register maps.
583         = do n_regs <- dynFlag stolen_x86_regs
584              sta    <- readIORef v_Static
585              return ( [ if sta then "-DDONT_WANT_WIN32_DLL_SUPPORT" else ""
586 --                    , if suffixMatch "mingw32" cTARGETPLATFORM then "-mno-cygwin" else "" 
587                       ],
588                       [ "-fno-defer-pop",
589 #ifdef HAVE_GCC_MNO_OMIT_LFPTR
590                         -- Some gccs are configured with
591                         -- -momit-leaf-frame-pointer on by default, and it
592                         -- apparently takes precedence over 
593                         -- -fomit-frame-pointer, so we disable it first here.
594                         "-mno-omit-leaf-frame-pointer",
595 #endif
596                         "-fomit-frame-pointer",
597                         -- we want -fno-builtin, because when gcc inlines
598                         -- built-in functions like memcpy() it tends to
599                         -- run out of registers, requiring -monly-n-regs
600                         "-fno-builtin",
601                         "-DSTOLEN_X86_REGS="++show n_regs ]
602                     )
603
604    | prefixMatch "ia64"    cTARGETPLATFORM  
605         = return ( [], ["-fomit-frame-pointer", "-G0"] )
606
607    | prefixMatch "x86_64"  cTARGETPLATFORM
608         = return ( [], ["-fomit-frame-pointer"] )
609
610    | prefixMatch "mips"    cTARGETPLATFORM
611         = return ( ["-static"], [] )
612
613    | prefixMatch "sparc"    cTARGETPLATFORM
614         = return ( [], ["-w"] )
615         -- For now, to suppress the gcc warning "call-clobbered
616         -- register used for global register variable", we simply
617         -- disable all warnings altogether using the -w flag. Oh well.
618
619    | prefixMatch "powerpc-apple-darwin" cTARGETPLATFORM
620       -- -no-cpp-precomp:
621       --     Disable Apple's precompiling preprocessor. It's a great thing
622       --     for "normal" programs, but it doesn't support register variable
623       --     declarations.
624       -- -mdynamic-no-pic:
625       --     Turn off PIC code generation to save space and time.
626       -- -fno-common:
627       --     Don't generate "common" symbols - these are unwanted
628       --     in dynamic libraries.
629
630         = if opt_PIC
631             then return ( ["-no-cpp-precomp", "-fno-common"],
632                           ["-fno-common"] )
633             else return ( ["-no-cpp-precomp", "-mdynamic-no-pic"],
634                           ["-mdynamic-no-pic"] )
635
636    | prefixMatch "powerpc" cTARGETPLATFORM && opt_PIC
637         = return ( ["-fPIC"], ["-fPIC"] )
638   
639    | otherwise
640         = return ( [], [] )
641
642 -----------------------------------------------------------------------------
643 -- local utils
644
645 addOpt_L a = updDynFlags (\s -> s{opt_L = a : opt_L s})
646 addOpt_P a = updDynFlags (\s -> s{opt_P = a : opt_P s})
647 addOpt_F a = updDynFlags (\s -> s{opt_F = a : opt_F s})
648 addOpt_c a = updDynFlags (\s -> s{opt_c = a : opt_c s})
649 addOpt_a a = updDynFlags (\s -> s{opt_a = a : opt_a s})
650 addOpt_m a = updDynFlags (\s -> s{opt_m = a : opt_m s})
651 #ifdef ILX
652 addOpt_I a = updDynFlags (\s -> s{opt_I = a : opt_I s})
653 addOpt_i a = updDynFlags (\s -> s{opt_i = a : opt_i s})
654 #endif
655
656 setVerbosity "" = updDynFlags (\dfs -> dfs{ verbosity = 3 })
657 setVerbosity n 
658   | all isDigit n = updDynFlags (\dfs -> dfs{ verbosity = read n })
659   | otherwise     = throwDyn (UsageError "can't parse verbosity flag (-v<n>)")
660
661 addCmdlineHCInclude a = updDynFlags (\s -> s{cmdlineHcIncludes =  a : cmdlineHcIncludes s})
662
663 -- -----------------------------------------------------------------------------
664 -- Version and usage messages
665
666 showVersion :: IO ()
667 showVersion = do
668   putStrLn (cProjectName ++ ", version " ++ cProjectVersion)
669   exitWith ExitSuccess
670
671 showGhcUsage = do 
672   (ghc_usage_path,ghci_usage_path) <- getUsageMsgPaths
673   mode <- readIORef v_GhcMode
674   let usage_path 
675         | mode == DoInteractive  = ghci_usage_path
676         | otherwise              = ghc_usage_path
677   usage <- readFile usage_path
678   dump usage
679   exitWith ExitSuccess
680   where
681      dump ""          = return ()
682      dump ('$':'$':s) = hPutStr stderr progName >> dump s
683      dump (c:s)       = hPutChar stderr c >> dump s