e7bc5fc9dc8a631e20f9b19b858fdad953653522
[ghc-hetmet.git] / ghc / compiler / main / DriverState.hs
1 -----------------------------------------------------------------------------
2 -- $Id: DriverState.hs,v 1.47 2001/06/28 10:19:48 sewardj Exp $
3 --
4 -- Settings for the driver
5 --
6 -- (c) The University of Glasgow 2000
7 --
8 -----------------------------------------------------------------------------
9
10 module DriverState where
11
12 #include "../includes/config.h"
13 #include "HsVersions.h"
14
15 import Packages         ( PackageConfig(..) )
16 import CmdLineOpts
17 import DriverPhases
18 import DriverUtil
19 import Util
20 import Config
21 import Exception
22 import IOExts
23 import Panic
24
25 import List
26 import Char  
27 import Monad
28
29 -----------------------------------------------------------------------------
30 -- non-configured things
31
32 cHaskell1Version = "5" -- i.e., Haskell 98
33
34 -----------------------------------------------------------------------------
35 -- GHC modes of operation
36
37 data GhcMode
38   = DoMkDependHS                        -- ghc -M
39   | DoMkDLL                             -- ghc --mk-dll
40   | StopBefore Phase                    -- ghc -E | -C | -S | -c
41   | DoMake                              -- ghc --make
42   | DoInteractive                       -- ghc --interactive
43   | DoLink                              -- [ the default ]
44   deriving (Eq)
45
46 GLOBAL_VAR(v_GhcMode, error "mode not set", GhcMode)
47
48 -----------------------------------------------------------------------------
49 -- Global compilation flags
50
51 -- Cpp-related flags
52 v_Hs_source_cpp_opts = global
53         [ "-D__HASKELL1__="++cHaskell1Version
54         , "-D__GLASGOW_HASKELL__="++cProjectVersionInt                          
55         , "-D__HASKELL98__"
56         , "-D__CONCURRENT_HASKELL__"
57         ]
58 {-# NOINLINE v_Hs_source_cpp_opts #-}
59
60 -- Keep output from intermediate phases
61 GLOBAL_VAR(v_Keep_hi_diffs,             False,          Bool)
62 GLOBAL_VAR(v_Keep_hc_files,             False,          Bool)
63 GLOBAL_VAR(v_Keep_s_files,              False,          Bool)
64 GLOBAL_VAR(v_Keep_raw_s_files,          False,          Bool)
65 GLOBAL_VAR(v_Keep_tmp_files,            False,          Bool)
66
67 -- Misc
68 GLOBAL_VAR(v_Scale_sizes_by,            1.0,            Double)
69 GLOBAL_VAR(v_Static,                    True,           Bool)
70 GLOBAL_VAR(v_NoHsMain,                  False,          Bool)
71 GLOBAL_VAR(v_Recomp,                    True,           Bool)
72 GLOBAL_VAR(v_Collect_ghc_timing,        False,          Bool)
73 GLOBAL_VAR(v_Do_asm_mangling,           True,           Bool)
74 GLOBAL_VAR(v_Excess_precision,          False,          Bool)
75
76 -----------------------------------------------------------------------------
77 -- Splitting object files (for libraries)
78
79 GLOBAL_VAR(v_Split_object_files,        False,          Bool)
80 GLOBAL_VAR(v_Split_info,                ("",0),         (String,Int))
81         -- The split prefix and number of files
82
83         
84 can_split :: Bool
85 can_split =  prefixMatch "i386"    cTARGETPLATFORM
86           || prefixMatch "alpha"   cTARGETPLATFORM
87           || prefixMatch "hppa"    cTARGETPLATFORM
88           || prefixMatch "m68k"    cTARGETPLATFORM
89           || prefixMatch "mips"    cTARGETPLATFORM
90           || prefixMatch "powerpc" cTARGETPLATFORM
91           || prefixMatch "rs6000"  cTARGETPLATFORM
92           || prefixMatch "sparc"   cTARGETPLATFORM
93
94 -----------------------------------------------------------------------------
95 -- Compiler output options
96
97 defaultHscLang
98   | cGhcWithNativeCodeGen == "YES" && 
99         (prefixMatch "i386" cTARGETPLATFORM ||
100          prefixMatch "sparc" cTARGETPLATFORM)   =  HscAsm
101   | otherwise                                   =  HscC
102
103 GLOBAL_VAR(v_Output_dir,  Nothing, Maybe String)
104 GLOBAL_VAR(v_Output_file, Nothing, Maybe String)
105 GLOBAL_VAR(v_Output_hi,   Nothing, Maybe String)
106
107 GLOBAL_VAR(v_Object_suf,  Nothing, Maybe String)
108 GLOBAL_VAR(v_HC_suf,      Nothing, Maybe String)
109 GLOBAL_VAR(v_Hi_dir,      Nothing, Maybe String)
110 GLOBAL_VAR(v_Hi_suf,      "hi",    String)
111
112 GLOBAL_VAR(v_Ld_inputs, [],      [String])
113
114 odir_ify :: String -> IO String
115 odir_ify f = do
116   odir_opt <- readIORef v_Output_dir
117   case odir_opt of
118         Nothing -> return f
119         Just d  -> return (newdir d f)
120
121 osuf_ify :: String -> IO String
122 osuf_ify f = do
123   osuf_opt <- readIORef v_Object_suf
124   case osuf_opt of
125         Nothing -> return f
126         Just s  -> return (newsuf s f)
127
128 -----------------------------------------------------------------------------
129 -- Compiler optimisation options
130
131 GLOBAL_VAR(v_OptLevel, 0, Int)
132
133 setOptLevel :: String -> IO ()
134 setOptLevel ""              = do { writeIORef v_OptLevel 1 }
135 setOptLevel "not"           = writeIORef v_OptLevel 0
136 setOptLevel [c] | isDigit c = do
137    let level = ord c - ord '0'
138    writeIORef v_OptLevel level
139 setOptLevel s = unknownFlagErr ("-O"++s)
140
141 GLOBAL_VAR(v_minus_o2_for_C,            False, Bool)
142 GLOBAL_VAR(v_MaxSimplifierIterations,   4,     Int)
143 GLOBAL_VAR(v_StgStats,                  False, Bool)
144 GLOBAL_VAR(v_UsageSPInf,                False, Bool)  -- Off by default
145 GLOBAL_VAR(v_Strictness,                True,  Bool)
146 GLOBAL_VAR(v_CPR,                       True,  Bool)
147 GLOBAL_VAR(v_CSE,                       True,  Bool)
148
149 -- these are the static flags you get without -O.
150 hsc_minusNoO_flags =
151        [ 
152         "-fignore-interface-pragmas",
153         "-fomit-interface-pragmas",
154         "-fdo-lambda-eta-expansion",    -- This one is important for a tiresome reason:
155                                         -- we want to make sure that the bindings for data 
156                                         -- constructors are eta-expanded.  This is probably
157                                         -- a good thing anyway, but it seems fragile.
158         "-flet-no-escape"
159         ]
160
161 -- these are the static flags you get when -O is on.
162 hsc_minusO_flags =
163   [ 
164         "-fignore-asserts",
165         "-ffoldr-build-on",
166         "-fdo-eta-reduction",
167         "-fdo-lambda-eta-expansion",
168         "-fcase-merge",
169         "-flet-to-case",
170         "-flet-no-escape"
171    ]
172
173 hsc_minusO2_flags = hsc_minusO_flags    -- for now
174
175 getStaticOptimisationFlags 0 = hsc_minusNoO_flags
176 getStaticOptimisationFlags 1 = hsc_minusO_flags
177 getStaticOptimisationFlags n = hsc_minusO2_flags
178
179 buildCoreToDo :: IO [CoreToDo]
180 buildCoreToDo = do
181    opt_level  <- readIORef v_OptLevel
182    max_iter   <- readIORef v_MaxSimplifierIterations
183    usageSP    <- readIORef v_UsageSPInf
184    strictness <- readIORef v_Strictness
185    cpr        <- readIORef v_CPR
186    cse        <- readIORef v_CSE
187
188    if opt_level == 0 then return
189       [
190         CoreDoSimplify (isAmongSimpl [
191             MaxSimplifierIterations max_iter
192         ])
193       ]
194
195     else {- opt_level >= 1 -} return [ 
196
197         -- initial simplify: mk specialiser happy: minimum effort please
198         CoreDoSimplify (isAmongSimpl [
199             SimplInlinePhase 0,
200                         -- Don't inline anything till full laziness has bitten
201                         -- In particular, inlining wrappers inhibits floating
202                         -- e.g. ...(case f x of ...)...
203                         --  ==> ...(case (case x of I# x# -> fw x#) of ...)...
204                         --  ==> ...(case x of I# x# -> case fw x# of ...)...
205                         -- and now the redex (f x) isn't floatable any more
206             DontApplyRules,
207                         -- Similarly, don't apply any rules until after full 
208                         -- laziness.  Notably, list fusion can prevent floating.
209             NoCaseOfCase,
210                         -- Don't do case-of-case transformations.
211                         -- This makes full laziness work better
212             MaxSimplifierIterations max_iter
213         ]),
214
215         -- Specialisation is best done before full laziness
216         -- so that overloaded functions have all their dictionary lambdas manifest
217         CoreDoSpecialising,
218
219         CoreDoFloatOutwards False{-not full-},
220         CoreDoFloatInwards,
221
222         CoreDoSimplify (isAmongSimpl [
223            SimplInlinePhase 1,
224                 -- Want to run with inline phase 1 after the specialiser to give
225                 -- maximum chance for fusion to work before we inline build/augment
226                 -- in phase 2.  This made a difference in 'ansi' where an 
227                 -- overloaded function wasn't inlined till too late.
228            MaxSimplifierIterations max_iter
229         ]),
230
231         -- infer usage information here in case we need it later.
232         -- (add more of these where you need them --KSW 1999-04)
233         if usageSP then CoreDoUSPInf else CoreDoNothing,
234
235         CoreDoSimplify (isAmongSimpl [
236                 -- Need inline-phase2 here so that build/augment get 
237                 -- inlined.  I found that spectral/hartel/genfft lost some useful
238                 -- strictness in the function sumcode' if augment is not inlined
239                 -- before strictness analysis runs
240            SimplInlinePhase 2,
241            MaxSimplifierIterations max_iter
242         ]),
243
244         CoreDoSimplify (isAmongSimpl [
245            MaxSimplifierIterations 2
246                 -- No -finline-phase: allow all Ids to be inlined now
247                 -- This gets foldr inlined before strictness analysis
248         ]),
249
250         if strictness then CoreDoStrictness else CoreDoNothing,
251         if cpr        then CoreDoCPResult   else CoreDoNothing,
252         CoreDoWorkerWrapper,
253         CoreDoGlomBinds,
254
255         CoreDoSimplify (isAmongSimpl [
256            MaxSimplifierIterations max_iter
257                 -- No -finline-phase: allow all Ids to be inlined now
258         ]),
259
260         CoreDoFloatOutwards False{-not full-},
261                 -- nofib/spectral/hartel/wang doubles in speed if you
262                 -- do full laziness late in the day.  It only happens
263                 -- after fusion and other stuff, so the early pass doesn't
264                 -- catch it.  For the record, the redex is 
265                 --        f_el22 (f_el21 r_midblock)
266
267
268 -- Leave out lambda lifting for now
269 --        "-fsimplify", -- Tidy up results of full laziness
270 --          "[", 
271 --                "-fmax-simplifier-iterations2",
272 --          "]",
273 --        "-ffloat-outwards-full",      
274
275         -- We want CSE to follow the final full-laziness pass, because it may
276         -- succeed in commoning up things floated out by full laziness.
277         -- CSE used to rely on the no-shadowing invariant, but it doesn't any more
278
279         if cse then CoreCSE else CoreDoNothing,
280
281         CoreDoFloatInwards,
282
283 -- Case-liberation for -O2.  This should be after
284 -- strictness analysis and the simplification which follows it.
285
286         if opt_level >= 2 then
287            CoreLiberateCase
288         else
289            CoreDoNothing,
290         if opt_level >= 2 then
291            CoreDoSpecConstr
292         else
293            CoreDoNothing,
294
295         -- Final clean-up simplification:
296         CoreDoSimplify (isAmongSimpl [
297           MaxSimplifierIterations max_iter
298                 -- No -finline-phase: allow all Ids to be inlined now
299         ])
300      ]
301
302 buildStgToDo :: IO [ StgToDo ]
303 buildStgToDo = do
304   stg_stats <- readIORef v_StgStats
305   let flags1 | stg_stats = [ D_stg_stats ]
306              | otherwise = [ ]
307
308         -- STG passes
309   ways_ <- readIORef v_Ways
310   let flags2 | WayProf `elem` ways_ = StgDoMassageForProfiling : flags1
311              | otherwise            = flags1
312
313   return flags2
314
315 -----------------------------------------------------------------------------
316 -- Paths & Libraries
317
318 split_marker = ':'   -- not configurable (ToDo)
319
320 v_Import_paths, v_Include_paths, v_Library_paths :: IORef [String]
321 GLOBAL_VAR(v_Import_paths,  ["."], [String])
322 GLOBAL_VAR(v_Include_paths, ["."], [String])
323 GLOBAL_VAR(v_Library_paths, [],  [String])
324
325 GLOBAL_VAR(v_Cmdline_libraries,   [], [String])
326
327 addToDirList :: IORef [String] -> String -> IO ()
328 addToDirList ref path
329   = do paths <- readIORef ref
330        writeIORef ref (paths ++ split split_marker path)
331
332 GLOBAL_VAR(v_HCHeader, "", String)
333
334 -----------------------------------------------------------------------------
335 -- Packages
336
337 -- package list is maintained in dependency order
338 GLOBAL_VAR(v_Packages, ("std":"rts":"gmp":[]), [String])
339
340 addPackage :: String -> IO ()
341 addPackage package
342   = do pkg_details <- readIORef v_Package_details
343        case lookupPkg package pkg_details of
344           Nothing -> throwDyn (CmdLineError ("unknown package name: " ++ package))
345           Just details -> do
346             ps <- readIORef v_Packages
347             unless (package `elem` ps) $ do
348                 mapM_ addPackage (package_deps details)
349                 ps <- readIORef v_Packages
350                 writeIORef v_Packages (package:ps)
351
352 getPackageImportPath   :: IO [String]
353 getPackageImportPath = do
354   ps <- getPackageInfo
355   return (nub (filter (not.null) (concatMap import_dirs ps)))
356
357 getPackageIncludePath   :: IO [String]
358 getPackageIncludePath = do
359   ps <- getPackageInfo
360   return (nub (filter (not.null) (concatMap include_dirs ps)))
361
362         -- includes are in reverse dependency order (i.e. rts first)
363 getPackageCIncludes   :: IO [String]
364 getPackageCIncludes = do
365   ps <- getPackageInfo
366   return (reverse (nub (filter (not.null) (concatMap c_includes ps))))
367
368 getPackageLibraryPath  :: IO [String]
369 getPackageLibraryPath = do
370   ps <- getPackageInfo
371   return (nub (filter (not.null) (concatMap library_dirs ps)))
372
373 getPackageLibraries    :: IO [String]
374 getPackageLibraries = do
375   ps <- getPackageInfo
376   tag <- readIORef v_Build_tag
377   let suffix = if null tag then "" else '_':tag
378   return (concat (
379         map (\p -> map (++suffix) (hACK (hs_libraries p)) ++ extra_libraries p) ps
380      ))
381   where
382      -- This is a totally horrible (temporary) hack, for Win32.  Problem is
383      -- that package.conf for Win32 says that the main prelude lib is 
384      -- split into HSstd1 and HSstd2, which is needed due to limitations in
385      -- the PEi386 file format, to make GHCi work.  However, we still only
386      -- have HSstd.a for static linking, not HSstd1.a and HSstd2.a.  
387      -- getPackageLibraries is called to find the .a's to add to the static
388      -- link line.  On Win32, this hACK detects HSstd1 and HSstd2 and 
389      -- replaces them with HSstd, so static linking still works.
390      -- Libraries needed for dynamic (GHCi) linking are discovered via
391      -- different route (in InteractiveUI.linkPackage).
392      -- See driver/PackageSrc.hs for the HSstd1/HSstd2 split definition.
393      -- THIS IS A STRICTLY TEMPORARY HACK (famous last words ...)
394      hACK libs
395 #      ifndef mingw32_TARGET_OS
396        = libs
397 #      else
398        = if   "HSstd1" `elem` libs && "HSstd2" `elem` libs
399          then "HSstd" : filter ((/= "HSstd").(take 5)) libs
400          else libs
401 #      endif
402
403 getPackageExtraGhcOpts :: IO [String]
404 getPackageExtraGhcOpts = do
405   ps <- getPackageInfo
406   return (concatMap extra_ghc_opts ps)
407
408 getPackageExtraCcOpts  :: IO [String]
409 getPackageExtraCcOpts = do
410   ps <- getPackageInfo
411   return (concatMap extra_cc_opts ps)
412
413 getPackageExtraLdOpts  :: IO [String]
414 getPackageExtraLdOpts = do
415   ps <- getPackageInfo
416   return (concatMap extra_ld_opts ps)
417
418 getPackageInfo :: IO [PackageConfig]
419 getPackageInfo = do
420   ps <- readIORef v_Packages
421   getPackageDetails ps
422
423 getPackageDetails :: [String] -> IO [PackageConfig]
424 getPackageDetails ps = do
425   pkg_details <- readIORef v_Package_details
426   return [ pkg | p <- ps, Just pkg <- [ lookupPkg p pkg_details ] ]
427
428 GLOBAL_VAR(v_Package_details, (error "package_details"), [PackageConfig])
429
430 lookupPkg :: String -> [PackageConfig] -> Maybe PackageConfig
431 lookupPkg nm ps
432    = case [p | p <- ps, name p == nm] of
433         []    -> Nothing
434         (p:_) -> Just p
435
436 -----------------------------------------------------------------------------
437 -- Ways
438
439 -- The central concept of a "way" is that all objects in a given
440 -- program must be compiled in the same "way".  Certain options change
441 -- parameters of the virtual machine, eg. profiling adds an extra word
442 -- to the object header, so profiling objects cannot be linked with
443 -- non-profiling objects.
444
445 -- After parsing the command-line options, we determine which "way" we
446 -- are building - this might be a combination way, eg. profiling+ticky-ticky.
447
448 -- We then find the "build-tag" associated with this way, and this
449 -- becomes the suffix used to find .hi files and libraries used in
450 -- this compilation.
451
452 GLOBAL_VAR(v_Build_tag, "", String)
453
454 data WayName
455   = WayProf
456   | WayUnreg
457   | WayTicky
458   | WayPar
459   | WayGran
460   | WaySMP
461   | WayDebug
462   | WayUser_a
463   | WayUser_b
464   | WayUser_c
465   | WayUser_d
466   | WayUser_e
467   | WayUser_f
468   | WayUser_g
469   | WayUser_h
470   | WayUser_i
471   | WayUser_j
472   | WayUser_k
473   | WayUser_l
474   | WayUser_m
475   | WayUser_n
476   | WayUser_o
477   | WayUser_A
478   | WayUser_B
479   deriving (Eq,Ord)
480
481 GLOBAL_VAR(v_Ways, [] ,[WayName])
482
483 allowed_combination way = way `elem` combs
484   where  -- the sub-lists must be ordered according to WayName, 
485          -- because findBuildTag sorts them
486     combs                = [ [WayProf,WayUnreg], [WayProf,WaySMP] ]
487
488 findBuildTag :: IO [String]  -- new options
489 findBuildTag = do
490   way_names <- readIORef v_Ways
491   case sort way_names of
492      []  -> do  -- writeIORef v_Build_tag ""
493                 return []
494
495      [w] -> do let details = lkupWay w
496                writeIORef v_Build_tag (wayTag details)
497                return (wayOpts details)
498
499      ws  -> if not (allowed_combination ws)
500                 then throwDyn (CmdLineError $
501                                 "combination not supported: "  ++
502                                 foldr1 (\a b -> a ++ '/':b) 
503                                 (map (wayName . lkupWay) ws))
504                 else let stuff = map lkupWay ws
505                          tag   = concat (map wayTag stuff)
506                          flags = map wayOpts stuff
507                      in do
508                      writeIORef v_Build_tag tag
509                      return (concat flags)
510
511 lkupWay w = 
512    case lookup w way_details of
513         Nothing -> error "findBuildTag"
514         Just details -> details
515
516 data Way = Way {
517   wayTag   :: String,
518   wayName  :: String,
519   wayOpts  :: [String]
520   }
521
522 way_details :: [ (WayName, Way) ]
523 way_details =
524   [ (WayProf, Way  "p" "Profiling"  
525         [ "-fscc-profiling"
526         , "-DPROFILING"
527         , "-optc-DPROFILING"
528         , "-fvia-C" ]),
529
530     (WayTicky, Way  "t" "Ticky-ticky Profiling"  
531         [ "-fticky-ticky"
532         , "-DTICKY_TICKY"
533         , "-optc-DTICKY_TICKY"
534         , "-fvia-C" ]),
535
536     (WayUnreg, Way  "u" "Unregisterised" 
537         unregFlags ),
538
539     -- optl's below to tell linker where to find the PVM library -- HWL
540     (WayPar, Way  "mp" "Parallel" 
541         [ "-fparallel"
542         , "-D__PARALLEL_HASKELL__"
543         , "-optc-DPAR"
544         , "-package concurrent"
545         , "-optc-w"
546         , "-optl-L${PVM_ROOT}/lib/${PVM_ARCH}"
547         , "-optl-lpvm3"
548         , "-optl-lgpvm3"
549         , "-fvia-C" ]),
550
551     -- at the moment we only change the RTS and could share compiler and libs!
552     (WayPar, Way  "mt" "Parallel ticky profiling" 
553         [ "-fparallel"
554         , "-D__PARALLEL_HASKELL__"
555         , "-optc-DPAR"
556         , "-optc-DPAR_TICKY"
557         , "-package concurrent"
558         , "-optc-w"
559         , "-optl-L${PVM_ROOT}/lib/${PVM_ARCH}"
560         , "-optl-lpvm3"
561         , "-optl-lgpvm3"
562         , "-fvia-C" ]),
563
564     (WayPar, Way  "md" "Distributed" 
565         [ "-fparallel"
566         , "-D__PARALLEL_HASKELL__"
567         , "-D__DISTRIBUTED_HASKELL__"
568         , "-optc-DPAR"
569         , "-optc-DDIST"
570         , "-package concurrent"
571         , "-optc-w"
572         , "-optl-L${PVM_ROOT}/lib/${PVM_ARCH}"
573         , "-optl-lpvm3"
574         , "-optl-lgpvm3"
575         , "-fvia-C" ]),
576
577     (WayGran, Way  "mg" "GranSim" 
578         [ "-fgransim"
579         , "-D__GRANSIM__"
580         , "-optc-DGRAN"
581         , "-package concurrent"
582         , "-fvia-C" ]),
583
584     (WaySMP, Way  "s" "SMP"
585         [ "-fsmp"
586         , "-optc-pthread"
587         , "-optl-pthread"
588         , "-optc-DSMP"
589         , "-fvia-C" ]),
590
591     (WayUser_a,  Way  "a"  "User way 'a'"  ["$WAY_a_REAL_OPTS"]),       
592     (WayUser_b,  Way  "b"  "User way 'b'"  ["$WAY_b_REAL_OPTS"]),       
593     (WayUser_c,  Way  "c"  "User way 'c'"  ["$WAY_c_REAL_OPTS"]),       
594     (WayUser_d,  Way  "d"  "User way 'd'"  ["$WAY_d_REAL_OPTS"]),       
595     (WayUser_e,  Way  "e"  "User way 'e'"  ["$WAY_e_REAL_OPTS"]),       
596     (WayUser_f,  Way  "f"  "User way 'f'"  ["$WAY_f_REAL_OPTS"]),       
597     (WayUser_g,  Way  "g"  "User way 'g'"  ["$WAY_g_REAL_OPTS"]),       
598     (WayUser_h,  Way  "h"  "User way 'h'"  ["$WAY_h_REAL_OPTS"]),       
599     (WayUser_i,  Way  "i"  "User way 'i'"  ["$WAY_i_REAL_OPTS"]),       
600     (WayUser_j,  Way  "j"  "User way 'j'"  ["$WAY_j_REAL_OPTS"]),       
601     (WayUser_k,  Way  "k"  "User way 'k'"  ["$WAY_k_REAL_OPTS"]),       
602     (WayUser_l,  Way  "l"  "User way 'l'"  ["$WAY_l_REAL_OPTS"]),       
603     (WayUser_m,  Way  "m"  "User way 'm'"  ["$WAY_m_REAL_OPTS"]),       
604     (WayUser_n,  Way  "n"  "User way 'n'"  ["$WAY_n_REAL_OPTS"]),       
605     (WayUser_o,  Way  "o"  "User way 'o'"  ["$WAY_o_REAL_OPTS"]),       
606     (WayUser_A,  Way  "A"  "User way 'A'"  ["$WAY_A_REAL_OPTS"]),       
607     (WayUser_B,  Way  "B"  "User way 'B'"  ["$WAY_B_REAL_OPTS"]) 
608   ]
609
610 unregFlags = 
611    [ "-optc-DNO_REGS"
612    , "-optc-DUSE_MINIINTERPRETER"
613    , "-fno-asm-mangling"
614    , "-funregisterised"
615    , "-fvia-C" ]
616
617 -----------------------------------------------------------------------------
618 -- Programs for particular phases
619
620 GLOBAL_VAR(v_Opt_dep,    [], [String])
621 GLOBAL_VAR(v_Anti_opt_C, [], [String])
622 GLOBAL_VAR(v_Opt_C,      [], [String])
623 GLOBAL_VAR(v_Opt_l,      [], [String])
624 GLOBAL_VAR(v_Opt_dll,    [], [String])
625
626 getStaticOpts :: IORef [String] -> IO [String]
627 getStaticOpts ref = readIORef ref >>= return . reverse