[project @ 1996-05-17 16:02:43 by partain]
[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("-fcompiling-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_FoldrBuildOn                = lookup  SLIT("-ffoldr-build-on")
189 opt_FoldrBuildTrace             = lookup  SLIT("-ffoldr-build-trace")
190 opt_ForConcurrent               = lookup  SLIT("-fconcurrent")
191 opt_GranMacros                  = lookup  SLIT("-fgransim")
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_PprStyle_All                = lookup  SLIT("-dppr-all")
205 opt_PprStyle_Debug              = lookup  SLIT("-dppr-debug")
206 opt_PprStyle_User               = lookup  SLIT("-dppr-user")
207 opt_ReportWhyUnfoldingsDisallowed= lookup SLIT("-freport-disallowed-unfoldings")
208 opt_SccProfilingOn              = lookup  SLIT("-fscc-profiling")
209 opt_ShowImportSpecs             = lookup  SLIT("-fshow-import-specs")
210 opt_ShowPragmaNameErrs          = lookup  SLIT("-fshow-pragma-name-errs")
211 opt_SigsRequired                = lookup  SLIT("-fsignatures-required")
212 opt_SpecialiseAll               = lookup  SLIT("-fspecialise-all")
213 opt_SpecialiseImports           = lookup  SLIT("-fspecialise-imports")
214 opt_SpecialiseOverloaded        = lookup  SLIT("-fspecialise-overloaded")
215 opt_SpecialiseTrace             = lookup  SLIT("-ftrace-specialisation")
216 opt_SpecialiseUnboxed           = lookup  SLIT("-fspecialise-unboxed")
217 opt_StgDoLetNoEscapes           = lookup  SLIT("-flet-no-escape")
218 opt_Verbose                     = lookup  SLIT("-v")
219 opt_SccGroup                    = lookup_str "-G="
220 opt_ProduceC                    = lookup_str "-C="
221 opt_ProduceS                    = lookup_str "-S="
222 opt_ProduceHi                   = lookup_str "-hifile=" -- the one to produce this time 
223 opt_HiMap                       = lookup_str "-himap="  -- file saying where to look for .hi files
224 opt_EnsureSplittableC           = lookup_str "-fglobalise-toplev-names="
225 opt_UnfoldingUseThreshold       = lookup_int "-funfolding-use-threshold"
226 opt_UnfoldingCreationThreshold  = lookup_int "-funfolding-creation-threshold"
227 opt_UnfoldingOverrideThreshold  = lookup_int "-funfolding-override-threshold"
228 opt_ReturnInRegsThreshold       = lookup_int "-freturn-in-regs-threshold"
229
230 opt_NoImplicitPrelude           = lookup  SLIT("-fno-implicit-prelude")
231 opt_IgnoreIfacePragmas          = lookup  SLIT("-fignore-interface-pragmas")
232 \end{code}
233
234 \begin{code}
235 classifyOpts :: ([CoreToDo],    -- Core-to-Core processing spec
236                  [StgToDo])     -- STG-to-STG   processing spec
237
238 classifyOpts = sep argv [] [] -- accumulators...
239   where
240     sep :: [FAST_STRING]                         -- cmd-line opts (input)
241         -> [CoreToDo] -> [StgToDo]       -- to_do accumulators
242         -> ([CoreToDo], [StgToDo])       -- result
243
244     sep [] core_td stg_td -- all done!
245       = (reverse core_td, reverse stg_td)
246
247 #       define CORE_TD(to_do) sep opts (to_do:core_td) stg_td
248 #       define STG_TD(to_do)  sep opts core_td (to_do:stg_td)
249 #       define IGNORE_ARG()   sep opts core_td stg_td
250
251     sep (opt1:opts) core_td stg_td
252       =
253         case (_UNPK_ opt1) of -- the non-"just match a string" options are at the end...
254
255           ',' : _       -> IGNORE_ARG() -- it is for the parser
256
257           "-fsimplify"  -> -- gather up SimplifierSwitches specially...
258                            simpl_sep opts [] core_td stg_td
259
260           "-fcalc-inlinings1"-> CORE_TD(CoreDoCalcInlinings1)
261           "-fcalc-inlinings2"-> CORE_TD(CoreDoCalcInlinings2)
262           "-ffloat-inwards"  -> CORE_TD(CoreDoFloatInwards)
263           "-ffull-laziness"  -> CORE_TD(CoreDoFullLaziness)
264           "-fliberate-case"  -> CORE_TD(CoreLiberateCase)
265           "-fprint-core"     -> CORE_TD(CoreDoPrintCore)
266           "-fstatic-args"    -> CORE_TD(CoreDoStaticArgs)
267           "-fstrictness"     -> CORE_TD(CoreDoStrictness)
268           "-fspecialise"     -> CORE_TD(CoreDoSpecialising)
269           "-fdeforest"       -> CORE_TD(CoreDoDeforest)
270           "-fadd-auto-sccs"  -> CORE_TD(CoreDoAutoCostCentres)
271           "-ffoldr-build-worker-wrapper"  -> CORE_TD(CoreDoFoldrBuildWorkerWrapper)
272           "-ffoldr-build-ww-anal"  -> CORE_TD(CoreDoFoldrBuildWWAnal)
273
274           "-fstg-static-args" -> STG_TD(StgDoStaticArgs)
275           "-fupdate-analysis" -> STG_TD(StgDoUpdateAnalysis)
276           "-dstg-stats"       -> STG_TD(D_stg_stats)
277           "-flambda-lift"     -> STG_TD(StgDoLambdaLift)
278           "-fmassage-stg-for-profiling" -> STG_TD(StgDoMassageForProfiling)
279
280           _ -> -- NB: the driver is really supposed to handle bad options
281                IGNORE_ARG()
282
283     ----------------
284
285     simpl_sep :: [FAST_STRING]      -- cmd-line opts (input)
286         -> [SimplifierSwitch]       -- simplifier-switch accumulator
287         -> [CoreToDo] -> [StgToDo]  -- to_do accumulators
288         -> ([CoreToDo], [StgToDo])  -- result
289
290         -- "simpl_sep" tailcalls "sep" once it's seen one set
291         -- of SimplifierSwitches for a CoreDoSimplify.
292
293 #ifdef DEBUG
294     simpl_sep input@[] simpl_sw core_td stg_td
295       = panic "simpl_sep []"
296 #endif
297
298         -- The SimplifierSwitches should be delimited by "(" and ")".
299
300     simpl_sep (opt1:opts) simpl_sw core_td stg_td
301       = case (_UNPK_ opt1) of
302           "(" -> ASSERT (null simpl_sw)
303                  simpl_sep opts [] core_td stg_td
304           ")" -> let
305                     this_simpl = CoreDoSimplify (isAmongSimpl simpl_sw)
306                  in
307                  sep opts (this_simpl : core_td) stg_td
308
309 #         define SIMPL_SW(sw) simpl_sep opts (sw:simpl_sw) core_td stg_td
310
311           -- the non-"just match a string" options are at the end...
312           "-fshow-simplifier-progress"      -> SIMPL_SW(ShowSimplifierProgress)
313           "-fcode-duplication-ok"           -> SIMPL_SW(SimplOkToDupCode)
314           "-ffloat-lets-exposing-whnf"      -> SIMPL_SW(SimplFloatLetsExposingWHNF)
315           "-ffloat-primops-ok"              -> SIMPL_SW(SimplOkToFloatPrimOps)
316           "-falways-float-lets-from-lets"   -> SIMPL_SW(SimplAlwaysFloatLetsFromLets)
317           "-fdo-case-elim"                  -> SIMPL_SW(SimplDoCaseElim)
318           "-fdo-eta-reduction"              -> SIMPL_SW(SimplDoEtaReduction)
319           "-fdo-lambda-eta-expansion"       -> SIMPL_SW(SimplDoLambdaEtaExpansion)
320           "-fdo-foldr-build"                -> SIMPL_SW(SimplDoFoldrBuild)
321           "-fdo-not-fold-back-append"       -> SIMPL_SW(SimplDontFoldBackAppend)
322           "-fdo-arity-expand"               -> SIMPL_SW(SimplDoArityExpand)
323           "-fdo-inline-foldr-build"         -> SIMPL_SW(SimplDoInlineFoldrBuild)
324           "-freuse-con"                     -> SIMPL_SW(SimplReuseCon)
325           "-fcase-of-case"                  -> SIMPL_SW(SimplCaseOfCase)
326           "-flet-to-case"                   -> SIMPL_SW(SimplLetToCase)
327           "-fpedantic-bottoms"              -> SIMPL_SW(SimplPedanticBottoms)
328           "-fkeep-spec-pragma-ids"          -> SIMPL_SW(KeepSpecPragmaIds)
329           "-fkeep-unused-bindings"          -> SIMPL_SW(KeepUnusedBindings)
330           "-fmay-delete-conjurable-ids"     -> SIMPL_SW(SimplMayDeleteConjurableIds)
331           "-fessential-unfoldings-only"     -> SIMPL_SW(EssentialUnfoldingsOnly)
332           "-fignore-inline-pragma"          -> SIMPL_SW(IgnoreINLINEPragma)
333           "-fno-let-from-case"              -> SIMPL_SW(SimplNoLetFromCase)
334           "-fno-let-from-app"               -> SIMPL_SW(SimplNoLetFromApp)
335           "-fno-let-from-strict-let"        -> SIMPL_SW(SimplNoLetFromStrictLet)
336
337           o | starts_with_msi  -> SIMPL_SW(MaxSimplifierIterations (read after_msi))
338             | starts_with_suut -> SIMPL_SW(SimplUnfoldingUseThreshold (read after_suut))
339             | starts_with_suct -> SIMPL_SW(SimplUnfoldingCreationThreshold (read after_suct))
340            where
341             maybe_suut          = startsWith "-fsimpl-uf-use-threshold"      o
342             maybe_suct          = startsWith "-fsimpl-uf-creation-threshold" o
343             maybe_msi           = startsWith "-fmax-simplifier-iterations"   o
344             starts_with_suut    = maybeToBool maybe_suut
345             starts_with_suct    = maybeToBool maybe_suct
346             starts_with_msi     = maybeToBool maybe_msi
347             (Just after_suut)   = maybe_suut
348             (Just after_suct)   = maybe_suct
349             (Just after_msi)    = maybe_msi
350
351           _ -> -- NB: the driver is really supposed to handle bad options
352                simpl_sep opts simpl_sw core_td stg_td
353 \end{code}
354
355 %************************************************************************
356 %*                                                                      *
357 \subsection{Switch ordering}
358 %*                                                                      *
359 %************************************************************************
360
361 In spite of the @Produce*@ and @SccGroup@ constructors, these things
362 behave just like enumeration types.
363
364 \begin{code}
365 instance Eq SimplifierSwitch where
366     a == b = tagOf_SimplSwitch a _EQ_ tagOf_SimplSwitch b
367
368 instance Ord SimplifierSwitch where
369     a <  b  = tagOf_SimplSwitch a _LT_ tagOf_SimplSwitch b
370     a <= b  = tagOf_SimplSwitch a _LE_ tagOf_SimplSwitch b
371
372 tagOf_SimplSwitch SimplOkToDupCode              =(ILIT(0) :: FAST_INT)
373 tagOf_SimplSwitch SimplFloatLetsExposingWHNF    = ILIT(1)
374 tagOf_SimplSwitch SimplOkToFloatPrimOps         = ILIT(2)
375 tagOf_SimplSwitch SimplAlwaysFloatLetsFromLets  = ILIT(3)
376 tagOf_SimplSwitch SimplDoCaseElim               = ILIT(4)
377 tagOf_SimplSwitch SimplReuseCon                 = ILIT(5)
378 tagOf_SimplSwitch SimplCaseOfCase               = ILIT(6)
379 tagOf_SimplSwitch SimplLetToCase                = ILIT(7)
380 tagOf_SimplSwitch SimplMayDeleteConjurableIds   = ILIT(9)
381 tagOf_SimplSwitch SimplPedanticBottoms          = ILIT(10)
382 tagOf_SimplSwitch SimplDoArityExpand            = ILIT(11)
383 tagOf_SimplSwitch SimplDoFoldrBuild             = ILIT(12)
384 tagOf_SimplSwitch SimplDoInlineFoldrBuild       = ILIT(14)
385 tagOf_SimplSwitch IgnoreINLINEPragma            = ILIT(15)
386 tagOf_SimplSwitch SimplDoLambdaEtaExpansion     = ILIT(16)
387 tagOf_SimplSwitch SimplDoEtaReduction           = ILIT(18)
388 tagOf_SimplSwitch EssentialUnfoldingsOnly       = ILIT(19)
389 tagOf_SimplSwitch ShowSimplifierProgress        = ILIT(20)
390 tagOf_SimplSwitch (MaxSimplifierIterations _)   = ILIT(21)
391 tagOf_SimplSwitch (SimplUnfoldingUseThreshold _)      = ILIT(22)
392 tagOf_SimplSwitch (SimplUnfoldingCreationThreshold _) = ILIT(23)
393 tagOf_SimplSwitch KeepSpecPragmaIds             = ILIT(24)
394 tagOf_SimplSwitch KeepUnusedBindings            = ILIT(25)
395 tagOf_SimplSwitch SimplNoLetFromCase            = ILIT(26)
396 tagOf_SimplSwitch SimplNoLetFromApp             = ILIT(27)
397 tagOf_SimplSwitch SimplNoLetFromStrictLet       = ILIT(28)
398 tagOf_SimplSwitch SimplDontFoldBackAppend       = ILIT(29)
399 -- If you add anything here, be sure to change lAST_SIMPL_SWITCH_TAG, too!
400
401 tagOf_SimplSwitch _ = panic# "tagOf_SimplSwitch"
402
403 lAST_SIMPL_SWITCH_TAG = IBOX(tagOf_SimplSwitch SimplDontFoldBackAppend)
404 \end{code}
405
406 %************************************************************************
407 %*                                                                      *
408 \subsection{Switch lookup}
409 %*                                                                      *
410 %************************************************************************
411
412 \begin{code}
413 isAmongSimpl :: [SimplifierSwitch] -> SimplifierSwitch -> SwitchResult
414
415 isAmongSimpl on_switches
416   = let
417         tidied_on_switches = foldl rm_dups [] on_switches
418
419         sw_tbl :: Array Int SwitchResult
420
421         sw_tbl = (array (0, lAST_SIMPL_SWITCH_TAG) -- bounds...
422                         all_undefined)
423                  // defined_elems
424
425         all_undefined = [ i := SwBool False | i <- [0 .. lAST_SIMPL_SWITCH_TAG ] ]
426
427         defined_elems = map mk_assoc_elem tidied_on_switches
428     in
429     -- (avoid some unboxing, bounds checking, and other horrible things:)
430     case sw_tbl of { _Array bounds_who_needs_'em stuff ->
431     \ switch ->
432         case (indexArray# stuff (tagOf_SimplSwitch switch)) of
433           _Lift v -> v
434     }
435   where
436     mk_assoc_elem k@(MaxSimplifierIterations lvl) = IBOX(tagOf_SimplSwitch k) := SwInt lvl
437     mk_assoc_elem k@(SimplUnfoldingUseThreshold      i) = IBOX(tagOf_SimplSwitch k) := SwInt i
438     mk_assoc_elem k@(SimplUnfoldingCreationThreshold i) = IBOX(tagOf_SimplSwitch k) := SwInt i
439
440     mk_assoc_elem k = IBOX(tagOf_SimplSwitch k) := SwBool   True -- I'm here, Mom!
441
442     -- cannot have duplicates if we are going to use the array thing
443
444     rm_dups switches_so_far switch
445       = if switch `is_elem` switches_so_far
446         then switches_so_far
447         else switch : switches_so_far
448       where
449         sw `is_elem` []     = False
450         sw `is_elem` (s:ss) = (tagOf_SimplSwitch sw) _EQ_ (tagOf_SimplSwitch s)
451                             || sw `is_elem` ss
452 \end{code}
453
454 %************************************************************************
455 %*                                                                      *
456 \subsection{Misc functions for command-line options}
457 %*                                                                      *
458 %************************************************************************
459
460
461 \begin{code}
462 switchIsOn :: (switch -> SwitchResult) -> switch -> Bool
463
464 switchIsOn lookup_fn switch
465   = case (lookup_fn switch) of
466       SwBool False -> False
467       _            -> True
468
469 stringSwitchSet :: (switch -> SwitchResult)
470                 -> (FAST_STRING -> switch)
471                 -> Maybe FAST_STRING
472
473 stringSwitchSet lookup_fn switch
474   = case (lookup_fn (switch (panic "stringSwitchSet"))) of
475       SwString str -> Just str
476       _            -> Nothing
477
478 intSwitchSet :: (switch -> SwitchResult)
479              -> (Int -> switch)
480              -> Maybe Int
481
482 intSwitchSet lookup_fn switch
483   = case (lookup_fn (switch (panic "intSwitchSet"))) of
484       SwInt int -> Just int
485       _         -> Nothing
486 \end{code}