[project @ 2000-10-17 13:22:10 by simonmar]
[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(..),
10         SimplifierSwitch(..), isAmongSimpl,
11         StgToDo(..),
12         SwitchResult(..),
13         HscLang(..),
14         DynFlag(..),    -- needed non-abstractly by DriverFlags
15         DynFlags(..),
16
17         intSwitchSet,
18         switchIsOn,
19         isStaticHscFlag,
20
21         opt_PprStyle_NoPrags,
22         opt_PprUserLength,
23         opt_PprStyle_Debug,
24
25         dopt,
26
27         -- other dynamic flags
28         dopt_CoreToDo,
29         dopt_StgToDo,
30
31         -- profiling opts
32         opt_AutoSccsOnAllToplevs,
33         opt_AutoSccsOnExportedToplevs,
34         opt_AutoSccsOnIndividualCafs,
35         opt_AutoSccsOnDicts,
36         opt_SccProfilingOn,
37         opt_DoTickyProfiling,
38
39         -- language opts
40         opt_AllStrict,
41         opt_DictsStrict,
42         opt_MaxContextReductionDepth,
43         opt_Generics,
44         opt_IrrefutableTuples,
45         opt_NumbersStrict,
46         opt_Parallel,
47         opt_SMP,
48
49         -- optimisation opts
50         opt_DoSemiTagging,
51         opt_FoldrBuildOn,
52         opt_LiberateCaseThreshold,
53         opt_StgDoLetNoEscapes,
54         opt_UnfoldCasms,
55         opt_UsageSPOn,
56         opt_UnboxStrictFields,
57         opt_SimplNoPreInlining,
58         opt_SimplDoEtaReduction,
59         opt_SimplDoLambdaEtaExpansion,
60         opt_SimplCaseOfCase,
61         opt_SimplCaseMerge,
62         opt_SimplPedanticBottoms,
63         opt_SimplExcessPrecision,
64
65         -- Unfolding control
66         opt_UF_HiFileThreshold,
67         opt_UF_CreationThreshold,
68         opt_UF_UseThreshold,
69         opt_UF_FunAppDiscount,
70         opt_UF_KeenessFactor,
71         opt_UF_UpdateInPlace,
72         opt_UF_CheapOp,
73         opt_UF_DearOp,
74
75         -- misc opts
76         opt_InPackage,
77         opt_EmitCExternDecls,
78         opt_EnsureSplittableC,
79         opt_GranMacros,
80         opt_HiVersion,
81         opt_HistorySize,
82         opt_IgnoreAsserts,
83         opt_IgnoreIfacePragmas,
84         opt_NoHiCheck,
85         opt_NoImplicitPrelude,
86         opt_OmitBlackHoling,
87         opt_OmitInterfacePragmas,
88         opt_NoPruneTyDecls,
89         opt_NoPruneDecls,
90         opt_ReportCompile,
91         opt_Static,
92         opt_Unregisterised,
93         opt_Verbose,
94
95         -- Code generation
96         opt_UseVanillaRegs,
97         opt_UseFloatRegs,
98         opt_UseDoubleRegs,
99         opt_UseLongRegs
100     ) where
101
102 #include "HsVersions.h"
103
104 import Array    ( array, (//) )
105 import GlaExts
106 import Argv
107 import Constants        -- Default values for some flags
108 import Util
109 import FastTypes
110
111 import Maybes           ( firstJust )
112 import Panic            ( panic )
113
114 #if __GLASGOW_HASKELL__ < 301
115 import ArrBase  ( Array(..) )
116 #else
117 import PrelArr  ( Array(..) )
118 #endif
119 \end{code}
120
121 %************************************************************************
122 %*                                                                      *
123 \subsection{Command-line options}
124 %*                                                                      *
125 %************************************************************************
126
127 The hsc command-line options are split into two categories:
128
129   - static flags
130   - dynamic flags
131
132 Static flags are represented by top-level values of type Bool or Int,
133 for example.  They therefore have the same value throughout the
134 invocation of hsc.
135
136 Dynamic flags are represented by an abstract type, DynFlags, which is
137 passed into hsc by the compilation manager for every compilation.
138 Dynamic flags are those that change on a per-compilation basis,
139 perhaps because they may be present in the OPTIONS pragma at the top
140 of a module.
141
142 Other flag-related blurb:
143
144 A list of {\em ToDo}s is things to be done in a particular part of
145 processing.  A (fictitious) example for the Core-to-Core simplifier
146 might be: run the simplifier, then run the strictness analyser, then
147 run the simplifier again (three ``todos'').
148
149 There are three ``to-do processing centers'' at the moment.  In the
150 main loop (\tr{main/Main.lhs}), in the Core-to-Core processing loop
151 (\tr{simplCore/SimplCore.lhs), and in the STG-to-STG processing loop
152 (\tr{simplStg/SimplStg.lhs}).
153
154 %************************************************************************
155 %*                                                                      *
156 \subsection{Datatypes associated with command-line options}
157 %*                                                                      *
158 %************************************************************************
159
160 \begin{code}
161 data SwitchResult
162   = SwBool      Bool            -- on/off
163   | SwString    FAST_STRING     -- nothing or a String
164   | SwInt       Int             -- nothing or an Int
165 \end{code}
166
167 \begin{code}
168 data CoreToDo           -- These are diff core-to-core passes,
169                         -- which may be invoked in any order,
170                         -- as many times as you like.
171
172   = CoreDoSimplify      -- The core-to-core simplifier.
173         (SimplifierSwitch -> SwitchResult)
174                         -- Each run of the simplifier can take a different
175                         -- set of simplifier-specific flags.
176   | CoreDoFloatInwards
177   | CoreDoFloatOutwards Bool    -- True <=> float lambdas to top level
178   | CoreLiberateCase
179   | CoreDoPrintCore
180   | CoreDoStaticArgs
181   | CoreDoStrictness
182   | CoreDoWorkerWrapper
183   | CoreDoSpecialising
184   | CoreDoUSPInf
185   | CoreDoCPResult
186   | CoreDoGlomBinds
187   | CoreCSE
188
189   | CoreDoNothing        -- useful when building up lists of these things
190 \end{code}
191
192 \begin{code}
193 data StgToDo
194   = StgDoStaticArgs
195   | StgDoLambdaLift
196   | StgDoMassageForProfiling  -- should be (next to) last
197   -- There's also setStgVarInfo, but its absolute "lastness"
198   -- is so critical that it is hardwired in (no flag).
199   | D_stg_stats
200 \end{code}
201
202 \begin{code}
203 data SimplifierSwitch
204   = MaxSimplifierIterations Int
205   | SimplInlinePhase Int
206   | DontApplyRules
207   | NoCaseOfCase
208   | SimplLetToCase
209 \end{code}
210
211 %************************************************************************
212 %*                                                                      *
213 \subsection{Dynamic command-line options}
214 %*                                                                      *
215 %************************************************************************
216
217 \begin{code}
218 data DynFlag
219
220    -- debugging flags
221    = Opt_D_dump_all
222    | Opt_D_dump_most
223    | Opt_D_dump_absC
224    | Opt_D_dump_asm
225    | Opt_D_dump_cpranal
226    | Opt_D_dump_deriv
227    | Opt_D_dump_ds
228    | Opt_D_dump_flatC
229    | Opt_D_dump_foreign
230    | Opt_D_dump_inlinings
231    | Opt_D_dump_occur_anal
232    | Opt_D_dump_parsed
233    | Opt_D_dump_realC
234    | Opt_D_dump_rn
235    | Opt_D_dump_simpl
236    | Opt_D_dump_simpl_iterations
237    | Opt_D_dump_spec
238    | Opt_D_dump_stg
239    | Opt_D_dump_stranal
240    | Opt_D_dump_tc
241    | Opt_D_dump_types
242    | Opt_D_dump_rules
243    | Opt_D_dump_usagesp
244    | Opt_D_dump_cse
245    | Opt_D_dump_worker_wrapper
246    | Opt_D_show_passes
247    | Opt_D_dump_rn_trace
248    | Opt_D_dump_rn_stats
249    | Opt_D_dump_stix
250    | Opt_D_dump_simpl_stats
251    | Opt_D_source_stats
252    | Opt_D_verbose_core2core
253    | Opt_D_verbose_stg2stg
254    | Opt_D_dump_hi_diffs
255    | Opt_D_dump_minimal_imports
256    | Opt_DoCoreLinting
257    | Opt_DoStgLinting
258    | Opt_DoUSPLinting
259
260    | Opt_WarnDuplicateExports
261    | Opt_WarnHiShadows
262    | Opt_WarnIncompletePatterns
263    | Opt_WarnMissingFields
264    | Opt_WarnMissingMethods
265    | Opt_WarnMissingSigs
266    | Opt_WarnNameShadowing
267    | Opt_WarnOverlappingPatterns
268    | Opt_WarnSimplePatterns
269    | Opt_WarnTypeDefaults
270    | Opt_WarnUnusedBinds
271    | Opt_WarnUnusedImports
272    | Opt_WarnUnusedMatches
273    | Opt_WarnDeprecations
274
275    -- language opts
276    | Opt_AllowOverlappingInstances
277    | Opt_AllowUndecidableInstances
278    | Opt_GlasgowExts
279    deriving (Eq)
280
281 data DynFlags = DynFlags {
282   coreToDo :: CoreToDo,
283   stgToDo  :: StgToDo,
284   hscLang  :: HscLang,
285   flags    :: [DynFlag]
286  }
287
288 dopt :: DynFlag -> DynFlags -> Bool
289 dopt f dflags  = f `elem` (flags dflags)
290
291 dopt_CoreToDo :: DynFlags -> CoreToDo
292 dopt_CoreToDo = coreToDo
293
294 dopt_StgToDo :: DynFlags -> StgToDo
295 dopt_StgToDo = stgToDo
296
297 data HscLang
298   = HscC
299   | HscAsm
300   | HscJava
301   | HscInterpreter
302   deriving Eq
303
304 dopt_HscLang :: DynFlags -> HscLang
305 dopt_HscLang = hscLang
306 \end{code}
307
308 %************************************************************************
309 %*                                                                      *
310 \subsection{Classifying command-line options}
311 %*                                                                      *
312 %************************************************************************
313
314 \begin{code}
315 lookUp           :: FAST_STRING -> Bool
316 lookup_int       :: String -> Maybe Int
317 lookup_def_int   :: String -> Int -> Int
318 lookup_def_float :: String -> Float -> Float
319 lookup_str       :: String -> Maybe String
320
321 lookUp     sw = sw `elem` argv
322         
323 lookup_str sw = firstJust (map (startsWith sw) unpacked_opts)
324
325 lookup_int sw = case (lookup_str sw) of
326                   Nothing -> Nothing
327                   Just xx -> Just (read xx)
328
329 lookup_def_int sw def = case (lookup_str sw) of
330                             Nothing -> def              -- Use default
331                             Just xx -> read xx
332
333 lookup_def_char sw def = case (lookup_str sw) of
334                             Just (xx:_) -> xx
335                             _           -> def          -- Use default
336
337 lookup_def_float sw def = case (lookup_str sw) of
338                             Nothing -> def              -- Use default
339                             Just xx -> read xx
340
341 unpacked_opts = map _UNPK_ argv
342
343 {-
344  Putting the compiler options into temporary at-files
345  may turn out to be necessary later on if we turn hsc into
346  a pure Win32 application where I think there's a command-line
347  length limit of 255. unpacked_opts understands the @ option.
348
349 unpacked_opts :: [String]
350 unpacked_opts =
351   concat $
352   map (expandAts) $
353   map _UNPK_ argv
354   where
355    expandAts ('@':fname) = words (unsafePerformIO (readFile fname))
356    expandAts l = [l]
357 -}
358 \end{code}
359
360 %************************************************************************
361 %*                                                                      *
362 \subsection{Static options}
363 %*                                                                      *
364 %************************************************************************
365
366 \begin{code}
367 -- debugging opts
368 opt_PprStyle_NoPrags            = lookUp  SLIT("-dppr-noprags")
369 opt_PprStyle_Debug              = lookUp  SLIT("-dppr-debug")
370 opt_PprUserLength               = lookup_def_int "-dppr-user-length" 5 --ToDo: give this a name
371
372 -- profiling opts
373 opt_AutoSccsOnAllToplevs        = lookUp  SLIT("-fauto-sccs-on-all-toplevs")
374 opt_AutoSccsOnExportedToplevs   = lookUp  SLIT("-fauto-sccs-on-exported-toplevs")
375 opt_AutoSccsOnIndividualCafs    = lookUp  SLIT("-fauto-sccs-on-individual-cafs")
376 opt_AutoSccsOnDicts             = lookUp  SLIT("-fauto-sccs-on-dicts")
377 opt_SccProfilingOn              = lookUp  SLIT("-fscc-profiling")
378 opt_DoTickyProfiling            = lookUp  SLIT("-fticky-ticky")
379
380 -- language opts
381 opt_AllStrict                   = lookUp  SLIT("-fall-strict")
382 opt_DictsStrict                 = lookUp  SLIT("-fdicts-strict")
383 opt_Generics                    = lookUp  SLIT("-fgenerics")
384 opt_IrrefutableTuples           = lookUp  SLIT("-firrefutable-tuples")
385 opt_MaxContextReductionDepth    = lookup_def_int "-fcontext-stack" mAX_CONTEXT_REDUCTION_DEPTH
386 opt_NumbersStrict               = lookUp  SLIT("-fnumbers-strict")
387 opt_Parallel                    = lookUp  SLIT("-fparallel")
388 opt_SMP                         = lookUp  SLIT("-fsmp")
389
390 -- optimisation opts
391 opt_DoSemiTagging               = lookUp  SLIT("-fsemi-tagging")
392 opt_FoldrBuildOn                = lookUp  SLIT("-ffoldr-build-on")
393 opt_LiberateCaseThreshold       = lookup_def_int "-fliberate-case-threshold" (10::Int)
394 opt_StgDoLetNoEscapes           = lookUp  SLIT("-flet-no-escape")
395 opt_UnfoldCasms                 = lookUp SLIT("-funfold-casms-in-hi-file")
396 opt_UsageSPOn                   = lookUp  SLIT("-fusagesp-on")
397 opt_UnboxStrictFields           = lookUp  SLIT("-funbox-strict-fields")
398
399 {-
400    The optional '-inpackage=P' flag tells what package
401    we are compiling this module for.
402    The Prelude, for example is compiled with '-package prelude'
403 -}
404 opt_InPackage                   = case lookup_str "-inpackage=" of
405                                     Just p  -> _PK_ p
406                                     Nothing -> SLIT("Main")     -- The package name if none is specified
407
408 opt_EmitCExternDecls            = lookUp  SLIT("-femit-extern-decls")
409 opt_EnsureSplittableC           = lookUp  SLIT("-fglobalise-toplev-names")
410 opt_GranMacros                  = lookUp  SLIT("-fgransim")
411 opt_HiVersion                   = lookup_def_int "-fhi-version=" 0 -- what version we're compiling.
412 opt_HistorySize                 = lookup_def_int "-fhistory-size" 20
413 opt_IgnoreAsserts               = lookUp  SLIT("-fignore-asserts")
414 opt_IgnoreIfacePragmas          = lookUp  SLIT("-fignore-interface-pragmas")
415 opt_NoHiCheck                   = lookUp  SLIT("-fno-hi-version-check")
416 opt_NoImplicitPrelude           = lookUp  SLIT("-fno-implicit-prelude")
417 opt_OmitBlackHoling             = lookUp  SLIT("-dno-black-holing")
418 opt_OmitInterfacePragmas        = lookUp  SLIT("-fomit-interface-pragmas")
419
420 -- Simplifier switches
421 opt_SimplNoPreInlining          = lookUp SLIT("-fno-pre-inlining")
422         -- NoPreInlining is there just to see how bad things
423         -- get if you don't do it!
424 opt_SimplDoEtaReduction         = lookUp SLIT("-fdo-eta-reduction")
425 opt_SimplDoLambdaEtaExpansion   = lookUp SLIT("-fdo-lambda-eta-expansion")
426 opt_SimplCaseOfCase             = lookUp SLIT("-fcase-of-case")
427 opt_SimplCaseMerge              = lookUp SLIT("-fcase-merge")
428 opt_SimplPedanticBottoms        = lookUp SLIT("-fpedantic-bottoms")
429 opt_SimplExcessPrecision        = lookUp SLIT("-fexcess-precision")
430
431 -- Unfolding control
432 opt_UF_HiFileThreshold          = lookup_def_int "-funfolding-interface-threshold" (45::Int)
433 opt_UF_CreationThreshold        = lookup_def_int "-funfolding-creation-threshold"  (45::Int)
434 opt_UF_UseThreshold             = lookup_def_int "-funfolding-use-threshold"       (8::Int)     -- Discounts can be big
435 opt_UF_FunAppDiscount           = lookup_def_int "-funfolding-fun-discount"        (6::Int)     -- It's great to inline a fn
436 opt_UF_KeenessFactor            = lookup_def_float "-funfolding-keeness-factor"    (1.5::Float)
437 opt_UF_UpdateInPlace            = lookUp  SLIT("-funfolding-update-in-place")
438
439 opt_UF_CheapOp  = ( 1 :: Int)   -- Only one instruction; and the args are charged for
440 opt_UF_DearOp   = ( 4 :: Int)
441                         
442 opt_ReportCompile               = lookUp SLIT("-freport-compile")
443 opt_NoPruneDecls                = lookUp SLIT("-fno-prune-decls")
444 opt_NoPruneTyDecls              = lookUp SLIT("-fno-prune-tydecls")
445 opt_Static                      = lookUp SLIT("-static")
446 opt_Unregisterised              = lookUp SLIT("-funregisterised")
447 opt_Verbose                     = lookUp SLIT("-v")
448
449 opt_UseVanillaRegs | opt_Unregisterised = 0
450                    | otherwise          = mAX_Real_Vanilla_REG
451 opt_UseFloatRegs   | opt_Unregisterised = 0
452                    | otherwise          = mAX_Real_Float_REG
453 opt_UseDoubleRegs  | opt_Unregisterised = 0
454                    | otherwise          = mAX_Real_Double_REG
455 opt_UseLongRegs    | opt_Unregisterised = 0
456                    | otherwise          = mAX_Real_Long_REG
457 \end{code}
458
459 %************************************************************************
460 %*                                                                      *
461 \subsection{List of static hsc flags}
462 %*                                                                      *
463 %************************************************************************
464
465 \begin{code}
466 isStaticHscFlag f =
467   f `elem` [
468         "-fauto-sccs-on-all-toplevs",
469         "-fauto-sccs-on-exported-toplevs",
470         "-fauto-sccs-on-individual-cafs",
471         "-fauto-sccs-on-dicts",
472         "-fscc-profiling",
473         "-fticky-ticky",
474         "-fall-strict",
475         "-fdicts-strict",
476         "-fgenerics",
477         "-firrefutable-tuples",
478         "-fnumbers-strict",
479         "-fparallel",
480         "-fsmp",
481         "-fsemi-tagging",
482         "-ffoldr-build-on",
483         "-flet-no-escape",
484         "-funfold-casms-in-hi-file",
485         "-fusagesp-on",
486         "-funbox-strict-fields",
487         "-femit-extern-decls",
488         "-fglobalise-toplev-names",
489         "-fgransim",
490         "-fignore-asserts",
491         "-fignore-interface-pragmas",
492         "-fno-hi-version-check",
493         "-fno-implicit-prelude",
494         "-dno-black-holing",
495         "-fomit-interface-pragmas",
496         "-fno-pre-inlining",
497         "-fdo-eta-reduction",
498         "-fdo-lambda-eta-expansion",
499         "-fcase-of-case",
500         "-fcase-merge",
501         "-fpedantic-bottoms",
502         "-fexcess-precision",
503         "-funfolding-update-in-place",
504         "-freport-compile",
505         "-fno-prune-decls",
506         "-fno-prune-tydecls",
507         "-static",
508         "-funregisterised",
509         "-v" ]
510   || any (flip prefixMatch f) [
511         "-fcontext-stack",
512         "-fliberate-case-threshold",
513         "-fhi-version=",
514         "-fhistory-size",
515         "-funfolding-interface-threshold",
516         "-funfolding-creation-threshold",
517         "-funfolding-use-threshold",
518         "-funfolding-fun-discount",
519         "-funfolding-keeness-factor"
520      ]
521 \end{code}
522
523 %************************************************************************
524 %*                                                                      *
525 \subsection{Switch ordering}
526 %*                                                                      *
527 %************************************************************************
528
529 These things behave just like enumeration types.
530
531 \begin{code}
532 instance Eq SimplifierSwitch where
533     a == b = tagOf_SimplSwitch a ==# tagOf_SimplSwitch b
534
535 instance Ord SimplifierSwitch where
536     a <  b  = tagOf_SimplSwitch a <# tagOf_SimplSwitch b
537     a <= b  = tagOf_SimplSwitch a <=# tagOf_SimplSwitch b
538
539
540 tagOf_SimplSwitch (SimplInlinePhase _)          = _ILIT(1)
541 tagOf_SimplSwitch (MaxSimplifierIterations _)   = _ILIT(2)
542 tagOf_SimplSwitch DontApplyRules                = _ILIT(3)
543 tagOf_SimplSwitch SimplLetToCase                = _ILIT(4)
544 tagOf_SimplSwitch NoCaseOfCase                  = _ILIT(5)
545
546 -- If you add anything here, be sure to change lAST_SIMPL_SWITCH_TAG, too!
547
548 lAST_SIMPL_SWITCH_TAG = 5
549 \end{code}
550
551 %************************************************************************
552 %*                                                                      *
553 \subsection{Switch lookup}
554 %*                                                                      *
555 %************************************************************************
556
557 \begin{code}
558 isAmongSimpl :: [SimplifierSwitch] -> SimplifierSwitch -> SwitchResult
559 isAmongSimpl on_switches                -- Switches mentioned later occur *earlier*
560                                         -- in the list; defaults right at the end.
561   = let
562         tidied_on_switches = foldl rm_dups [] on_switches
563                 -- The fold*l* ensures that we keep the latest switches;
564                 -- ie the ones that occur earliest in the list.
565
566         sw_tbl :: Array Int SwitchResult
567         sw_tbl = (array (0, lAST_SIMPL_SWITCH_TAG) -- bounds...
568                         all_undefined)
569                  // defined_elems
570
571         all_undefined = [ (i, SwBool False) | i <- [0 .. lAST_SIMPL_SWITCH_TAG ] ]
572
573         defined_elems = map mk_assoc_elem tidied_on_switches
574     in
575     -- (avoid some unboxing, bounds checking, and other horrible things:)
576 #if __GLASGOW_HASKELL__ < 405
577     case sw_tbl of { Array bounds_who_needs_'em stuff ->
578 #else
579     case sw_tbl of { Array _ _ stuff ->
580 #endif
581     \ switch ->
582         case (indexArray# stuff (tagOf_SimplSwitch switch)) of
583 #if __GLASGOW_HASKELL__ < 400
584           Lift v -> v
585 #elif __GLASGOW_HASKELL__ < 403
586           (# _, v #) -> v
587 #else
588           (# v #) -> v
589 #endif
590     }
591   where
592     mk_assoc_elem k@(MaxSimplifierIterations lvl)
593         = (iBox (tagOf_SimplSwitch k), SwInt lvl)
594     mk_assoc_elem k@(SimplInlinePhase n)
595         = (iBox (tagOf_SimplSwitch k), SwInt n)
596     mk_assoc_elem k
597         = (iBox (tagOf_SimplSwitch k), SwBool True) -- I'm here, Mom!
598
599     -- cannot have duplicates if we are going to use the array thing
600     rm_dups switches_so_far switch
601       = if switch `is_elem` switches_so_far
602         then switches_so_far
603         else switch : switches_so_far
604       where
605         sw `is_elem` []     = False
606         sw `is_elem` (s:ss) = (tagOf_SimplSwitch sw) ==# (tagOf_SimplSwitch s)
607                             || sw `is_elem` ss
608 \end{code}
609
610 Default settings for simplifier switches
611
612 \begin{code}
613 defaultSimplSwitches = [MaxSimplifierIterations 1]
614 \end{code}
615
616 %************************************************************************
617 %*                                                                      *
618 \subsection{Misc functions for command-line options}
619 %*                                                                      *
620 %************************************************************************
621
622
623 \begin{code}
624 switchIsOn :: (switch -> SwitchResult) -> switch -> Bool
625
626 switchIsOn lookup_fn switch
627   = case (lookup_fn switch) of
628       SwBool False -> False
629       _            -> True
630
631 intSwitchSet :: (switch -> SwitchResult)
632              -> (Int -> switch)
633              -> Maybe Int
634
635 intSwitchSet lookup_fn switch
636   = case (lookup_fn (switch (panic "intSwitchSet"))) of
637       SwInt int -> Just int
638       _         -> Nothing
639 \end{code}
640
641 \begin{code}
642 startsWith :: String -> String -> Maybe String
643 -- startsWith pfx (pfx++rest) = Just rest
644
645 startsWith []     str = Just str
646 startsWith (c:cs) (s:ss)
647   = if c /= s then Nothing else startsWith cs ss
648 startsWith  _     []  = Nothing
649
650 endsWith  :: String -> String -> Maybe String
651 endsWith cs ss
652   = case (startsWith (reverse cs) (reverse ss)) of
653       Nothing -> Nothing
654       Just rs -> Just (reverse rs)
655 \end{code}