e0a0382b28b652808c2180b7fb03ba511f731fd9
[ghc-hetmet.git] / ghc / compiler / main / CmdLineOpts.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1996
3 %
4 \section[CmdLineOpts]{Things to do with command-line options}
5
6 \begin{code}
7 #include "HsVersions.h"
8
9 module CmdLineOpts where
10
11 import PreludeGlaST     -- bad bad bad boy, Will (_Array internals)
12 import Argv
13
14 CHK_Ubiq() -- debugging consistency check
15
16 import Maybes           ( assocMaybe, firstJust, maybeToBool, Maybe(..) )
17 import Util             ( startsWith, panic, panic#, assertPanic )
18 \end{code}
19
20 A command-line {\em switch} is (generally) either on or off; e.g., the
21 ``verbose'' (-v) switch is either on or off.  (The \tr{-G<group>}
22 switch is an exception; it's set to a string, or nothing.)
23
24 A list of {\em ToDo}s is things to be done in a particular part of
25 processing.  A (fictitious) example for the Core-to-Core simplifier
26 might be: run the simplifier, then run the strictness analyser, then
27 run the simplifier again (three ``todos'').
28
29 There are three ``to-do processing centers'' at the moment.  In the
30 main loop (\tr{main/Main.lhs}), in the Core-to-Core processing loop
31 (\tr{simplCore/SimplCore.lhs), and in the STG-to-STG processing loop
32 (\tr{simplStg/SimplStg.lhs}).
33
34 %************************************************************************
35 %*                                                                      *
36 \subsection{Datatypes associated with command-line options}
37 %*                                                                      *
38 %************************************************************************
39
40 \begin{code}
41 data SwitchResult
42   = SwBool      Bool            -- on/off
43   | SwString    FAST_STRING     -- nothing or a String
44   | SwInt       Int             -- nothing or an Int
45 \end{code}
46
47 \begin{code}
48 data CoreToDo           -- These are diff core-to-core passes,
49                         -- which may be invoked in any order,
50                         -- as many times as you like.
51
52   = CoreDoSimplify      -- The core-to-core simplifier.
53         (SimplifierSwitch -> SwitchResult)
54                         -- Each run of the simplifier can take a different
55                         -- set of simplifier-specific flags.
56   | CoreDoCalcInlinings1
57   | CoreDoCalcInlinings2
58   | CoreDoFloatInwards
59   | CoreDoFullLaziness
60   | CoreLiberateCase
61   | CoreDoPrintCore
62   | CoreDoStaticArgs
63   | CoreDoStrictness
64   | CoreDoSpecialising
65   | CoreDoDeforest
66   | CoreDoAutoCostCentres
67   | CoreDoFoldrBuildWorkerWrapper
68   | CoreDoFoldrBuildWWAnal
69 \end{code}
70
71 \begin{code}
72 data StgToDo
73   = StgDoStaticArgs
74   | StgDoUpdateAnalysis
75   | StgDoLambdaLift
76   | StgDoMassageForProfiling  -- should be (next to) last
77   -- There's also setStgVarInfo, but its absolute "lastness"
78   -- is so critical that it is hardwired in (no flag).
79   | D_stg_stats
80 \end{code}
81
82 \begin{code}
83 data SimplifierSwitch
84   = SimplOkToDupCode
85   | SimplFloatLetsExposingWHNF
86   | SimplOkToFloatPrimOps
87   | SimplAlwaysFloatLetsFromLets
88   | SimplDoCaseElim
89   | SimplReuseCon
90   | SimplCaseOfCase
91   | SimplLetToCase
92   | SimplMayDeleteConjurableIds
93   | SimplPedanticBottoms -- see Simplifier for an explanation
94   | SimplDoArityExpand   -- expand arity of bindings
95   | SimplDoFoldrBuild    -- This is the per-simplification flag;
96                          -- see also FoldrBuildOn, used elsewhere
97                          -- in the compiler.
98   | SimplDoInlineFoldrBuild
99                          -- inline foldr/build (*after* f/b rule is used)
100
101   | IgnoreINLINEPragma
102   | SimplDoLambdaEtaExpansion
103   | SimplDoEtaReduction
104
105   | EssentialUnfoldingsOnly -- never mind the thresholds, only
106                             -- do unfoldings that *must* be done
107                             -- (to saturate constructors and primitives)
108
109   | ShowSimplifierProgress  -- report counts on every interation
110
111   | MaxSimplifierIterations Int
112
113   | SimplUnfoldingUseThreshold      Int -- per-simplification variants
114   | SimplUnfoldingCreationThreshold Int
115
116   | KeepSpecPragmaIds       -- We normally *toss* Ids we can do without
117   | KeepUnusedBindings
118
119   | SimplNoLetFromCase      -- used when turning off floating entirely
120   | SimplNoLetFromApp       -- (for experimentation only) WDP 95/10
121   | SimplNoLetFromStrictLet
122
123   | SimplDontFoldBackAppend
124                         -- we fold `foldr (:)' back into flip (++),
125                         -- but we *don't* want to do it when compiling
126                         -- List.hs, otherwise
127                         -- xs ++ ys = foldr (:) ys xs
128                         -- {- via our loopback -}
129                         -- xs ++ ys = xs ++ ys
130                         -- Oops!
131                         -- So only use this flag inside List.hs
132                         -- (Sigh, what a HACK, Andy.  WDP 96/01)
133 \end{code}
134
135 %************************************************************************
136 %*                                                                      *
137 \subsection{Classifying command-line options}
138 %*                                                                      *
139 %************************************************************************
140
141 \begin{code}
142 lookup     :: FAST_STRING -> Bool
143 lookup_int :: String -> Maybe Int
144 lookup_str :: String -> Maybe String
145
146 lookup     sw = maybeToBool (assoc_opts sw)
147         
148 lookup_str sw = firstJust (map (startsWith sw) unpacked_opts)
149
150 lookup_int sw = case (lookup_str sw) of
151                   Nothing -> Nothing
152                   Just xx -> Just (read xx)
153
154 assoc_opts    = assocMaybe [ (a, True) | a <- argv ]
155 unpacked_opts = map _UNPK_ argv
156 \end{code}
157
158 \begin{code}
159 opt_AllDemanded                 = lookup  SLIT("-fall-demanded")
160 opt_AllStrict                   = lookup  SLIT("-fall-strict")
161 opt_AutoSccsOnAllToplevs        = lookup  SLIT("-fauto-sccs-on-all-toplevs")
162 opt_AutoSccsOnExportedToplevs   = lookup  SLIT("-fauto-sccs-on-exported-toplevs")
163 opt_AutoSccsOnIndividualCafs    = lookup  SLIT("-fauto-sccs-on-individual-cafs")
164 opt_CompilingPrelude            = lookup  SLIT("-prelude")
165 opt_D_dump_absC                 = lookup  SLIT("-ddump-absC")
166 opt_D_dump_asm                  = lookup  SLIT("-ddump-asm")
167 opt_D_dump_deforest             = lookup  SLIT("-ddump-deforest")
168 opt_D_dump_deriv                = lookup  SLIT("-ddump-deriv")
169 opt_D_dump_ds                   = lookup  SLIT("-ddump-ds")
170 opt_D_dump_flatC                = lookup  SLIT("-ddump-flatC")
171 opt_D_dump_occur_anal           = lookup  SLIT("-ddump-occur-anal")
172 opt_D_dump_rdr                  = lookup  SLIT("-ddump-rdr")
173 opt_D_dump_realC                = lookup  SLIT("-ddump-realC")
174 opt_D_dump_rn                   = lookup  SLIT("-ddump-rn")
175 opt_D_dump_simpl                = lookup  SLIT("-ddump-simpl")
176 opt_D_dump_spec                 = lookup  SLIT("-ddump-spec")
177 opt_D_dump_stg                  = lookup  SLIT("-ddump-stg")
178 opt_D_dump_stranal              = lookup  SLIT("-ddump-stranal")
179 opt_D_dump_tc                   = lookup  SLIT("-ddump-tc")
180 opt_D_show_passes               = lookup  SLIT("-dshow-passes")
181 opt_D_simplifier_stats          = lookup  SLIT("-dsimplifier-stats")
182 opt_D_source_stats              = lookup  SLIT("-dsource-stats")
183 opt_D_verbose_core2core         = lookup  SLIT("-dverbose-simpl")
184 opt_D_verbose_stg2stg           = lookup  SLIT("-dverbose-stg")
185 opt_DoCoreLinting               = lookup  SLIT("-dcore-lint")
186 opt_DoSemiTagging               = lookup  SLIT("-fsemi-tagging")
187 opt_DoTickyProfiling            = lookup  SLIT("-fticky-ticky")
188 opt_EmitArityChecks             = lookup  SLIT("-darity-checks")
189 opt_FoldrBuildOn                = lookup  SLIT("-ffoldr-build-on")
190 opt_FoldrBuildTrace             = lookup  SLIT("-ffoldr-build-trace")
191 opt_ForConcurrent               = lookup  SLIT("-fconcurrent")
192 opt_GlasgowExts                 = lookup  SLIT("-fglasgow-exts")
193 opt_Haskell_1_3                 = lookup  SLIT("-fhaskell-1.3")
194 opt_HideBuiltinNames            = lookup  SLIT("-fhide-builtin-names")
195 opt_HideMostBuiltinNames        = lookup  SLIT("-fmin-builtin-names")
196 opt_IgnoreStrictnessPragmas     = lookup  SLIT("-fignore-strictness-pragmas")
197 opt_IrrefutableEverything       = lookup  SLIT("-firrefutable-everything")
198 opt_IrrefutableTuples           = lookup  SLIT("-firrefutable-tuples")
199 opt_WarnNameShadowing           = lookup  SLIT("-fwarn-name-shadowing")
200 opt_NumbersStrict               = lookup  SLIT("-fnumbers-strict")
201 opt_OmitBlackHoling             = lookup  SLIT("-dno-black-holing")
202 opt_OmitDefaultInstanceMethods  = lookup  SLIT("-fomit-default-instance-methods")
203 opt_OmitInterfacePragmas        = lookup  SLIT("-fomit-interface-pragmas")
204 opt_OmitReexportedInstances     = lookup  SLIT("-fomit-reexported-instances")
205 opt_PprStyle_All                = lookup  SLIT("-dppr-all")
206 opt_PprStyle_Debug              = lookup  SLIT("-dppr-debug")
207 opt_PprStyle_User               = lookup  SLIT("-dppr-user")
208 opt_ReportWhyUnfoldingsDisallowed= lookup SLIT("-freport-disallowed-unfoldings")
209 opt_SccProfilingOn              = lookup  SLIT("-fscc-profiling")
210 opt_ShowImportSpecs             = lookup  SLIT("-fshow-import-specs")
211 opt_ShowPragmaNameErrs          = lookup  SLIT("-fshow-pragma-name-errs")
212 opt_SigsRequired                = lookup  SLIT("-fsignatures-required")
213 opt_SpecialiseAll               = lookup  SLIT("-fspecialise-all")
214 opt_SpecialiseImports           = lookup  SLIT("-fspecialise-imports")
215 opt_SpecialiseOverloaded        = lookup  SLIT("-fspecialise-overloaded")
216 opt_SpecialiseTrace             = lookup  SLIT("-ftrace-specialisation")
217 opt_SpecialiseUnboxed           = lookup  SLIT("-fspecialise-unboxed")
218 opt_StgDoLetNoEscapes           = lookup  SLIT("-flet-no-escape")
219 opt_UseGetMentionedVars         = lookup  SLIT("-fuse-get-mentioned-vars")
220 opt_Verbose                     = lookup  SLIT("-v")
221 opt_AsmTarget                   = lookup_str "-fasm="
222 opt_SccGroup                    = lookup_str "-G="
223 opt_ProduceC                    = lookup_str "-C="
224 opt_ProduceS                    = lookup_str "-S="
225 opt_ProduceHi                   = lookup_str "-hifile="
226 opt_ProduceHu                   = lookup_str "-hufile="
227 opt_EnsureSplittableC           = lookup_str "-fglobalise-toplev-names="
228 opt_UnfoldingUseThreshold       = lookup_int "-funfolding-use-threshold"
229 opt_UnfoldingCreationThreshold  = lookup_int "-funfolding-creation-threshold"
230 opt_UnfoldingOverrideThreshold  = lookup_int "-funfolding-override-threshold"
231 opt_ReturnInRegsThreshold       = lookup_int "-freturn-in-regs-threshold"
232
233 opt_NoImplicitPrelude           = lookup  SLIT("-fno-implicit-prelude")
234 opt_IgnoreIfacePragmas          = lookup  SLIT("-fignore-interface-pragmas")
235
236 opt_HiSuffix     = case (lookup_str "-hisuffix=")    of { Nothing -> ".hi" ; Just x -> x }
237 opt_SysHiSuffix  = case (lookup_str "-syshisuffix=") of { Nothing -> ".hi" ; Just x -> x }
238
239 opt_HiDirList    = get_dir_list "-i="
240 opt_SysHiDirList = get_dir_list "-j="
241
242 get_dir_list tag
243   = case (lookup_str tag) of
244       Nothing -> [{-no dirs to search???-}]
245       Just xs -> colon_split xs "" [] -- character and dir accumulators, both reversed...
246   where
247     colon_split []         cacc dacc = reverse (reverse cacc : dacc)
248     colon_split (':' : xs) cacc dacc = colon_split xs "" (reverse cacc : dacc)
249     colon_split ( x  : xs) cacc dacc = colon_split xs (x : cacc) dacc
250
251 -- -hisuf, -hisuf-prelude
252 -- -fno-implicit-prelude
253 -- -fignore-interface-pragmas
254 -- importdirs and sysimport dirs
255 \end{code}
256
257 \begin{code}
258 classifyOpts :: ([CoreToDo],    -- Core-to-Core processing spec
259                  [StgToDo])     -- STG-to-STG   processing spec
260
261 classifyOpts = sep argv [] [] -- accumulators...
262   where
263     sep :: [FAST_STRING]                         -- cmd-line opts (input)
264         -> [CoreToDo] -> [StgToDo]       -- to_do accumulators
265         -> ([CoreToDo], [StgToDo])       -- result
266
267     sep [] core_td stg_td -- all done!
268       = (reverse core_td, reverse stg_td)
269
270 #       define CORE_TD(to_do) sep opts (to_do:core_td) stg_td
271 #       define STG_TD(to_do)  sep opts core_td (to_do:stg_td)
272 #       define IGNORE_ARG()   sep opts core_td stg_td
273
274     sep (opt1:opts) core_td stg_td
275       =
276         case (_UNPK_ opt1) of -- the non-"just match a string" options are at the end...
277
278           ',' : _       -> IGNORE_ARG() -- it is for the parser
279
280           "-fsimplify"  -> -- gather up SimplifierSwitches specially...
281                            simpl_sep opts [] core_td stg_td
282
283           "-fcalc-inlinings1"-> CORE_TD(CoreDoCalcInlinings1)
284           "-fcalc-inlinings2"-> CORE_TD(CoreDoCalcInlinings2)
285           "-ffloat-inwards"  -> CORE_TD(CoreDoFloatInwards)
286           "-ffull-laziness"  -> CORE_TD(CoreDoFullLaziness)
287           "-fliberate-case"  -> CORE_TD(CoreLiberateCase)
288           "-fprint-core"     -> CORE_TD(CoreDoPrintCore)
289           "-fstatic-args"    -> CORE_TD(CoreDoStaticArgs)
290           "-fstrictness"     -> CORE_TD(CoreDoStrictness)
291           "-fspecialise"     -> CORE_TD(CoreDoSpecialising)
292           "-fdeforest"       -> CORE_TD(CoreDoDeforest)
293           "-fadd-auto-sccs"  -> CORE_TD(CoreDoAutoCostCentres)
294           "-ffoldr-build-worker-wrapper"  -> CORE_TD(CoreDoFoldrBuildWorkerWrapper)
295           "-ffoldr-build-ww-anal"  -> CORE_TD(CoreDoFoldrBuildWWAnal)
296
297           "-fstg-static-args" -> STG_TD(StgDoStaticArgs)
298           "-fupdate-analysis" -> STG_TD(StgDoUpdateAnalysis)
299           "-dstg-stats"       -> STG_TD(D_stg_stats)
300           "-flambda-lift"     -> STG_TD(StgDoLambdaLift)
301           "-fmassage-stg-for-profiling" -> STG_TD(StgDoMassageForProfiling)
302
303           _ -> -- NB: the driver is really supposed to handle bad options
304                IGNORE_ARG()
305
306     ----------------
307
308     simpl_sep :: [FAST_STRING]      -- cmd-line opts (input)
309         -> [SimplifierSwitch]       -- simplifier-switch accumulator
310         -> [CoreToDo] -> [StgToDo]  -- to_do accumulators
311         -> ([CoreToDo], [StgToDo])  -- result
312
313         -- "simpl_sep" tailcalls "sep" once it's seen one set
314         -- of SimplifierSwitches for a CoreDoSimplify.
315
316 #ifdef DEBUG
317     simpl_sep input@[] simpl_sw core_td stg_td
318       = panic "simpl_sep []"
319 #endif
320
321         -- The SimplifierSwitches should be delimited by "(" and ")".
322
323     simpl_sep (opt1:opts) simpl_sw core_td stg_td
324       = case (_UNPK_ opt1) of
325           "(" -> ASSERT (null simpl_sw)
326                  simpl_sep opts [] core_td stg_td
327           ")" -> let
328                     this_simpl = CoreDoSimplify (isAmongSimpl simpl_sw)
329                  in
330                  sep opts (this_simpl : core_td) stg_td
331
332 #         define SIMPL_SW(sw) simpl_sep opts (sw:simpl_sw) core_td stg_td
333
334           -- the non-"just match a string" options are at the end...
335           "-fshow-simplifier-progress"      -> SIMPL_SW(ShowSimplifierProgress)
336           "-fcode-duplication-ok"           -> SIMPL_SW(SimplOkToDupCode)
337           "-ffloat-lets-exposing-whnf"      -> SIMPL_SW(SimplFloatLetsExposingWHNF)
338           "-ffloat-primops-ok"              -> SIMPL_SW(SimplOkToFloatPrimOps)
339           "-falways-float-lets-from-lets"   -> SIMPL_SW(SimplAlwaysFloatLetsFromLets)
340           "-fdo-case-elim"                  -> SIMPL_SW(SimplDoCaseElim)
341           "-fdo-eta-reduction"              -> SIMPL_SW(SimplDoEtaReduction)
342           "-fdo-lambda-eta-expansion"       -> SIMPL_SW(SimplDoLambdaEtaExpansion)
343           "-fdo-foldr-build"                -> SIMPL_SW(SimplDoFoldrBuild)
344           "-fdo-not-fold-back-append"       -> SIMPL_SW(SimplDontFoldBackAppend)
345           "-fdo-arity-expand"               -> SIMPL_SW(SimplDoArityExpand)
346           "-fdo-inline-foldr-build"         -> SIMPL_SW(SimplDoInlineFoldrBuild)
347           "-freuse-con"                     -> SIMPL_SW(SimplReuseCon)
348           "-fcase-of-case"                  -> SIMPL_SW(SimplCaseOfCase)
349           "-flet-to-case"                   -> SIMPL_SW(SimplLetToCase)
350           "-fpedantic-bottoms"              -> SIMPL_SW(SimplPedanticBottoms)
351           "-fkeep-spec-pragma-ids"          -> SIMPL_SW(KeepSpecPragmaIds)
352           "-fkeep-unused-bindings"          -> SIMPL_SW(KeepUnusedBindings)
353           "-fmay-delete-conjurable-ids"     -> SIMPL_SW(SimplMayDeleteConjurableIds)
354           "-fessential-unfoldings-only"     -> SIMPL_SW(EssentialUnfoldingsOnly)
355           "-fignore-inline-pragma"          -> SIMPL_SW(IgnoreINLINEPragma)
356           "-fno-let-from-case"              -> SIMPL_SW(SimplNoLetFromCase)
357           "-fno-let-from-app"               -> SIMPL_SW(SimplNoLetFromApp)
358           "-fno-let-from-strict-let"        -> SIMPL_SW(SimplNoLetFromStrictLet)
359
360           o | starts_with_msi  -> SIMPL_SW(MaxSimplifierIterations (read after_msi))
361             | starts_with_suut -> SIMPL_SW(SimplUnfoldingUseThreshold (read after_suut))
362             | starts_with_suct -> SIMPL_SW(SimplUnfoldingCreationThreshold (read after_suct))
363            where
364             maybe_suut          = startsWith "-fsimpl-uf-use-threshold"      o
365             maybe_suct          = startsWith "-fsimpl-uf-creation-threshold" o
366             maybe_msi           = startsWith "-fmax-simplifier-iterations"   o
367             starts_with_suut    = maybeToBool maybe_suut
368             starts_with_suct    = maybeToBool maybe_suct
369             starts_with_msi     = maybeToBool maybe_msi
370             (Just after_suut)   = maybe_suut
371             (Just after_suct)   = maybe_suct
372             (Just after_msi)    = maybe_msi
373
374           _ -> -- NB: the driver is really supposed to handle bad options
375                simpl_sep opts simpl_sw core_td stg_td
376 \end{code}
377
378 %************************************************************************
379 %*                                                                      *
380 \subsection{Switch ordering}
381 %*                                                                      *
382 %************************************************************************
383
384 In spite of the @Produce*@ and @SccGroup@ constructors, these things
385 behave just like enumeration types.
386
387 \begin{code}
388 instance Eq SimplifierSwitch where
389     a == b = tagOf_SimplSwitch a _EQ_ tagOf_SimplSwitch b
390
391 instance Ord SimplifierSwitch where
392     a <  b  = tagOf_SimplSwitch a _LT_ tagOf_SimplSwitch b
393     a <= b  = tagOf_SimplSwitch a _LE_ tagOf_SimplSwitch b
394
395 tagOf_SimplSwitch SimplOkToDupCode              =(ILIT(0) :: FAST_INT)
396 tagOf_SimplSwitch SimplFloatLetsExposingWHNF    = ILIT(1)
397 tagOf_SimplSwitch SimplOkToFloatPrimOps         = ILIT(2)
398 tagOf_SimplSwitch SimplAlwaysFloatLetsFromLets  = ILIT(3)
399 tagOf_SimplSwitch SimplDoCaseElim               = ILIT(4)
400 tagOf_SimplSwitch SimplReuseCon                 = ILIT(5)
401 tagOf_SimplSwitch SimplCaseOfCase               = ILIT(6)
402 tagOf_SimplSwitch SimplLetToCase                = ILIT(7)
403 tagOf_SimplSwitch SimplMayDeleteConjurableIds   = ILIT(9)
404 tagOf_SimplSwitch SimplPedanticBottoms          = ILIT(10)
405 tagOf_SimplSwitch SimplDoArityExpand            = ILIT(11)
406 tagOf_SimplSwitch SimplDoFoldrBuild             = ILIT(12)
407 tagOf_SimplSwitch SimplDoInlineFoldrBuild       = ILIT(14)
408 tagOf_SimplSwitch IgnoreINLINEPragma            = ILIT(15)
409 tagOf_SimplSwitch SimplDoLambdaEtaExpansion     = ILIT(16)
410 tagOf_SimplSwitch SimplDoEtaReduction           = ILIT(18)
411 tagOf_SimplSwitch EssentialUnfoldingsOnly       = ILIT(19)
412 tagOf_SimplSwitch ShowSimplifierProgress        = ILIT(20)
413 tagOf_SimplSwitch (MaxSimplifierIterations _)   = ILIT(21)
414 tagOf_SimplSwitch (SimplUnfoldingUseThreshold _)      = ILIT(22)
415 tagOf_SimplSwitch (SimplUnfoldingCreationThreshold _) = ILIT(23)
416 tagOf_SimplSwitch KeepSpecPragmaIds             = ILIT(24)
417 tagOf_SimplSwitch KeepUnusedBindings            = ILIT(25)
418 tagOf_SimplSwitch SimplNoLetFromCase            = ILIT(26)
419 tagOf_SimplSwitch SimplNoLetFromApp             = ILIT(27)
420 tagOf_SimplSwitch SimplNoLetFromStrictLet       = ILIT(28)
421 tagOf_SimplSwitch SimplDontFoldBackAppend       = ILIT(29)
422 -- If you add anything here, be sure to change lAST_SIMPL_SWITCH_TAG, too!
423
424 tagOf_SimplSwitch _ = panic# "tagOf_SimplSwitch"
425
426 lAST_SIMPL_SWITCH_TAG = IBOX(tagOf_SimplSwitch SimplDontFoldBackAppend)
427 \end{code}
428
429 %************************************************************************
430 %*                                                                      *
431 \subsection{Switch lookup}
432 %*                                                                      *
433 %************************************************************************
434
435 \begin{code}
436 isAmongSimpl :: [SimplifierSwitch] -> SimplifierSwitch -> SwitchResult
437
438 isAmongSimpl on_switches
439   = let
440         tidied_on_switches = foldl rm_dups [] on_switches
441
442         sw_tbl :: Array Int SwitchResult
443
444         sw_tbl = (array (0, lAST_SIMPL_SWITCH_TAG) -- bounds...
445                         all_undefined)
446                  // defined_elems
447
448         all_undefined = [ i := SwBool False | i <- [0 .. lAST_SIMPL_SWITCH_TAG ] ]
449
450         defined_elems = map mk_assoc_elem tidied_on_switches
451     in
452     -- (avoid some unboxing, bounds checking, and other horrible things:)
453     case sw_tbl of { _Array bounds_who_needs_'em stuff ->
454     \ switch ->
455         case (indexArray# stuff (tagOf_SimplSwitch switch)) of
456           _Lift v -> v
457     }
458   where
459     mk_assoc_elem k@(MaxSimplifierIterations lvl) = IBOX(tagOf_SimplSwitch k) := SwInt lvl
460     mk_assoc_elem k@(SimplUnfoldingUseThreshold      i) = IBOX(tagOf_SimplSwitch k) := SwInt i
461     mk_assoc_elem k@(SimplUnfoldingCreationThreshold i) = IBOX(tagOf_SimplSwitch k) := SwInt i
462
463     mk_assoc_elem k = IBOX(tagOf_SimplSwitch k) := SwBool   True -- I'm here, Mom!
464
465     -- cannot have duplicates if we are going to use the array thing
466
467     rm_dups switches_so_far switch
468       = if switch `is_elem` switches_so_far
469         then switches_so_far
470         else switch : switches_so_far
471       where
472         sw `is_elem` []     = False
473         sw `is_elem` (s:ss) = (tagOf_SimplSwitch sw) _EQ_ (tagOf_SimplSwitch s)
474                             || sw `is_elem` ss
475 \end{code}
476
477 %************************************************************************
478 %*                                                                      *
479 \subsection{Misc functions for command-line options}
480 %*                                                                      *
481 %************************************************************************
482
483
484 \begin{code}
485 switchIsOn :: (switch -> SwitchResult) -> switch -> Bool
486
487 switchIsOn lookup_fn switch
488   = case (lookup_fn switch) of
489       SwBool False -> False
490       _            -> True
491
492 stringSwitchSet :: (switch -> SwitchResult)
493                 -> (FAST_STRING -> switch)
494                 -> Maybe FAST_STRING
495
496 stringSwitchSet lookup_fn switch
497   = case (lookup_fn (switch (panic "stringSwitchSet"))) of
498       SwString str -> Just str
499       _            -> Nothing
500
501 intSwitchSet :: (switch -> SwitchResult)
502              -> (Int -> switch)
503              -> Maybe Int
504
505 intSwitchSet lookup_fn switch
506   = case (lookup_fn (switch (panic "intSwitchSet"))) of
507       SwInt int -> Just int
508       _         -> Nothing
509 \end{code}