06b9cf75028a57012d10f189c3bca6e02a84b85b
[ghc-hetmet.git] / ghc / compiler / main / CmdLineOpts.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1996-98
3 %
4 \section[CmdLineOpts]{Things to do with command-line options}
5
6 \begin{code}
7 module CmdLineOpts (
8         CoreToDo(..),
9         SimplifierSwitch(..),
10         StgToDo(..),
11         SwitchResult(..),
12         classifyOpts,
13
14         intSwitchSet,
15         switchIsOn,
16
17         -- debugging opts
18         opt_D_dump_absC,
19         opt_D_dump_asm,
20         opt_D_dump_cpranal,
21         opt_D_dump_deriv,
22         opt_D_dump_ds,
23         opt_D_dump_flatC,
24         opt_D_dump_foreign,
25         opt_D_dump_inlinings,
26         opt_D_dump_occur_anal,
27         opt_D_dump_rdr,
28         opt_D_dump_realC,
29         opt_D_dump_rn,
30         opt_D_dump_rules,
31         opt_D_dump_simpl,
32         opt_D_dump_simpl_iterations,
33         opt_D_dump_simpl_stats,
34         opt_D_dump_spec,
35         opt_D_dump_stg,
36         opt_D_dump_stranal,
37         opt_D_dump_tc,
38         opt_D_dump_usagesp,
39         opt_D_dump_worker_wrapper,
40         opt_D_show_passes,
41         opt_D_dump_rn_trace,
42         opt_D_dump_rn_stats,
43         opt_D_source_stats,
44         opt_D_verbose_core2core,
45         opt_D_verbose_stg2stg,
46         opt_DoCoreLinting,
47         opt_DoStgLinting,
48         opt_DoUSPLinting,
49         opt_PprStyle_Debug,
50         opt_PprStyle_NoPrags,
51         opt_PprUserLength,
52
53         -- warning opts
54         opt_WarnDuplicateExports,
55         opt_WarnHiShadows,
56         opt_WarnIncompletePatterns,
57         opt_WarnMissingMethods,
58         opt_WarnMissingSigs,
59         opt_WarnNameShadowing,
60         opt_WarnOverlappingPatterns,
61         opt_WarnSimplePatterns,
62         opt_WarnTypeDefaults,
63         opt_WarnUnusedBinds,
64         opt_WarnUnusedImports,
65         opt_WarnUnusedMatches,
66
67         -- profiling opts
68         opt_AutoSccsOnAllToplevs,
69         opt_AutoSccsOnExportedToplevs,
70         opt_AutoSccsOnIndividualCafs,
71         opt_AutoSccsOnDicts,
72         opt_SccGroup,
73         opt_SccProfilingOn,
74         opt_DoTickyProfiling,
75
76         -- language opts
77         opt_AllStrict,
78         opt_DictsStrict,
79         opt_MaxContextReductionDepth,
80         opt_AllowOverlappingInstances,
81         opt_AllowUndecidableInstances,
82         opt_GlasgowExts,
83         opt_IrrefutableTuples,
84         opt_NumbersStrict,
85         opt_Parallel,
86
87         -- optimisation opts
88         opt_DoEtaReduction,
89         opt_DoSemiTagging,
90         opt_FoldrBuildOn,
91         opt_LiberateCaseThreshold,
92         opt_NoPreInlining,
93         opt_StgDoLetNoEscapes,
94         opt_UnfoldCasms,
95         opt_UsageSPOn,
96         opt_UnboxStrictFields,
97         opt_SimplNoPreInlining,
98         opt_SimplDoEtaReduction,
99         opt_SimplDoCaseElim,
100         opt_SimplDoLambdaEtaExpansion,
101         opt_SimplCaseOfCase,
102         opt_SimplCaseMerge,
103         opt_SimplLetToCase,
104         opt_SimplPedanticBottoms,
105
106         -- Unfolding control
107         opt_UF_HiFileThreshold,
108         opt_UF_CreationThreshold,
109         opt_UF_UseThreshold,
110         opt_UF_ScrutConDiscount,
111         opt_UF_FunAppDiscount,
112         opt_UF_PrimArgDiscount,
113         opt_UF_KeenessFactor,
114         opt_UF_CheapOp,
115         opt_UF_DearOp,
116         opt_UF_NoRepLit,
117
118         -- misc opts
119         opt_CompilingPrelude,
120         opt_EmitCExternDecls,
121         opt_EnsureSplittableC,
122         opt_GranMacros,
123         opt_HiMap,
124         opt_HiVersion,
125         opt_HistorySize,
126         opt_IgnoreAsserts,
127         opt_IgnoreIfacePragmas,
128         opt_NoHiCheck,
129         opt_NoImplicitPrelude,
130         opt_OmitBlackHoling,
131         opt_OmitInterfacePragmas,
132         opt_ProduceC,
133         opt_ProduceExportCStubs,
134         opt_ProduceExportHStubs,
135         opt_ProduceHi,
136         opt_ProduceS,
137         opt_NoPruneDecls,
138         opt_ReportCompile,
139         opt_SourceUnchanged,
140         opt_Static,
141         opt_Unregisterised,
142         opt_Verbose,
143
144         -- Code generation
145         opt_UseVanillaRegs,
146         opt_UseFloatRegs,
147         opt_UseDoubleRegs,
148         opt_UseLongRegs
149     ) where
150
151 #include "HsVersions.h"
152
153 import Array    ( array, (//) )
154 import GlaExts
155 import Argv
156 import Constants        -- Default values for some flags
157
158 import Maybes           ( assocMaybe, firstJust, maybeToBool )
159 import Panic            ( panic, panic# )
160
161 #if __GLASGOW_HASKELL__ < 301
162 import ArrBase  ( Array(..) )
163 #else
164 import PrelArr  ( Array(..) )
165 #endif
166 \end{code}
167
168 A command-line {\em switch} is (generally) either on or off; e.g., the
169 ``verbose'' (-v) switch is either on or off.  (The \tr{-G<group>}
170 switch is an exception; it's set to a string, or nothing.)
171
172 A list of {\em ToDo}s is things to be done in a particular part of
173 processing.  A (fictitious) example for the Core-to-Core simplifier
174 might be: run the simplifier, then run the strictness analyser, then
175 run the simplifier again (three ``todos'').
176
177 There are three ``to-do processing centers'' at the moment.  In the
178 main loop (\tr{main/Main.lhs}), in the Core-to-Core processing loop
179 (\tr{simplCore/SimplCore.lhs), and in the STG-to-STG processing loop
180 (\tr{simplStg/SimplStg.lhs}).
181
182
183 %************************************************************************
184 %*                                                                      *
185 \subsection{Datatypes associated with command-line options}
186 %*                                                                      *
187 %************************************************************************
188
189 \begin{code}
190 data SwitchResult
191   = SwBool      Bool            -- on/off
192   | SwString    FAST_STRING     -- nothing or a String
193   | SwInt       Int             -- nothing or an Int
194 \end{code}
195
196 \begin{code}
197 data CoreToDo           -- These are diff core-to-core passes,
198                         -- which may be invoked in any order,
199                         -- as many times as you like.
200
201   = CoreDoSimplify      -- The core-to-core simplifier.
202         (SimplifierSwitch -> SwitchResult)
203                         -- Each run of the simplifier can take a different
204                         -- set of simplifier-specific flags.
205   | CoreDoFloatInwards
206   | CoreDoFullLaziness
207   | CoreLiberateCase
208   | CoreDoPrintCore
209   | CoreDoStaticArgs
210   | CoreDoStrictness
211   | CoreDoWorkerWrapper
212   | CoreDoSpecialising
213   | CoreDoUSPInf
214   | CoreDoCPResult 
215 \end{code}
216
217 \begin{code}
218 data StgToDo
219   = StgDoStaticArgs
220   | StgDoUpdateAnalysis
221   | StgDoLambdaLift
222   | StgDoMassageForProfiling  -- should be (next to) last
223   -- There's also setStgVarInfo, but its absolute "lastness"
224   -- is so critical that it is hardwired in (no flag).
225   | D_stg_stats
226 \end{code}
227
228 \begin{code}
229 data SimplifierSwitch
230   = MaxSimplifierIterations Int
231   | SimplInlinePhase Int
232 \end{code}
233
234 %************************************************************************
235 %*                                                                      *
236 \subsection{Classifying command-line options}
237 %*                                                                      *
238 %************************************************************************
239
240 \begin{code}
241 lookUp           :: FAST_STRING -> Bool
242 lookup_int       :: String -> Maybe Int
243 lookup_def_int   :: String -> Int -> Int
244 lookup_def_float :: String -> Float -> Float
245 lookup_str       :: String -> Maybe String
246
247 lookUp     sw = maybeToBool (assoc_opts sw)
248         
249 lookup_str sw = firstJust (map (startsWith sw) unpacked_opts)
250
251 lookup_int sw = case (lookup_str sw) of
252                   Nothing -> Nothing
253                   Just xx -> Just (read xx)
254
255 lookup_def_int sw def = case (lookup_str sw) of
256                             Nothing -> def              -- Use default
257                             Just xx -> read xx
258
259 lookup_def_float sw def = case (lookup_str sw) of
260                             Nothing -> def              -- Use default
261                             Just xx -> read xx
262
263 assoc_opts    = assocMaybe [ (a, True) | a <- argv ]
264 unpacked_opts = map _UNPK_ argv
265
266 {-
267  Putting the compiler options into temporary at-files
268  may turn out to be necessary later on if we turn hsc into
269  a pure Win32 application where I think there's a command-line
270  length limit of 255. unpacked_opts understands the @ option.
271
272 assoc_opts    = assocMaybe [ (_PK_ a, True) | a <- unpacked_opts ]
273
274 unpacked_opts :: [String]
275 unpacked_opts =
276   concat $
277   map (expandAts) $
278   map _UNPK_ argv
279   where
280    expandAts ('@':fname) = words (unsafePerformIO (readFile fname))
281    expandAts l = [l]
282 -}
283 \end{code}
284
285 \begin{code}
286 -- debugging opts
287 opt_D_dump_absC                 = lookUp  SLIT("-ddump-absC")
288 opt_D_dump_asm                  = lookUp  SLIT("-ddump-asm")
289 opt_D_dump_cpranal              = lookUp  SLIT("-ddump-cpranalyse")
290 opt_D_dump_deriv                = lookUp  SLIT("-ddump-deriv")
291 opt_D_dump_ds                   = lookUp  SLIT("-ddump-ds")
292 opt_D_dump_flatC                = lookUp  SLIT("-ddump-flatC")
293 opt_D_dump_foreign              = lookUp  SLIT("-ddump-foreign-stubs")
294 opt_D_dump_inlinings            = lookUp  SLIT("-ddump-inlinings")
295 opt_D_dump_occur_anal           = lookUp  SLIT("-ddump-occur-anal")
296 opt_D_dump_rdr                  = lookUp  SLIT("-ddump-rdr")
297 opt_D_dump_realC                = lookUp  SLIT("-ddump-realC")
298 opt_D_dump_rn                   = lookUp  SLIT("-ddump-rn")
299 opt_D_dump_simpl                = lookUp  SLIT("-ddump-simpl")
300 opt_D_dump_simpl_iterations     = lookUp  SLIT("-ddump-simpl-iterations")
301 opt_D_dump_spec                 = lookUp  SLIT("-ddump-spec")
302 opt_D_dump_stg                  = lookUp  SLIT("-ddump-stg")
303 opt_D_dump_stranal              = lookUp  SLIT("-ddump-stranal")
304 opt_D_dump_tc                   = lookUp  SLIT("-ddump-tc")
305 opt_D_dump_rules                = lookUp  SLIT("-ddump-rules")
306 opt_D_dump_usagesp              = lookUp  SLIT("-ddump-usagesp")
307 opt_D_dump_worker_wrapper       = lookUp  SLIT("-ddump-workwrap")
308 opt_D_show_passes               = lookUp  SLIT("-dshow-passes")
309 opt_D_dump_rn_trace             = lookUp  SLIT("-ddump-rn-trace")
310 opt_D_dump_rn_stats             = lookUp  SLIT("-ddump-rn-stats")
311 opt_D_dump_simpl_stats          = lookUp  SLIT("-ddump-simpl-stats")
312 opt_D_source_stats              = lookUp  SLIT("-dsource-stats")
313 opt_D_verbose_core2core         = lookUp  SLIT("-dverbose-simpl")
314 opt_D_verbose_stg2stg           = lookUp  SLIT("-dverbose-stg")
315 opt_DoCoreLinting               = lookUp  SLIT("-dcore-lint")
316 opt_DoStgLinting                = lookUp  SLIT("-dstg-lint")
317 opt_DoUSPLinting                = lookUp  SLIT("-dusagesp-lint")
318 opt_PprStyle_NoPrags            = lookUp  SLIT("-dppr-noprags")
319 opt_PprStyle_Debug              = lookUp  SLIT("-dppr-debug")
320 opt_PprUserLength               = lookup_def_int "-dppr-user-length" 5 --ToDo: give this a name
321
322 -- warning opts
323 opt_WarnDuplicateExports        = lookUp  SLIT("-fwarn-duplicate-exports")
324 opt_WarnHiShadows               = lookUp  SLIT("-fwarn-hi-shadowing")
325 opt_WarnIncompletePatterns      = lookUp  SLIT("-fwarn-incomplete-patterns")
326 opt_WarnMissingMethods          = lookUp  SLIT("-fwarn-missing-methods")
327 opt_WarnMissingSigs             = lookUp  SLIT("-fwarn-missing-signatures")
328 opt_WarnNameShadowing           = lookUp  SLIT("-fwarn-name-shadowing")
329 opt_WarnOverlappingPatterns     = lookUp  SLIT("-fwarn-overlapping-patterns")
330 opt_WarnSimplePatterns          = lookUp  SLIT("-fwarn-simple-patterns")
331 opt_WarnTypeDefaults            = lookUp  SLIT("-fwarn-type-defaults")
332 opt_WarnUnusedBinds             = lookUp  SLIT("-fwarn-unused-binds")
333 opt_WarnUnusedImports           = lookUp  SLIT("-fwarn-unused-imports")
334 opt_WarnUnusedMatches           = lookUp  SLIT("-fwarn-unused-matches")
335
336 -- profiling opts
337 opt_AutoSccsOnAllToplevs        = lookUp  SLIT("-fauto-sccs-on-all-toplevs")
338 opt_AutoSccsOnExportedToplevs   = lookUp  SLIT("-fauto-sccs-on-exported-toplevs")
339 opt_AutoSccsOnIndividualCafs    = lookUp  SLIT("-fauto-sccs-on-individual-cafs")
340 opt_AutoSccsOnDicts             = lookUp  SLIT("-fauto-sccs-on-dicts")
341 opt_SccGroup                    = lookup_str "-G="
342 opt_SccProfilingOn              = lookUp  SLIT("-fscc-profiling")
343 opt_DoTickyProfiling            = lookUp  SLIT("-fticky-ticky")
344
345 -- language opts
346 opt_AllStrict                   = lookUp  SLIT("-fall-strict")
347 opt_DictsStrict                 = lookUp  SLIT("-fdicts-strict")
348 opt_AllowOverlappingInstances   = lookUp  SLIT("-fallow-overlapping-instances")
349 opt_AllowUndecidableInstances   = lookUp  SLIT("-fallow-undecidable-instances")
350 opt_GlasgowExts                 = lookUp  SLIT("-fglasgow-exts")
351 opt_IrrefutableTuples           = lookUp  SLIT("-firrefutable-tuples")
352 opt_MaxContextReductionDepth    = lookup_def_int "-fcontext-stack" mAX_CONTEXT_REDUCTION_DEPTH
353 opt_NumbersStrict               = lookUp  SLIT("-fnumbers-strict")
354 opt_Parallel                    = lookUp  SLIT("-fparallel")
355
356 -- optimisation opts
357 opt_DoEtaReduction              = lookUp  SLIT("-fdo-eta-reduction")
358 opt_DoSemiTagging               = lookUp  SLIT("-fsemi-tagging")
359 opt_FoldrBuildOn                = lookUp  SLIT("-ffoldr-build-on")
360 opt_LiberateCaseThreshold       = lookup_def_int "-fliberate-case-threshold" (10::Int)
361 opt_NoPreInlining               = lookUp  SLIT("-fno-pre-inlining")
362 opt_StgDoLetNoEscapes           = lookUp  SLIT("-flet-no-escape")
363 opt_UnfoldCasms                 = lookUp SLIT("-funfold-casms-in-hi-file")
364 opt_UsageSPOn                   = lookUp  SLIT("-fusagesp-on")
365 opt_UnboxStrictFields           = lookUp  SLIT("-funbox-strict-fields")
366
367   {-
368    It's a bit unfortunate to have to re-introduce this chap, but on Win32
369    platforms we do need a way of distinguishing between the case when we're
370    compiling a static version of the Prelude and one that's going to be
371    put into a DLL. Why? Because the compiler's wired in modules need to
372    be attributed as either coming from a DLL or not.
373   -}
374 opt_CompilingPrelude            = lookUp  SLIT("-fcompiling-prelude")
375 opt_EmitCExternDecls            = lookUp  SLIT("-femit-extern-decls")
376 opt_EnsureSplittableC           = lookUp  SLIT("-fglobalise-toplev-names")
377 opt_GranMacros                  = lookUp  SLIT("-fgransim")
378 opt_HiMap                       = lookup_str "-himap="       -- file saying where to look for .hi files
379 opt_HiVersion                   = lookup_def_int "-fhi-version=" 0 -- what version we're compiling.
380 opt_HistorySize                 = lookup_def_int "-fhistory-size" 20
381 opt_IgnoreAsserts               = lookUp  SLIT("-fignore-asserts")
382 opt_IgnoreIfacePragmas          = lookUp  SLIT("-fignore-interface-pragmas")
383 opt_NoHiCheck                   = lookUp  SLIT("-fno-hi-version-check")
384 opt_NoImplicitPrelude           = lookUp  SLIT("-fno-implicit-prelude")
385 opt_OmitBlackHoling             = lookUp  SLIT("-dno-black-holing")
386 opt_OmitInterfacePragmas        = lookUp  SLIT("-fomit-interface-pragmas")
387 opt_ProduceC                    = lookup_str "-C="
388 opt_ProduceExportCStubs         = lookup_str "-F="
389 opt_ProduceExportHStubs         = lookup_str "-FH="
390 opt_ProduceHi                   = lookup_str "-hifile=" -- the one to produce this time 
391
392 -- Simplifier switches
393 opt_SimplNoPreInlining          = lookUp SLIT("-fno-pre-inlining")
394         -- NoPreInlining is there just to see how bad things
395         -- get if you don't do it!
396 opt_SimplDoEtaReduction         = lookUp SLIT("-fdo-eta-reduction")
397 opt_SimplDoCaseElim             = lookUp SLIT("-fdo-case-elim")
398 opt_SimplDoLambdaEtaExpansion   = lookUp SLIT("-fdo-lambda-eta-expansion")
399 opt_SimplCaseOfCase             = lookUp SLIT("-fcase-of-case")
400 opt_SimplCaseMerge              = lookUp SLIT("-fcase-merge")
401 opt_SimplLetToCase              = lookUp SLIT("-flet-to-case")
402 opt_SimplPedanticBottoms        = lookUp SLIT("-fpedantic-bottoms")
403
404 -- Unfolding control
405 opt_UF_HiFileThreshold          = lookup_def_int "-funfolding-interface-threshold" (30::Int)
406 opt_UF_CreationThreshold        = lookup_def_int "-funfolding-creation-threshold"  (30::Int)
407 opt_UF_UseThreshold             = lookup_def_int "-funfolding-use-threshold"       (8::Int)     -- Discounts can be big
408 opt_UF_ScrutConDiscount         = lookup_def_int "-funfolding-con-discount"        (3::Int)
409 opt_UF_FunAppDiscount           = lookup_def_int "-funfolding-fun-discount"        (6::Int)     -- It's great to inline a fn
410 opt_UF_PrimArgDiscount          = lookup_def_int "-funfolding-prim-discount"       (1::Int)
411 opt_UF_KeenessFactor            = lookup_def_float "-funfolding-keeness-factor"    (2.0::Float)
412
413 opt_UF_CheapOp  = ( 1 :: Int)
414 opt_UF_DearOp   = ( 8 :: Int)
415 opt_UF_NoRepLit = ( 20 :: Int)  -- Strings can be pretty big
416                         
417 opt_ProduceS                    = lookup_str "-S="
418 opt_ReportCompile               = lookUp SLIT("-freport-compile")
419 opt_NoPruneDecls                = lookUp SLIT("-fno-prune-decls")
420 opt_SourceUnchanged             = lookUp SLIT("-fsource-unchanged")
421 opt_Static                      = lookUp SLIT("-static")
422 opt_Unregisterised              = lookUp SLIT("-funregisterised")
423 opt_Verbose                     = lookUp SLIT("-v")
424
425 opt_UseVanillaRegs | opt_Unregisterised = 0
426                    | otherwise          = mAX_Real_Vanilla_REG
427 opt_UseFloatRegs   | opt_Unregisterised = 0
428                    | otherwise          = mAX_Real_Float_REG
429 opt_UseDoubleRegs  | opt_Unregisterised = 0
430                    | otherwise          = mAX_Real_Double_REG
431 opt_UseLongRegs    | opt_Unregisterised = 0
432                    | otherwise          = mAX_Real_Long_REG
433 \end{code}
434
435 \begin{code}
436 classifyOpts :: ([CoreToDo],    -- Core-to-Core processing spec
437                  [StgToDo])     -- STG-to-STG   processing spec
438
439 classifyOpts = sep argv [] [] -- accumulators...
440   where
441     sep :: [FAST_STRING]                 -- cmd-line opts (input)
442         -> [CoreToDo] -> [StgToDo]       -- to_do accumulators
443         -> ([CoreToDo], [StgToDo])       -- result
444
445     sep [] core_td stg_td -- all done!
446       = (reverse core_td, reverse stg_td)
447
448 #       define CORE_TD(to_do) sep opts (to_do:core_td) stg_td
449 #       define STG_TD(to_do)  sep opts core_td (to_do:stg_td)
450
451     sep (opt1:opts) core_td stg_td
452       = case (_UNPK_ opt1) of -- the non-"just match a string" options are at the end...
453           ',' : _       -> sep opts core_td stg_td -- it is for the parser
454
455           "-fsimplify"  -> -- gather up SimplifierSwitches specially...
456                            simpl_sep opts defaultSimplSwitches core_td stg_td
457
458           "-ffloat-inwards"  -> CORE_TD(CoreDoFloatInwards)
459           "-ffull-laziness"  -> CORE_TD(CoreDoFullLaziness)
460           "-fliberate-case"  -> CORE_TD(CoreLiberateCase)
461           "-fprint-core"     -> CORE_TD(CoreDoPrintCore)
462           "-fstatic-args"    -> CORE_TD(CoreDoStaticArgs)
463           "-fstrictness"     -> CORE_TD(CoreDoStrictness)
464           "-fworker-wrapper" -> CORE_TD(CoreDoWorkerWrapper)
465           "-fspecialise"     -> CORE_TD(CoreDoSpecialising)
466           "-fusagesp"        -> CORE_TD(CoreDoUSPInf)
467           "-fcpr-analyse"    -> CORE_TD(CoreDoCPResult)
468
469           "-fstg-static-args" -> STG_TD(StgDoStaticArgs)
470           "-fupdate-analysis" -> STG_TD(StgDoUpdateAnalysis)
471           "-dstg-stats"       -> STG_TD(D_stg_stats)
472           "-flambda-lift"     -> STG_TD(StgDoLambdaLift)
473           "-fmassage-stg-for-profiling" -> STG_TD(StgDoMassageForProfiling)
474
475           _ -> -- NB: the driver is really supposed to handle bad options
476                sep opts core_td stg_td
477
478     ----------------
479
480     simpl_sep :: [FAST_STRING]            -- cmd-line opts (input)
481               -> [SimplifierSwitch]       -- simplifier-switch accumulator
482               -> [CoreToDo] -> [StgToDo]  -- to_do accumulators
483               -> ([CoreToDo], [StgToDo])  -- result
484
485         -- "simpl_sep" tailcalls "sep" once it's seen one set
486         -- of SimplifierSwitches for a CoreDoSimplify.
487
488 #ifdef DEBUG
489     simpl_sep input@[] simpl_sw core_td stg_td
490       = panic "simpl_sep []"
491 #endif
492
493         -- The SimplifierSwitches should be delimited by "[" and "]".
494
495     simpl_sep (opt1:opts) simpl_sw core_td stg_td
496       = case (_UNPK_ opt1) of
497           "[" -> simpl_sep opts simpl_sw core_td stg_td
498           "]" -> let
499                     this_simpl = CoreDoSimplify (isAmongSimpl simpl_sw)
500                  in
501                  sep opts (this_simpl : core_td) stg_td
502
503           opt -> case matchSimplSw opt of
504                         Just sw -> simpl_sep opts (sw:simpl_sw) core_td stg_td
505                         Nothing -> simpl_sep opts simpl_sw      core_td stg_td
506
507 matchSimplSw opt
508   = firstJust   [ matchSwInt  opt "-fmax-simplifier-iterations"         MaxSimplifierIterations
509                 , matchSwInt  opt "-finline-phase"                      SimplInlinePhase
510                 ]
511
512 matchSwBool :: String -> String -> a -> Maybe a
513 matchSwBool opt str sw | opt == str = Just sw
514                        | otherwise  = Nothing
515
516 matchSwInt :: String -> String -> (Int -> a) -> Maybe a
517 matchSwInt opt str sw = case startsWith str opt of
518                             Just opt_left -> Just (sw (read opt_left))
519                             Nothing       -> Nothing
520 \end{code}
521
522 %************************************************************************
523 %*                                                                      *
524 \subsection{Switch ordering}
525 %*                                                                      *
526 %************************************************************************
527
528 In spite of the @Produce*@ and @SccGroup@ constructors, these things
529 behave just like enumeration types.
530
531 \begin{code}
532 instance Eq SimplifierSwitch where
533     a == b = tagOf_SimplSwitch a _EQ_ tagOf_SimplSwitch b
534
535 instance Ord SimplifierSwitch where
536     a <  b  = tagOf_SimplSwitch a _LT_ tagOf_SimplSwitch b
537     a <= b  = tagOf_SimplSwitch a _LE_ tagOf_SimplSwitch b
538
539
540 tagOf_SimplSwitch (SimplInlinePhase _)          = ILIT(1)
541 tagOf_SimplSwitch (MaxSimplifierIterations _)   = ILIT(2)
542
543 -- If you add anything here, be sure to change lAST_SIMPL_SWITCH_TAG, too!
544
545 lAST_SIMPL_SWITCH_TAG = 2
546 \end{code}
547
548 %************************************************************************
549 %*                                                                      *
550 \subsection{Switch lookup}
551 %*                                                                      *
552 %************************************************************************
553
554 \begin{code}
555 isAmongSimpl :: [SimplifierSwitch] -> SimplifierSwitch -> SwitchResult
556
557 isAmongSimpl on_switches                -- Switches mentioned later occur *earlier*
558                                         -- in the list; defaults right at the end.
559   = let
560         tidied_on_switches = foldl rm_dups [] on_switches
561                 -- The fold*l* ensures that we keep the latest switches;
562                 -- ie the ones that occur earliest in the list.
563
564         sw_tbl :: Array Int SwitchResult
565         sw_tbl = (array (0, lAST_SIMPL_SWITCH_TAG) -- bounds...
566                         all_undefined)
567                  // defined_elems
568
569         all_undefined = [ (i, SwBool False) | i <- [0 .. lAST_SIMPL_SWITCH_TAG ] ]
570
571         defined_elems = map mk_assoc_elem tidied_on_switches
572     in
573     -- (avoid some unboxing, bounds checking, and other horrible things:)
574     case sw_tbl of { Array bounds_who_needs_'em stuff ->
575     \ switch ->
576         case (indexArray# stuff (tagOf_SimplSwitch switch)) of
577 #if __GLASGOW_HASKELL__ < 400
578           Lift v -> v
579 #elif __GLASGOW_HASKELL__ < 403
580           (# _, v #) -> v
581 #else
582           (# v #) -> v
583 #endif
584     }
585   where
586     mk_assoc_elem k@(MaxSimplifierIterations lvl) = (IBOX(tagOf_SimplSwitch k), SwInt lvl)
587     mk_assoc_elem k@(SimplInlinePhase n)          = (IBOX(tagOf_SimplSwitch k), SwInt n)
588     mk_assoc_elem k                               = (IBOX(tagOf_SimplSwitch k), SwBool True) -- I'm here, Mom!
589
590     -- cannot have duplicates if we are going to use the array thing
591     rm_dups switches_so_far switch
592       = if switch `is_elem` switches_so_far
593         then switches_so_far
594         else switch : switches_so_far
595       where
596         sw `is_elem` []     = False
597         sw `is_elem` (s:ss) = (tagOf_SimplSwitch sw) _EQ_ (tagOf_SimplSwitch s)
598                             || sw `is_elem` ss
599 \end{code}
600
601 Default settings for simplifier switches
602
603 \begin{code}
604 defaultSimplSwitches = [MaxSimplifierIterations 1]
605 \end{code}
606
607 %************************************************************************
608 %*                                                                      *
609 \subsection{Misc functions for command-line options}
610 %*                                                                      *
611 %************************************************************************
612
613
614 \begin{code}
615 switchIsOn :: (switch -> SwitchResult) -> switch -> Bool
616
617 switchIsOn lookup_fn switch
618   = case (lookup_fn switch) of
619       SwBool False -> False
620       _            -> True
621
622 intSwitchSet :: (switch -> SwitchResult)
623              -> (Int -> switch)
624              -> Maybe Int
625
626 intSwitchSet lookup_fn switch
627   = case (lookup_fn (switch (panic "intSwitchSet"))) of
628       SwInt int -> Just int
629       _         -> Nothing
630 \end{code}
631
632 \begin{code}
633 startsWith :: String -> String -> Maybe String
634 -- startsWith pfx (pfx++rest) = Just rest
635
636 startsWith []     str = Just str
637 startsWith (c:cs) (s:ss)
638   = if c /= s then Nothing else startsWith cs ss
639 startsWith  _     []  = Nothing
640
641 endsWith  :: String -> String -> Maybe String
642 endsWith cs ss
643   = case (startsWith (reverse cs) (reverse ss)) of
644       Nothing -> Nothing
645       Just rs -> Just (reverse rs)
646 \end{code}