Separate the static flag parser from the static global variables
[ghc-hetmet.git] / compiler / main / StaticFlags.hs
1 {-# OPTIONS -fno-cse #-}
2 -- -fno-cse is needed for GLOBAL_VAR's to behave properly
3
4 -----------------------------------------------------------------------------
5 --
6 -- Static flags
7 --
8 -- Static flags can only be set once, on the command-line.  Inside GHC,
9 -- each static flag corresponds to a top-level value, usually of type Bool.
10 --
11 -- (c) The University of Glasgow 2005
12 --
13 -----------------------------------------------------------------------------
14
15 module StaticFlags (
16         staticFlags,
17         initStaticOpts,
18
19         -- Ways
20         WayName(..), v_Ways, v_Build_tag, v_RTS_Build_tag, isRTSWay,
21
22         -- Output style options
23         opt_PprUserLength,
24         opt_SuppressUniques,
25         opt_PprStyle_Debug,
26         opt_NoDebugOutput,
27
28         -- profiling opts
29         opt_AutoSccsOnAllToplevs,
30         opt_AutoSccsOnExportedToplevs,
31         opt_AutoSccsOnIndividualCafs,
32         opt_SccProfilingOn,
33         opt_DoTickyProfiling,
34
35         -- Hpc opts
36         opt_Hpc,
37
38         -- language opts
39         opt_DictsStrict,
40         opt_IrrefutableTuples,
41         opt_Parallel,
42
43         -- optimisation opts
44         opt_DsMultiTyVar,
45         opt_NoStateHack,
46         opt_SpecInlineJoinPoints,
47         opt_CprOff,
48         opt_SimplNoPreInlining,
49         opt_SimplExcessPrecision,
50         opt_MaxWorkerArgs,
51
52         -- Unfolding control
53         opt_UF_CreationThreshold,
54         opt_UF_UseThreshold,
55         opt_UF_FunAppDiscount,
56         opt_UF_KeenessFactor,
57         opt_UF_DearOp,
58
59         -- Optimization fuel controls
60         opt_Fuel,
61
62         -- Related to linking
63         opt_PIC,
64         opt_Static,
65
66         -- misc opts
67         opt_IgnoreDotGhci,
68         opt_ErrorSpans,
69         opt_GranMacros,
70         opt_HiVersion,
71         opt_HistorySize,
72         opt_OmitBlackHoling,
73         opt_Unregisterised,
74         opt_EmitExternalCore,
75         v_Ld_inputs,
76         tablesNextToCode,
77
78     -- For the parser
79     addOpt, removeOpt, addWay, findBuildTag, v_opt_C_ready
80   ) where
81
82 #include "HsVersions.h"
83
84 import Config
85 import FastString
86 import Util
87 import Maybes           ( firstJust )
88 import Panic
89
90 import Data.IORef
91 import System.IO.Unsafe ( unsafePerformIO )
92 import Data.List
93
94 -----------------------------------------------------------------------------
95 -- Static flags
96
97 initStaticOpts :: IO ()
98 initStaticOpts = writeIORef v_opt_C_ready True
99
100 addOpt :: String -> IO ()
101 addOpt = consIORef v_opt_C
102
103 addWay :: WayName -> IO ()
104 addWay = consIORef v_Ways
105
106 removeOpt :: String -> IO ()
107 removeOpt f = do
108   fs <- readIORef v_opt_C
109   writeIORef v_opt_C $! filter (/= f) fs    
110
111 lookUp           :: FastString -> Bool
112 lookup_def_int   :: String -> Int -> Int
113 lookup_def_float :: String -> Float -> Float
114 lookup_str       :: String -> Maybe String
115
116 -- holds the static opts while they're being collected, before
117 -- being unsafely read by unpacked_static_opts below.
118 GLOBAL_VAR(v_opt_C, defaultStaticOpts, [String])
119 GLOBAL_VAR(v_opt_C_ready, False, Bool)
120
121 staticFlags :: [String]
122 staticFlags = unsafePerformIO $ do
123   ready <- readIORef v_opt_C_ready
124   if (not ready)
125         then panic "Static flags have not been initialised!\n        Please call GHC.newSession or GHC.parseStaticFlags early enough."
126         else readIORef v_opt_C
127
128 -- -static is the default
129 defaultStaticOpts :: [String]
130 defaultStaticOpts = ["-static"]
131
132 packed_static_opts :: [FastString]
133 packed_static_opts   = map mkFastString staticFlags
134
135 lookUp     sw = sw `elem` packed_static_opts
136         
137 -- (lookup_str "foo") looks for the flag -foo=X or -fooX, 
138 -- and returns the string X
139 lookup_str sw 
140    = case firstJust (map (maybePrefixMatch sw) staticFlags) of
141         Just ('=' : str) -> Just str
142         Just str         -> Just str
143         Nothing          -> Nothing     
144
145 lookup_def_int sw def = case (lookup_str sw) of
146                             Nothing -> def              -- Use default
147                             Just xx -> try_read sw xx
148
149 lookup_def_float sw def = case (lookup_str sw) of
150                             Nothing -> def              -- Use default
151                             Just xx -> try_read sw xx
152
153
154 try_read :: Read a => String -> String -> a
155 -- (try_read sw str) tries to read s; if it fails, it
156 -- bleats about flag sw
157 try_read sw str
158   = case reads str of
159         ((x,_):_) -> x  -- Be forgiving: ignore trailing goop, and alternative parses
160         []        -> ghcError (UsageError ("Malformed argument " ++ str ++ " for flag " ++ sw))
161                         -- ToDo: hack alert. We should really parse the arugments
162                         --       and announce errors in a more civilised way.
163
164
165 {-
166  Putting the compiler options into temporary at-files
167  may turn out to be necessary later on if we turn hsc into
168  a pure Win32 application where I think there's a command-line
169  length limit of 255. unpacked_opts understands the @ option.
170
171 unpacked_opts :: [String]
172 unpacked_opts =
173   concat $
174   map (expandAts) $
175   map unpackFS argv  -- NOT ARGV any more: v_Static_hsc_opts
176   where
177    expandAts ('@':fname) = words (unsafePerformIO (readFile fname))
178    expandAts l = [l]
179 -}
180
181 opt_IgnoreDotGhci :: Bool
182 opt_IgnoreDotGhci               = lookUp (fsLit "-ignore-dot-ghci")
183
184 -- debugging opts
185 opt_SuppressUniques :: Bool
186 opt_SuppressUniques             = lookUp  (fsLit "-dsuppress-uniques")
187 opt_PprStyle_Debug  :: Bool
188 opt_PprStyle_Debug              = lookUp  (fsLit "-dppr-debug")
189 opt_PprUserLength   :: Int
190 opt_PprUserLength               = lookup_def_int "-dppr-user-length" 5 --ToDo: give this a name
191 opt_Fuel            :: Int
192 opt_Fuel                        = lookup_def_int "-dopt-fuel" maxBound
193 opt_NoDebugOutput   :: Bool
194 opt_NoDebugOutput               = lookUp  (fsLit "-dno-debug-output")
195
196
197 -- profiling opts
198 opt_AutoSccsOnAllToplevs :: Bool
199 opt_AutoSccsOnAllToplevs        = lookUp  (fsLit "-fauto-sccs-on-all-toplevs")
200 opt_AutoSccsOnExportedToplevs :: Bool
201 opt_AutoSccsOnExportedToplevs   = lookUp  (fsLit "-fauto-sccs-on-exported-toplevs")
202 opt_AutoSccsOnIndividualCafs :: Bool
203 opt_AutoSccsOnIndividualCafs    = lookUp  (fsLit "-fauto-sccs-on-individual-cafs")
204 opt_SccProfilingOn :: Bool
205 opt_SccProfilingOn              = lookUp  (fsLit "-fscc-profiling")
206 opt_DoTickyProfiling :: Bool
207 opt_DoTickyProfiling            = WayTicky `elem` (unsafePerformIO $ readIORef v_Ways)
208
209 -- Hpc opts
210 opt_Hpc :: Bool
211 opt_Hpc                         = lookUp (fsLit "-fhpc")  
212
213 -- language opts
214 opt_DictsStrict :: Bool
215 opt_DictsStrict                 = lookUp  (fsLit "-fdicts-strict")
216 opt_IrrefutableTuples :: Bool
217 opt_IrrefutableTuples           = lookUp  (fsLit "-firrefutable-tuples")
218 opt_Parallel :: Bool
219 opt_Parallel                    = lookUp  (fsLit "-fparallel")
220
221 -- optimisation opts
222 opt_DsMultiTyVar :: Bool
223 opt_DsMultiTyVar                = not (lookUp (fsLit "-fno-ds-multi-tyvar"))
224         -- On by default
225
226 opt_SpecInlineJoinPoints :: Bool
227 opt_SpecInlineJoinPoints        = lookUp  (fsLit "-fspec-inline-join-points")
228
229 opt_NoStateHack :: Bool
230 opt_NoStateHack                 = lookUp  (fsLit "-fno-state-hack")
231 opt_CprOff :: Bool
232 opt_CprOff                      = lookUp  (fsLit "-fcpr-off")
233         -- Switch off CPR analysis in the new demand analyser
234 opt_MaxWorkerArgs :: Int
235 opt_MaxWorkerArgs               = lookup_def_int "-fmax-worker-args" (10::Int)
236
237 opt_GranMacros :: Bool
238 opt_GranMacros                  = lookUp  (fsLit "-fgransim")
239 opt_HiVersion :: Integer
240 opt_HiVersion                   = read (cProjectVersionInt ++ cProjectPatchLevel) :: Integer
241 opt_HistorySize :: Int
242 opt_HistorySize                 = lookup_def_int "-fhistory-size" 20
243 opt_OmitBlackHoling :: Bool
244 opt_OmitBlackHoling             = lookUp  (fsLit "-dno-black-holing")
245
246 -- Simplifier switches
247 opt_SimplNoPreInlining :: Bool
248 opt_SimplNoPreInlining          = lookUp  (fsLit "-fno-pre-inlining")
249         -- NoPreInlining is there just to see how bad things
250         -- get if you don't do it!
251 opt_SimplExcessPrecision :: Bool
252 opt_SimplExcessPrecision        = lookUp  (fsLit "-fexcess-precision")
253
254 -- Unfolding control
255 opt_UF_CreationThreshold :: Int
256 opt_UF_CreationThreshold        = lookup_def_int "-funfolding-creation-threshold"  (45::Int)
257 opt_UF_UseThreshold :: Int
258 opt_UF_UseThreshold             = lookup_def_int "-funfolding-use-threshold"       (8::Int)     -- Discounts can be big
259 opt_UF_FunAppDiscount :: Int
260 opt_UF_FunAppDiscount           = lookup_def_int "-funfolding-fun-discount"        (6::Int)     -- It's great to inline a fn
261 opt_UF_KeenessFactor :: Float
262 opt_UF_KeenessFactor            = lookup_def_float "-funfolding-keeness-factor"    (1.5::Float)
263
264 opt_UF_DearOp :: Int
265 opt_UF_DearOp   = ( 4 :: Int)
266
267
268 -- Related to linking
269 opt_PIC :: Bool
270 #if darwin_TARGET_OS && x86_64_TARGET_ARCH
271 opt_PIC                         = True
272 #else
273 opt_PIC                         = lookUp (fsLit "-fPIC")
274 #endif
275 opt_Static :: Bool
276 opt_Static                      = lookUp  (fsLit "-static")
277 opt_Unregisterised :: Bool
278 opt_Unregisterised              = lookUp  (fsLit "-funregisterised")
279
280 -- Derived, not a real option.  Determines whether we will be compiling
281 -- info tables that reside just before the entry code, or with an
282 -- indirection to the entry code.  See TABLES_NEXT_TO_CODE in 
283 -- includes/InfoTables.h.
284 tablesNextToCode :: Bool
285 tablesNextToCode                = not opt_Unregisterised
286                                   && cGhcEnableTablesNextToCode == "YES"
287
288 opt_EmitExternalCore :: Bool
289 opt_EmitExternalCore            = lookUp  (fsLit "-fext-core")
290
291 -- Include full span info in error messages, instead of just the start position.
292 opt_ErrorSpans :: Bool
293 opt_ErrorSpans                  = lookUp (fsLit "-ferror-spans")
294
295
296 -- object files and libraries to be linked in are collected here.
297 -- ToDo: perhaps this could be done without a global, it wasn't obvious
298 -- how to do it though --SDM.
299 GLOBAL_VAR(v_Ld_inputs, [],      [String])
300
301 -----------------------------------------------------------------------------
302 -- Ways
303
304 -- The central concept of a "way" is that all objects in a given
305 -- program must be compiled in the same "way".  Certain options change
306 -- parameters of the virtual machine, eg. profiling adds an extra word
307 -- to the object header, so profiling objects cannot be linked with
308 -- non-profiling objects.
309
310 -- After parsing the command-line options, we determine which "way" we
311 -- are building - this might be a combination way, eg. profiling+ticky-ticky.
312
313 -- We then find the "build-tag" associated with this way, and this
314 -- becomes the suffix used to find .hi files and libraries used in
315 -- this compilation.
316
317 GLOBAL_VAR(v_Build_tag, "", String)
318
319 -- The RTS has its own build tag, because there are some ways that
320 -- affect the RTS only.
321 GLOBAL_VAR(v_RTS_Build_tag, "", String)
322
323 data WayName
324   = WayThreaded
325   | WayDebug
326   | WayProf
327   | WayTicky
328   | WayPar
329   | WayGran
330   | WayNDP
331   | WayUser_a
332   | WayUser_b
333   | WayUser_c
334   | WayUser_d
335   | WayUser_e
336   | WayUser_f
337   | WayUser_g
338   | WayUser_h
339   | WayUser_i
340   | WayUser_j
341   | WayUser_k
342   | WayUser_l
343   | WayUser_m
344   | WayUser_n
345   | WayUser_o
346   | WayUser_A
347   | WayUser_B
348   deriving (Eq,Ord)
349
350 GLOBAL_VAR(v_Ways, [] ,[WayName])
351
352 allowed_combination :: [WayName] -> Bool
353 allowed_combination way = and [ x `allowedWith` y 
354                               | x <- way, y <- way, x < y ]
355   where
356         -- Note ordering in these tests: the left argument is
357         -- <= the right argument, according to the Ord instance
358         -- on Way above.
359
360         -- debug is allowed with everything
361         _ `allowedWith` WayDebug                = True
362         WayDebug `allowedWith` _                = True
363
364         WayProf `allowedWith` WayNDP            = True
365         WayThreaded `allowedWith` WayProf       = True
366         _ `allowedWith` _                       = False
367
368
369 findBuildTag :: IO [String]  -- new options
370 findBuildTag = do
371   way_names <- readIORef v_Ways
372   let ws = sort (nub way_names)
373
374   if not (allowed_combination ws)
375       then ghcError (CmdLineError $
376                     "combination not supported: "  ++
377                     foldr1 (\a b -> a ++ '/':b) 
378                     (map (wayName . lkupWay) ws))
379       else let ways    = map lkupWay ws
380                tag     = mkBuildTag (filter (not.wayRTSOnly) ways)
381                rts_tag = mkBuildTag ways
382                flags   = map wayOpts ways
383            in do
384            writeIORef v_Build_tag tag
385            writeIORef v_RTS_Build_tag rts_tag
386            return (concat flags)
387
388
389
390 mkBuildTag :: [Way] -> String
391 mkBuildTag ways = concat (intersperse "_" (map wayTag ways))
392
393 lkupWay :: WayName -> Way
394 lkupWay w = 
395    case lookup w way_details of
396         Nothing -> error "findBuildTag"
397         Just details -> details
398
399 isRTSWay :: WayName -> Bool
400 isRTSWay = wayRTSOnly . lkupWay 
401
402 data Way = Way {
403   wayTag     :: String,
404   wayRTSOnly :: Bool,
405   wayName    :: String,
406   wayOpts    :: [String]
407   }
408
409 way_details :: [ (WayName, Way) ]
410 way_details =
411   [ (WayThreaded, Way "thr" True "Threaded" [
412 #if defined(freebsd_TARGET_OS)
413 --        "-optc-pthread"
414 --      , "-optl-pthread"
415         -- FreeBSD's default threading library is the KSE-based M:N libpthread,
416         -- which GHC has some problems with.  It's currently not clear whether
417         -- the problems are our fault or theirs, but it seems that using the
418         -- alternative 1:1 threading library libthr works around it:
419           "-optl-lthr"
420 #elif defined(solaris2_TARGET_OS)
421           "-optl-lrt"
422 #endif
423         ] ),
424
425     (WayDebug, Way "debug" True "Debug" [] ),
426
427     (WayProf, Way  "p" False "Profiling"
428         [ "-fscc-profiling"
429         , "-DPROFILING"
430         , "-optc-DPROFILING" ]),
431
432     (WayTicky, Way  "t" True "Ticky-ticky Profiling"  
433         [ "-DTICKY_TICKY"
434         , "-optc-DTICKY_TICKY" ]),
435
436     -- optl's below to tell linker where to find the PVM library -- HWL
437     (WayPar, Way  "mp" False "Parallel" 
438         [ "-fparallel"
439         , "-D__PARALLEL_HASKELL__"
440         , "-optc-DPAR"
441         , "-package concurrent"
442         , "-optc-w"
443         , "-optl-L${PVM_ROOT}/lib/${PVM_ARCH}"
444         , "-optl-lpvm3"
445         , "-optl-lgpvm3" ]),
446
447     -- at the moment we only change the RTS and could share compiler and libs!
448     (WayPar, Way  "mt" False "Parallel ticky profiling" 
449         [ "-fparallel"
450         , "-D__PARALLEL_HASKELL__"
451         , "-optc-DPAR"
452         , "-optc-DPAR_TICKY"
453         , "-package concurrent"
454         , "-optc-w"
455         , "-optl-L${PVM_ROOT}/lib/${PVM_ARCH}"
456         , "-optl-lpvm3"
457         , "-optl-lgpvm3" ]),
458
459     (WayPar, Way  "md" False "Distributed" 
460         [ "-fparallel"
461         , "-D__PARALLEL_HASKELL__"
462         , "-D__DISTRIBUTED_HASKELL__"
463         , "-optc-DPAR"
464         , "-optc-DDIST"
465         , "-package concurrent"
466         , "-optc-w"
467         , "-optl-L${PVM_ROOT}/lib/${PVM_ARCH}"
468         , "-optl-lpvm3"
469         , "-optl-lgpvm3" ]),
470
471     (WayGran, Way  "mg" False "GranSim"
472         [ "-fgransim"
473         , "-D__GRANSIM__"
474         , "-optc-DGRAN"
475         , "-package concurrent" ]),
476
477     (WayNDP, Way  "ndp" False "Nested data parallelism"
478         [ "-XParr"
479         , "-fvectorise"]),
480
481     (WayUser_a,  Way  "a"  False "User way 'a'"  ["$WAY_a_REAL_OPTS"]), 
482     (WayUser_b,  Way  "b"  False "User way 'b'"  ["$WAY_b_REAL_OPTS"]), 
483     (WayUser_c,  Way  "c"  False "User way 'c'"  ["$WAY_c_REAL_OPTS"]), 
484     (WayUser_d,  Way  "d"  False "User way 'd'"  ["$WAY_d_REAL_OPTS"]), 
485     (WayUser_e,  Way  "e"  False "User way 'e'"  ["$WAY_e_REAL_OPTS"]), 
486     (WayUser_f,  Way  "f"  False "User way 'f'"  ["$WAY_f_REAL_OPTS"]), 
487     (WayUser_g,  Way  "g"  False "User way 'g'"  ["$WAY_g_REAL_OPTS"]), 
488     (WayUser_h,  Way  "h"  False "User way 'h'"  ["$WAY_h_REAL_OPTS"]), 
489     (WayUser_i,  Way  "i"  False "User way 'i'"  ["$WAY_i_REAL_OPTS"]), 
490     (WayUser_j,  Way  "j"  False "User way 'j'"  ["$WAY_j_REAL_OPTS"]), 
491     (WayUser_k,  Way  "k"  False "User way 'k'"  ["$WAY_k_REAL_OPTS"]), 
492     (WayUser_l,  Way  "l"  False "User way 'l'"  ["$WAY_l_REAL_OPTS"]), 
493     (WayUser_m,  Way  "m"  False "User way 'm'"  ["$WAY_m_REAL_OPTS"]), 
494     (WayUser_n,  Way  "n"  False "User way 'n'"  ["$WAY_n_REAL_OPTS"]), 
495     (WayUser_o,  Way  "o"  False "User way 'o'"  ["$WAY_o_REAL_OPTS"]), 
496     (WayUser_A,  Way  "A"  False "User way 'A'"  ["$WAY_A_REAL_OPTS"]), 
497     (WayUser_B,  Way  "B"  False "User way 'B'"  ["$WAY_B_REAL_OPTS"]) 
498   ]
499