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