[project @ 2004-12-22 16:58:34 by simonpj]
[ghc-hetmet.git] / ghc / compiler / main / CmdLineOpts.lhs
1
2 % (c) The University of Glasgow, 1996-2000
3 %
4 \section[CmdLineOpts]{Things to do with command-line options}
5
6 \begin{code}
7
8 module CmdLineOpts (
9         CoreToDo(..), buildCoreToDo, StgToDo(..),
10         SimplifierSwitch(..), 
11         SimplifierMode(..), FloatOutSwitches(..),
12
13         HscLang(..),
14         DynFlag(..),    -- needed non-abstractly by DriverFlags
15         DynFlags(..),
16         PackageFlag(..),
17
18         v_Static_hsc_opts,
19
20         isStaticHscFlag,
21
22         -- Manipulating DynFlags
23         defaultDynFlags,                -- DynFlags
24         dopt,                           -- DynFlag -> DynFlags -> Bool
25         dopt_set, dopt_unset,           -- DynFlags -> DynFlag -> DynFlags
26         dopt_CoreToDo,                  -- DynFlags -> [CoreToDo]
27         dopt_StgToDo,                   -- DynFlags -> [StgToDo]
28         dopt_HscLang,                   -- DynFlags -> HscLang
29         dopt_OutName,                   -- DynFlags -> String
30         getOpts,                        -- (DynFlags -> [a]) -> IO [a]
31         getVerbFlag,
32         updOptLevel,
33
34         -- sets of warning opts
35         minusWOpts,
36         minusWallOpts,
37
38         -- Output style options
39         opt_PprUserLength,
40         opt_PprStyle_Debug,
41
42         -- profiling opts
43         opt_AutoSccsOnAllToplevs,
44         opt_AutoSccsOnExportedToplevs,
45         opt_AutoSccsOnIndividualCafs,
46         opt_SccProfilingOn,
47         opt_DoTickyProfiling,
48
49         -- language opts
50         opt_DictsStrict,
51         opt_MaxContextReductionDepth,
52         opt_IrrefutableTuples,
53         opt_Parallel,
54         opt_SMP,
55         opt_RuntimeTypes,
56         opt_Flatten,
57
58         -- optimisation opts
59         opt_NoMethodSharing, 
60         opt_NoStateHack,
61         opt_LiberateCaseThreshold,
62         opt_CprOff,
63         opt_RulesOff,
64         opt_SimplNoPreInlining,
65         opt_SimplExcessPrecision,
66         opt_MaxWorkerArgs,
67
68         -- Unfolding control
69         opt_UF_CreationThreshold,
70         opt_UF_UseThreshold,
71         opt_UF_FunAppDiscount,
72         opt_UF_KeenessFactor,
73         opt_UF_UpdateInPlace,
74         opt_UF_DearOp,
75
76         -- misc opts
77         opt_ErrorSpans,
78         opt_EmitCExternDecls,
79         opt_EnsureSplittableC,
80         opt_GranMacros,
81         opt_HiVersion,
82         opt_HistorySize,
83         opt_OmitBlackHoling,
84         opt_Static,
85         opt_Unregisterised,
86         opt_EmitExternalCore,
87         opt_PIC
88     ) where
89
90 #include "HsVersions.h"
91
92 import {-# SOURCE #-} Packages (PackageState)
93 import Constants        -- Default values for some flags
94 import Util
95 import FastString       ( FastString, mkFastString )
96 import Config
97 import Maybes           ( firstJust )
98
99 import Panic            ( ghcError, GhcException(UsageError) )
100 import GLAEXTS
101 import DATA_IOREF       ( IORef, readIORef )
102 import UNSAFE_IO        ( unsafePerformIO )
103 \end{code}
104
105 %************************************************************************
106 %*                                                                      *
107 \subsection{Command-line options}
108 %*                                                                      *
109 %************************************************************************
110
111 The hsc command-line options are split into two categories:
112
113   - static flags
114   - dynamic flags
115
116 Static flags are represented by top-level values of type Bool or Int,
117 for example.  They therefore have the same value throughout the
118 invocation of hsc.
119
120 Dynamic flags are represented by an abstract type, DynFlags, which is
121 passed into hsc by the compilation manager for every compilation.
122 Dynamic flags are those that change on a per-compilation basis,
123 perhaps because they may be present in the OPTIONS pragma at the top
124 of a module.
125
126 Other flag-related blurb:
127
128 A list of {\em ToDo}s is things to be done in a particular part of
129 processing.  A (fictitious) example for the Core-to-Core simplifier
130 might be: run the simplifier, then run the strictness analyser, then
131 run the simplifier again (three ``todos'').
132
133 There are three ``to-do processing centers'' at the moment.  In the
134 main loop (\tr{main/Main.lhs}), in the Core-to-Core processing loop
135 (\tr{simplCore/SimplCore.lhs), and in the STG-to-STG processing loop
136 (\tr{simplStg/SimplStg.lhs}).
137
138 %************************************************************************
139 %*                                                                      *
140 \subsection{Datatypes associated with command-line options}
141 %*                                                                      *
142 %************************************************************************
143
144 \begin{code}
145 data CoreToDo           -- These are diff core-to-core passes,
146                         -- which may be invoked in any order,
147                         -- as many times as you like.
148
149   = CoreDoSimplify      -- The core-to-core simplifier.
150         SimplifierMode
151         [SimplifierSwitch]
152                         -- Each run of the simplifier can take a different
153                         -- set of simplifier-specific flags.
154   | CoreDoFloatInwards
155   | CoreDoFloatOutwards FloatOutSwitches
156   | CoreLiberateCase
157   | CoreDoPrintCore
158   | CoreDoStaticArgs
159   | CoreDoStrictness
160   | CoreDoWorkerWrapper
161   | CoreDoSpecialising
162   | CoreDoSpecConstr
163   | CoreDoOldStrictness
164   | CoreDoGlomBinds
165   | CoreCSE
166   | CoreDoRuleCheck Int{-CompilerPhase-} String -- Check for non-application of rules 
167                                                 -- matching this string
168
169   | CoreDoNothing        -- useful when building up lists of these things
170 \end{code}
171
172 \begin{code}
173 data StgToDo
174   = StgDoMassageForProfiling  -- should be (next to) last
175   -- There's also setStgVarInfo, but its absolute "lastness"
176   -- is so critical that it is hardwired in (no flag).
177   | D_stg_stats
178 \end{code}
179
180 \begin{code}
181 data SimplifierMode             -- See comments in SimplMonad
182   = SimplGently
183   | SimplPhase Int
184
185 data SimplifierSwitch
186   = MaxSimplifierIterations Int
187   | NoCaseOfCase
188
189 data FloatOutSwitches
190   = FloatOutSw  Bool    -- True <=> float lambdas to top level
191                 Bool    -- True <=> float constants to top level,
192                         --          even if they do not escape a lambda
193 \end{code}
194
195 %************************************************************************
196 %*                                                                      *
197 \subsection{Dynamic command-line options}
198 %*                                                                      *
199 %************************************************************************
200
201 \begin{code}
202 data DynFlag
203
204    -- debugging flags
205    = Opt_D_dump_cmm
206    | Opt_D_dump_asm
207    | Opt_D_dump_cpranal
208    | Opt_D_dump_deriv
209    | Opt_D_dump_ds
210    | Opt_D_dump_flatC
211    | Opt_D_dump_foreign
212    | Opt_D_dump_inlinings
213    | Opt_D_dump_occur_anal
214    | Opt_D_dump_parsed
215    | Opt_D_dump_rn
216    | Opt_D_dump_simpl
217    | Opt_D_dump_simpl_iterations
218    | Opt_D_dump_spec
219    | Opt_D_dump_prep
220    | Opt_D_dump_stg
221    | Opt_D_dump_stranal
222    | Opt_D_dump_tc
223    | Opt_D_dump_types
224    | Opt_D_dump_rules
225    | Opt_D_dump_cse
226    | Opt_D_dump_worker_wrapper
227    | Opt_D_dump_rn_trace
228    | Opt_D_dump_rn_stats
229    | Opt_D_dump_opt_cmm
230    | Opt_D_dump_simpl_stats
231    | Opt_D_dump_tc_trace
232    | Opt_D_dump_if_trace
233    | Opt_D_dump_splices
234    | Opt_D_dump_BCOs
235    | Opt_D_dump_vect
236    | Opt_D_source_stats
237    | Opt_D_verbose_core2core
238    | Opt_D_verbose_stg2stg
239    | Opt_D_dump_hi
240    | Opt_D_dump_hi_diffs
241    | Opt_D_dump_minimal_imports
242    | Opt_DoCoreLinting
243    | Opt_DoStgLinting
244    | Opt_DoCmmLinting
245
246    | Opt_WarnIsError            -- -Werror; makes warnings fatal
247    | Opt_WarnDuplicateExports
248    | Opt_WarnHiShadows
249    | Opt_WarnIncompletePatterns
250    | Opt_WarnIncompletePatternsRecUpd
251    | Opt_WarnMissingFields
252    | Opt_WarnMissingMethods
253    | Opt_WarnMissingSigs
254    | Opt_WarnNameShadowing
255    | Opt_WarnOverlappingPatterns
256    | Opt_WarnSimplePatterns
257    | Opt_WarnTypeDefaults
258    | Opt_WarnUnusedBinds
259    | Opt_WarnUnusedImports
260    | Opt_WarnUnusedMatches
261    | Opt_WarnDeprecations
262    | Opt_WarnDodgyImports
263    | Opt_WarnOrphans
264
265    -- language opts
266    | Opt_AllowOverlappingInstances
267    | Opt_AllowUndecidableInstances
268    | Opt_AllowIncoherentInstances
269    | Opt_MonomorphismRestriction
270    | Opt_GlasgowExts
271    | Opt_FFI
272    | Opt_PArr                          -- syntactic support for parallel arrays
273    | Opt_Arrows                        -- Arrow-notation syntax
274    | Opt_TH
275    | Opt_ImplicitParams
276    | Opt_Generics
277    | Opt_ImplicitPrelude 
278    | Opt_ScopedTypeVariables
279
280    -- optimisation opts
281    | Opt_Strictness
282    | Opt_FullLaziness
283    | Opt_CSE
284    | Opt_IgnoreInterfacePragmas
285    | Opt_OmitInterfacePragmas
286    | Opt_DoLambdaEtaExpansion
287    | Opt_IgnoreAsserts
288    | Opt_DoEtaReduction
289    | Opt_CaseMerge
290    | Opt_UnboxStrictFields
291
292    deriving (Eq)
293
294 data DynFlags = DynFlags {
295   coreToDo              :: Maybe [CoreToDo], -- reserved for use with -Ofile
296   stgToDo               :: [StgToDo],
297   hscLang               :: HscLang,
298   hscOutName            :: String,      -- name of the output file
299   hscStubHOutName       :: String,      -- name of the .stub_h output file
300   hscStubCOutName       :: String,      -- name of the .stub_c output file
301   extCoreName           :: String,      -- name of the .core output file
302   verbosity             :: Int,         -- verbosity level
303   optLevel              :: Int,         -- optimisation level
304   maxSimplIterations    :: Int,         -- max simplifier iterations
305   ruleCheck             :: Maybe String,
306   cppFlag               :: Bool,        -- preprocess with cpp?
307   ppFlag                :: Bool,        -- preprocess with a Haskell Pp?
308   stolen_x86_regs       :: Int,         
309   cmdlineHcIncludes     :: [String],    -- -#includes
310   importPaths           :: [FilePath],
311
312   -- options for particular phases
313   opt_L                 :: [String],
314   opt_P                 :: [String],
315   opt_F                 :: [String],
316   opt_c                 :: [String],
317   opt_a                 :: [String],
318   opt_m                 :: [String],
319 #ifdef ILX                         
320   opt_I                 :: [String],
321   opt_i                 :: [String],
322 #endif
323
324   -- ** Package flags
325   extraPkgConfs         :: [FilePath],
326         -- The -package-conf flags given on the command line, in the order
327         -- they appeared.
328
329   readUserPkgConf       :: Bool,
330         -- Whether or not to read the user package database
331         -- (-no-user-package-conf).
332
333   packageFlags          :: [PackageFlag],
334         -- The -package and -hide-package flags from the command-line
335
336   -- ** Package state
337   pkgState              :: PackageState,
338
339   -- hsc dynamic flags
340   flags                 :: [DynFlag]
341  }
342
343 data PackageFlag
344   = ExposePackage  String
345   | HidePackage    String
346   | IgnorePackage  String
347
348 data HscLang
349   = HscC
350   | HscAsm
351   | HscJava
352   | HscILX
353   | HscInterpreted
354   | HscNothing
355     deriving (Eq, Show)
356
357 defaultHscLang
358   | cGhcWithNativeCodeGen == "YES" && 
359         (prefixMatch "i386" cTARGETPLATFORM ||
360          prefixMatch "sparc" cTARGETPLATFORM ||
361          prefixMatch "powerpc" cTARGETPLATFORM)   =  HscAsm
362   | otherwise                                   =  HscC
363
364 defaultDynFlags = DynFlags {
365   coreToDo = Nothing, stgToDo = [], 
366   hscLang = defaultHscLang, 
367   hscOutName = "", 
368   hscStubHOutName = "", hscStubCOutName = "",
369   extCoreName = "",
370   verbosity             = 0, 
371   optLevel              = 0,
372   maxSimplIterations    = 4,
373   ruleCheck             = Nothing,
374   cppFlag               = False,
375   ppFlag                = False,
376   stolen_x86_regs       = 4,
377   cmdlineHcIncludes     = [],
378   importPaths           = ["."],
379   opt_L                 = [],
380   opt_P                 = [],
381   opt_F                 = [],
382   opt_c                 = [],
383   opt_a                 = [],
384   opt_m                 = [],
385 #ifdef ILX
386   opt_I                 = [],
387   opt_i                 = [],
388 #endif
389
390   extraPkgConfs         = [],
391   readUserPkgConf       = True,
392   packageFlags          = [],
393   pkgState              = error "pkgState",
394
395   flags = [ 
396             Opt_ImplicitPrelude,
397             Opt_MonomorphismRestriction,
398             Opt_Generics,
399                         -- Generating the helper-functions for
400                         -- generics is now on by default
401             Opt_Strictness,
402                         -- strictness is on by default, but this only
403                         -- applies to -O.
404             Opt_CSE,            -- similarly for CSE.
405             Opt_FullLaziness,   -- ...and for full laziness
406
407             Opt_DoLambdaEtaExpansion,
408                         -- This one is important for a tiresome reason:
409                         -- we want to make sure that the bindings for data 
410                         -- constructors are eta-expanded.  This is probably
411                         -- a good thing anyway, but it seems fragile.
412
413             -- and the default no-optimisation options:
414             Opt_IgnoreInterfacePragmas,
415             Opt_OmitInterfacePragmas
416
417            ] ++ standardWarnings
418   }
419
420 {- 
421     Verbosity levels:
422         
423     0   |   print errors & warnings only
424     1   |   minimal verbosity: print "compiling M ... done." for each module.
425     2   |   equivalent to -dshow-passes
426     3   |   equivalent to existing "ghc -v"
427     4   |   "ghc -v -ddump-most"
428     5   |   "ghc -v -ddump-all"
429 -}
430
431 dopt :: DynFlag -> DynFlags -> Bool
432 dopt f dflags  = f `elem` (flags dflags)
433
434 dopt_CoreToDo :: DynFlags -> Maybe [CoreToDo]
435 dopt_CoreToDo = coreToDo
436
437 dopt_StgToDo :: DynFlags -> [StgToDo]
438 dopt_StgToDo = stgToDo
439
440 dopt_OutName :: DynFlags -> String
441 dopt_OutName = hscOutName
442
443 dopt_HscLang :: DynFlags -> HscLang
444 dopt_HscLang = hscLang
445
446 dopt_set :: DynFlags -> DynFlag -> DynFlags
447 dopt_set dfs f = dfs{ flags = f : flags dfs }
448
449 dopt_unset :: DynFlags -> DynFlag -> DynFlags
450 dopt_unset dfs f = dfs{ flags = filter (/= f) (flags dfs) }
451
452 getOpts :: DynFlags -> (DynFlags -> [a]) -> [a]
453         -- We add to the options from the front, so we need to reverse the list
454 getOpts dflags opts = reverse (opts dflags)
455
456 getVerbFlag dflags 
457   | verbosity dflags >= 3  = "-v" 
458   | otherwise =  ""
459
460 -----------------------------------------------------------------------------
461 -- Setting the optimisation level
462
463 updOptLevel n dfs
464   = if (n >= 1)
465      then dfs2{ hscLang = HscC, optLevel = n } -- turn on -fvia-C with -O
466      else dfs2{ optLevel = n }
467   where
468    dfs1 = foldr (flip dopt_unset) dfs  remove_dopts
469    dfs2 = foldr (flip dopt_set)   dfs1 extra_dopts
470
471    extra_dopts
472         | n == 0    = opt_0_dopts
473         | otherwise = opt_1_dopts
474
475    remove_dopts
476         | n == 0    = opt_1_dopts
477         | otherwise = opt_0_dopts
478         
479 opt_0_dopts =  [ 
480         Opt_IgnoreInterfacePragmas,
481         Opt_OmitInterfacePragmas
482     ]
483
484 opt_1_dopts = [
485         Opt_IgnoreAsserts,
486         Opt_DoEtaReduction,
487         Opt_CaseMerge
488      ]
489
490 -- Core-to-core phases:
491
492 buildCoreToDo :: DynFlags -> [CoreToDo]
493 buildCoreToDo dflags = core_todo
494   where
495     opt_level     = optLevel dflags
496     max_iter      = maxSimplIterations dflags
497     strictness    = dopt Opt_Strictness dflags
498     full_laziness = dopt Opt_FullLaziness dflags
499     cse           = dopt Opt_CSE dflags
500     rule_check    = ruleCheck dflags
501
502     core_todo = 
503      if opt_level == 0 then
504       [
505         CoreDoSimplify (SimplPhase 0) [
506             MaxSimplifierIterations max_iter
507         ]
508       ]
509
510      else {- opt_level >= 1 -} [ 
511
512         -- initial simplify: mk specialiser happy: minimum effort please
513         CoreDoSimplify SimplGently [
514                         --      Simplify "gently"
515                         -- Don't inline anything till full laziness has bitten
516                         -- In particular, inlining wrappers inhibits floating
517                         -- e.g. ...(case f x of ...)...
518                         --  ==> ...(case (case x of I# x# -> fw x#) of ...)...
519                         --  ==> ...(case x of I# x# -> case fw x# of ...)...
520                         -- and now the redex (f x) isn't floatable any more
521                         -- Similarly, don't apply any rules until after full 
522                         -- laziness.  Notably, list fusion can prevent floating.
523
524             NoCaseOfCase,
525                         -- Don't do case-of-case transformations.
526                         -- This makes full laziness work better
527             MaxSimplifierIterations max_iter
528         ],
529
530         -- Specialisation is best done before full laziness
531         -- so that overloaded functions have all their dictionary lambdas manifest
532         CoreDoSpecialising,
533
534         if full_laziness then CoreDoFloatOutwards (FloatOutSw False False)
535                          else CoreDoNothing,
536
537         CoreDoFloatInwards,
538
539         CoreDoSimplify (SimplPhase 2) [
540                 -- Want to run with inline phase 2 after the specialiser to give
541                 -- maximum chance for fusion to work before we inline build/augment
542                 -- in phase 1.  This made a difference in 'ansi' where an 
543                 -- overloaded function wasn't inlined till too late.
544            MaxSimplifierIterations max_iter
545         ],
546         case rule_check of { Just pat -> CoreDoRuleCheck 2 pat; Nothing -> CoreDoNothing },
547
548         CoreDoSimplify (SimplPhase 1) [
549                 -- Need inline-phase2 here so that build/augment get 
550                 -- inlined.  I found that spectral/hartel/genfft lost some useful
551                 -- strictness in the function sumcode' if augment is not inlined
552                 -- before strictness analysis runs
553            MaxSimplifierIterations max_iter
554         ],
555         case rule_check of { Just pat -> CoreDoRuleCheck 1 pat; Nothing -> CoreDoNothing },
556
557         CoreDoSimplify (SimplPhase 0) [
558                 -- Phase 0: allow all Ids to be inlined now
559                 -- This gets foldr inlined before strictness analysis
560
561            MaxSimplifierIterations 3
562                 -- At least 3 iterations because otherwise we land up with
563                 -- huge dead expressions because of an infelicity in the 
564                 -- simpifier.   
565                 --      let k = BIG in foldr k z xs
566                 -- ==>  let k = BIG in letrec go = \xs -> ...(k x).... in go xs
567                 -- ==>  let k = BIG in letrec go = \xs -> ...(BIG x).... in go xs
568                 -- Don't stop now!
569
570         ],
571         case rule_check of { Just pat -> CoreDoRuleCheck 0 pat; Nothing -> CoreDoNothing },
572
573 #ifdef OLD_STRICTNESS
574         CoreDoOldStrictness
575 #endif
576         if strictness then CoreDoStrictness else CoreDoNothing,
577         CoreDoWorkerWrapper,
578         CoreDoGlomBinds,
579
580         CoreDoSimplify (SimplPhase 0) [
581            MaxSimplifierIterations max_iter
582         ],
583
584         if full_laziness then
585           CoreDoFloatOutwards (FloatOutSw False   -- Not lambdas
586                                           True)   -- Float constants
587         else CoreDoNothing,
588                 -- nofib/spectral/hartel/wang doubles in speed if you
589                 -- do full laziness late in the day.  It only happens
590                 -- after fusion and other stuff, so the early pass doesn't
591                 -- catch it.  For the record, the redex is 
592                 --        f_el22 (f_el21 r_midblock)
593
594
595         -- We want CSE to follow the final full-laziness pass, because it may
596         -- succeed in commoning up things floated out by full laziness.
597         -- CSE used to rely on the no-shadowing invariant, but it doesn't any more
598
599         if cse then CoreCSE else CoreDoNothing,
600
601         CoreDoFloatInwards,
602
603 -- Case-liberation for -O2.  This should be after
604 -- strictness analysis and the simplification which follows it.
605
606         case rule_check of { Just pat -> CoreDoRuleCheck 0 pat; Nothing -> CoreDoNothing },
607
608         if opt_level >= 2 then
609            CoreLiberateCase
610         else
611            CoreDoNothing,
612         if opt_level >= 2 then
613            CoreDoSpecConstr
614         else
615            CoreDoNothing,
616
617         -- Final clean-up simplification:
618         CoreDoSimplify (SimplPhase 0) [
619           MaxSimplifierIterations max_iter
620         ]
621      ]
622 \end{code}
623
624 %************************************************************************
625 %*                                                                      *
626 \subsection{Warnings}
627 %*                                                                      *
628 %************************************************************************
629
630 \begin{code}
631 standardWarnings
632     = [ Opt_WarnDeprecations,
633         Opt_WarnOverlappingPatterns,
634         Opt_WarnMissingFields,
635         Opt_WarnMissingMethods,
636         Opt_WarnDuplicateExports
637       ]
638
639 minusWOpts
640     = standardWarnings ++ 
641       [ Opt_WarnUnusedBinds,
642         Opt_WarnUnusedMatches,
643         Opt_WarnUnusedImports,
644         Opt_WarnIncompletePatterns,
645         Opt_WarnDodgyImports
646       ]
647
648 minusWallOpts
649     = minusWOpts ++
650       [ Opt_WarnTypeDefaults,
651         Opt_WarnNameShadowing,
652         Opt_WarnMissingSigs,
653         Opt_WarnHiShadows,
654         Opt_WarnOrphans
655       ]
656 \end{code}
657
658 %************************************************************************
659 %*                                                                      *
660 \subsection{Classifying command-line options}
661 %*                                                                      *
662 %************************************************************************
663
664 \begin{code}
665 -- v_Statis_hsc_opts is here to avoid a circular dependency with
666 -- main/DriverState.
667 GLOBAL_VAR(v_Static_hsc_opts, [], [String])
668
669 lookUp           :: FastString -> Bool
670 lookup_def_int   :: String -> Int -> Int
671 lookup_def_float :: String -> Float -> Float
672 lookup_str       :: String -> Maybe String
673
674 unpacked_static_opts = unsafePerformIO (readIORef v_Static_hsc_opts)
675 packed_static_opts   = map mkFastString unpacked_static_opts
676
677 lookUp     sw = sw `elem` packed_static_opts
678         
679 -- (lookup_str "foo") looks for the flag -foo=X or -fooX, 
680 -- and returns the string X
681 lookup_str sw 
682    = case firstJust (map (startsWith sw) unpacked_static_opts) of
683         Just ('=' : str) -> Just str
684         Just str         -> Just str
685         Nothing          -> Nothing     
686
687 lookup_def_int sw def = case (lookup_str sw) of
688                             Nothing -> def              -- Use default
689                             Just xx -> try_read sw xx
690
691 lookup_def_float sw def = case (lookup_str sw) of
692                             Nothing -> def              -- Use default
693                             Just xx -> try_read sw xx
694
695
696 try_read :: Read a => String -> String -> a
697 -- (try_read sw str) tries to read s; if it fails, it
698 -- bleats about flag sw
699 try_read sw str
700   = case reads str of
701         ((x,_):_) -> x  -- Be forgiving: ignore trailing goop, and alternative parses
702         []        -> ghcError (UsageError ("Malformed argument " ++ str ++ " for flag " ++ sw))
703                         -- ToDo: hack alert. We should really parse the arugments
704                         --       and announce errors in a more civilised way.
705
706
707 {-
708  Putting the compiler options into temporary at-files
709  may turn out to be necessary later on if we turn hsc into
710  a pure Win32 application where I think there's a command-line
711  length limit of 255. unpacked_opts understands the @ option.
712
713 unpacked_opts :: [String]
714 unpacked_opts =
715   concat $
716   map (expandAts) $
717   map unpackFS argv  -- NOT ARGV any more: v_Static_hsc_opts
718   where
719    expandAts ('@':fname) = words (unsafePerformIO (readFile fname))
720    expandAts l = [l]
721 -}
722 \end{code}
723
724 %************************************************************************
725 %*                                                                      *
726 \subsection{Static options}
727 %*                                                                      *
728 %************************************************************************
729
730 \begin{code}
731 -- debugging opts
732 opt_PprStyle_Debug              = lookUp  FSLIT("-dppr-debug")
733 opt_PprUserLength               = lookup_def_int "-dppr-user-length" 5 --ToDo: give this a name
734
735 -- profiling opts
736 opt_AutoSccsOnAllToplevs        = lookUp  FSLIT("-fauto-sccs-on-all-toplevs")
737 opt_AutoSccsOnExportedToplevs   = lookUp  FSLIT("-fauto-sccs-on-exported-toplevs")
738 opt_AutoSccsOnIndividualCafs    = lookUp  FSLIT("-fauto-sccs-on-individual-cafs")
739 opt_SccProfilingOn              = lookUp  FSLIT("-fscc-profiling")
740 opt_DoTickyProfiling            = lookUp  FSLIT("-fticky-ticky")
741
742 -- language opts
743 opt_AllStrict                   = lookUp  FSLIT("-fall-strict")
744 opt_DictsStrict                 = lookUp  FSLIT("-fdicts-strict")
745 opt_IrrefutableTuples           = lookUp  FSLIT("-firrefutable-tuples")
746 opt_MaxContextReductionDepth    = lookup_def_int "-fcontext-stack" mAX_CONTEXT_REDUCTION_DEPTH
747 opt_Parallel                    = lookUp  FSLIT("-fparallel")
748 opt_SMP                         = lookUp  FSLIT("-fsmp")
749 opt_Flatten                     = lookUp  FSLIT("-fflatten")
750
751 -- optimisation opts
752 opt_NoStateHack                 = lookUp  FSLIT("-fno-state-hack")
753 opt_NoMethodSharing             = lookUp  FSLIT("-fno-method-sharing")
754 opt_CprOff                      = lookUp  FSLIT("-fcpr-off")
755 opt_RulesOff                    = lookUp  FSLIT("-frules-off")
756         -- Switch off CPR analysis in the new demand analyser
757 opt_LiberateCaseThreshold       = lookup_def_int "-fliberate-case-threshold" (10::Int)
758 opt_MaxWorkerArgs               = lookup_def_int "-fmax-worker-args" (10::Int)
759
760 opt_EmitCExternDecls            = lookUp  FSLIT("-femit-extern-decls")
761 opt_EnsureSplittableC           = lookUp  FSLIT("-fglobalise-toplev-names")
762 opt_GranMacros                  = lookUp  FSLIT("-fgransim")
763 opt_HiVersion                   = read (cProjectVersionInt ++ cProjectPatchLevel) :: Int
764 opt_HistorySize                 = lookup_def_int "-fhistory-size" 20
765 opt_OmitBlackHoling             = lookUp  FSLIT("-dno-black-holing")
766 opt_RuntimeTypes                = lookUp  FSLIT("-fruntime-types")
767
768 -- Simplifier switches
769 opt_SimplNoPreInlining          = lookUp  FSLIT("-fno-pre-inlining")
770         -- NoPreInlining is there just to see how bad things
771         -- get if you don't do it!
772 opt_SimplExcessPrecision        = lookUp  FSLIT("-fexcess-precision")
773
774 -- Unfolding control
775 opt_UF_CreationThreshold        = lookup_def_int "-funfolding-creation-threshold"  (45::Int)
776 opt_UF_UseThreshold             = lookup_def_int "-funfolding-use-threshold"       (8::Int)     -- Discounts can be big
777 opt_UF_FunAppDiscount           = lookup_def_int "-funfolding-fun-discount"        (6::Int)     -- It's great to inline a fn
778 opt_UF_KeenessFactor            = lookup_def_float "-funfolding-keeness-factor"    (1.5::Float)
779 opt_UF_UpdateInPlace            = lookUp  FSLIT("-funfolding-update-in-place")
780
781 opt_UF_DearOp   = ( 4 :: Int)
782                         
783 opt_Static                      = lookUp  FSLIT("-static")
784 opt_Unregisterised              = lookUp  FSLIT("-funregisterised")
785 opt_EmitExternalCore            = lookUp  FSLIT("-fext-core")
786
787 -- Include full span info in error messages, instead of just the start position.
788 opt_ErrorSpans                  = lookUp FSLIT("-ferror-spans")
789
790 opt_PIC                         = lookUp FSLIT("-fPIC")
791 \end{code}
792
793 %************************************************************************
794 %*                                                                      *
795 \subsection{List of static hsc flags}
796 %*                                                                      *
797 %************************************************************************
798
799 \begin{code}
800 isStaticHscFlag f =
801   f `elem` [
802         "fauto-sccs-on-all-toplevs",
803         "fauto-sccs-on-exported-toplevs",
804         "fauto-sccs-on-individual-cafs",
805         "fauto-sccs-on-dicts",
806         "fscc-profiling",
807         "fticky-ticky",
808         "fall-strict",
809         "fdicts-strict",
810         "firrefutable-tuples",
811         "fparallel",
812         "fsmp",
813         "fflatten",
814         "fsemi-tagging",
815         "flet-no-escape",
816         "femit-extern-decls",
817         "fglobalise-toplev-names",
818         "fgransim",
819         "fno-hi-version-check",
820         "dno-black-holing",
821         "fno-method-sharing",
822         "fno-state-hack",
823         "fruntime-types",
824         "fno-pre-inlining",
825         "fexcess-precision",
826         "funfolding-update-in-place",
827         "static",
828         "funregisterised",
829         "fext-core",
830         "frule-check",
831         "frules-off",
832         "fcpr-off",
833         "ferror-spans",
834         "fPIC"
835         ]
836   || any (flip prefixMatch f) [
837         "fcontext-stack",
838         "fliberate-case-threshold",
839         "fmax-worker-args",
840         "fhistory-size",
841         "funfolding-creation-threshold",
842         "funfolding-use-threshold",
843         "funfolding-fun-discount",
844         "funfolding-keeness-factor"
845      ]
846 \end{code}
847
848 %************************************************************************
849 %*                                                                      *
850 \subsection{Misc functions for command-line options}
851 %*                                                                      *
852 %************************************************************************
853
854
855
856 \begin{code}
857 startsWith :: String -> String -> Maybe String
858 -- startsWith pfx (pfx++rest) = Just rest
859
860 startsWith []     str = Just str
861 startsWith (c:cs) (s:ss)
862   = if c /= s then Nothing else startsWith cs ss
863 startsWith  _     []  = Nothing
864
865 endsWith  :: String -> String -> Maybe String
866 endsWith cs ss
867   = case (startsWith (reverse cs) (reverse ss)) of
868       Nothing -> Nothing
869       Just rs -> Just (reverse rs)
870 \end{code}