Add -dppr-case-as-let to print "strict lets" as actual lets
[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(..), Way(..), v_Ways, isRTSWay, mkBuildTag,
21
22         -- Output style options
23         opt_PprUserLength,
24         opt_PprCaseAsLet,
25         opt_PprStyle_Debug, opt_TraceLevel,
26         opt_NoDebugOutput,
27
28         -- Suppressing boring aspects of core dumps
29         opt_SuppressAll,
30         opt_SuppressUniques,
31         opt_SuppressCoercions,
32         opt_SuppressModulePrefixes,
33         opt_SuppressTypeApplications,
34         opt_SuppressIdInfo,
35         opt_SuppressTypeSignatures,
36
37         -- profiling opts
38         opt_SccProfilingOn,
39
40         -- Hpc opts
41         opt_Hpc,
42
43         -- language opts
44         opt_DictsStrict,
45         opt_IrrefutableTuples,
46         opt_Parallel,
47
48         -- optimisation opts
49         opt_NoStateHack,
50         opt_SimpleListLiterals,
51         opt_CprOff,
52         opt_SimplNoPreInlining,
53         opt_SimplExcessPrecision,
54         opt_MaxWorkerArgs,
55
56         -- Unfolding control
57         opt_UF_CreationThreshold,
58         opt_UF_UseThreshold,
59         opt_UF_FunAppDiscount,
60         opt_UF_DictDiscount,
61         opt_UF_KeenessFactor,
62         opt_UF_DearOp,
63
64         -- Optimization fuel controls
65         opt_Fuel,
66
67         -- Related to linking
68         opt_PIC,
69         opt_Static,
70
71         -- misc opts
72         opt_IgnoreDotGhci,
73         opt_ErrorSpans,
74         opt_GranMacros,
75         opt_HiVersion,
76         opt_HistorySize,
77         opt_OmitBlackHoling,
78         opt_Unregisterised,
79         v_Ld_inputs,
80         tablesNextToCode,
81         opt_StubDeadValues,
82         opt_Ticky,
83
84     -- For the parser
85     addOpt, removeOpt, addWay, getWayFlags, v_opt_C_ready
86   ) where
87
88 #include "HsVersions.h"
89
90 import Config
91 import FastString
92 import Util
93 import Maybes           ( firstJusts )
94 import Panic
95
96 import Data.Maybe       ( listToMaybe )
97 import Data.IORef
98 import System.IO.Unsafe ( unsafePerformIO )
99 import Data.List
100
101 -----------------------------------------------------------------------------
102 -- Static flags
103
104 initStaticOpts :: IO ()
105 initStaticOpts = writeIORef v_opt_C_ready True
106
107 addOpt :: String -> IO ()
108 addOpt = consIORef v_opt_C
109
110 addWay :: WayName -> IO ()
111 addWay = consIORef v_Ways . lkupWay
112
113 removeOpt :: String -> IO ()
114 removeOpt f = do
115   fs <- readIORef v_opt_C
116   writeIORef v_opt_C $! filter (/= f) fs    
117
118 lookUp           :: FastString -> Bool
119 lookup_def_int   :: String -> Int -> Int
120 lookup_def_float :: String -> Float -> Float
121 lookup_str       :: String -> Maybe String
122
123 -- holds the static opts while they're being collected, before
124 -- being unsafely read by unpacked_static_opts below.
125 GLOBAL_VAR(v_opt_C, defaultStaticOpts, [String])
126 GLOBAL_VAR(v_opt_C_ready, False, Bool)
127
128 staticFlags :: [String]
129 staticFlags = unsafePerformIO $ do
130   ready <- readIORef v_opt_C_ready
131   if (not ready)
132         then panic "Static flags have not been initialised!\n        Please call GHC.newSession or GHC.parseStaticFlags early enough."
133         else readIORef v_opt_C
134
135 -- -static is the default
136 defaultStaticOpts :: [String]
137 defaultStaticOpts = ["-static"]
138
139 packed_static_opts :: [FastString]
140 packed_static_opts   = map mkFastString staticFlags
141
142 lookUp     sw = sw `elem` packed_static_opts
143         
144 -- (lookup_str "foo") looks for the flag -foo=X or -fooX, 
145 -- and returns the string X
146 lookup_str sw 
147    = case firstJusts (map (stripPrefix sw) staticFlags) of
148         Just ('=' : str) -> Just str
149         Just str         -> Just str
150         Nothing          -> Nothing     
151
152 lookup_def_int sw def = case (lookup_str sw) of
153                             Nothing -> def              -- Use default
154                             Just xx -> try_read sw xx
155
156 lookup_def_float sw def = case (lookup_str sw) of
157                             Nothing -> def              -- Use default
158                             Just xx -> try_read sw xx
159
160
161 try_read :: Read a => String -> String -> a
162 -- (try_read sw str) tries to read s; if it fails, it
163 -- bleats about flag sw
164 try_read sw str
165   = case reads str of
166         ((x,_):_) -> x  -- Be forgiving: ignore trailing goop, and alternative parses
167         []        -> ghcError (UsageError ("Malformed argument " ++ str ++ " for flag " ++ sw))
168                         -- ToDo: hack alert. We should really parse the arugments
169                         --       and announce errors in a more civilised way.
170
171
172 {-
173  Putting the compiler options into temporary at-files
174  may turn out to be necessary later on if we turn hsc into
175  a pure Win32 application where I think there's a command-line
176  length limit of 255. unpacked_opts understands the @ option.
177
178 unpacked_opts :: [String]
179 unpacked_opts =
180   concat $
181   map (expandAts) $
182   map unpackFS argv  -- NOT ARGV any more: v_Static_hsc_opts
183   where
184    expandAts ('@':fname) = words (unsafePerformIO (readFile fname))
185    expandAts l = [l]
186 -}
187
188 opt_IgnoreDotGhci :: Bool
189 opt_IgnoreDotGhci               = lookUp (fsLit "-ignore-dot-ghci")
190
191 -- debugging options
192 -- | Suppress all that is suppressable in core dumps.
193 opt_SuppressAll :: Bool
194 opt_SuppressAll 
195         = lookUp  (fsLit "-dsuppress-all")
196
197 -- | Suppress unique ids on variables.
198 opt_SuppressUniques :: Bool
199 opt_SuppressUniques
200         =  lookUp  (fsLit "-dsuppress-all")
201         || lookUp  (fsLit "-dsuppress-uniques")
202
203 -- | Suppress all coercions, them replacing with '...'
204 opt_SuppressCoercions :: Bool
205 opt_SuppressCoercions
206         =  lookUp  (fsLit "-dsuppress-all") 
207         || lookUp  (fsLit "-dsuppress-coercions")
208
209 -- | Suppress module id prefixes on variables.
210 opt_SuppressModulePrefixes :: Bool
211 opt_SuppressModulePrefixes
212         =  lookUp  (fsLit "-dsuppress-all")
213         || lookUp  (fsLit "-dsuppress-module-prefixes")
214
215 -- | Suppress type applications.
216 opt_SuppressTypeApplications :: Bool
217 opt_SuppressTypeApplications
218         =  lookUp  (fsLit "-dsuppress-all")
219         || lookUp  (fsLit "-dsuppress-type-applications")
220
221 -- | Suppress info such as arity and unfoldings on identifiers.
222 opt_SuppressIdInfo :: Bool
223 opt_SuppressIdInfo 
224         =  lookUp  (fsLit "-dsuppress-all")
225         || lookUp  (fsLit "-dsuppress-idinfo")
226
227 -- | Suppress seprate type signatures in core, but leave types on lambda bound vars
228 opt_SuppressTypeSignatures :: Bool
229 opt_SuppressTypeSignatures
230         =  lookUp  (fsLit "-dsuppress-all")
231         || lookUp  (fsLit "-dsuppress-type-signatures")
232
233
234 -- | Display case expressions with a single alternative as strict let bindings
235 opt_PprCaseAsLet :: Bool
236 opt_PprCaseAsLet
237         = lookUp   (fsLit "-dppr-case-as-let")
238
239 opt_PprStyle_Debug  :: Bool
240 opt_PprStyle_Debug              = lookUp  (fsLit "-dppr-debug")
241
242 opt_TraceLevel :: Int
243 opt_TraceLevel = lookup_def_int "-dtrace-level" 1       -- Standard level is 1
244                                                         -- Less verbose is 0
245
246 opt_PprUserLength   :: Int
247 opt_PprUserLength               = lookup_def_int "-dppr-user-length" 5 --ToDo: give this a name
248
249 opt_Fuel            :: Int
250 opt_Fuel                        = lookup_def_int "-dopt-fuel" maxBound
251
252 opt_NoDebugOutput   :: Bool
253 opt_NoDebugOutput               = lookUp  (fsLit "-dno-debug-output")
254
255
256 -- profiling opts
257 opt_SccProfilingOn :: Bool
258 opt_SccProfilingOn              = lookUp  (fsLit "-fscc-profiling")
259
260 -- Hpc opts
261 opt_Hpc :: Bool
262 opt_Hpc                         = lookUp (fsLit "-fhpc")  
263
264 -- language opts
265 opt_DictsStrict :: Bool
266 opt_DictsStrict                 = lookUp  (fsLit "-fdicts-strict")
267
268 opt_IrrefutableTuples :: Bool
269 opt_IrrefutableTuples           = lookUp  (fsLit "-firrefutable-tuples")
270
271 opt_Parallel :: Bool
272 opt_Parallel                    = lookUp  (fsLit "-fparallel")
273
274 opt_SimpleListLiterals :: Bool
275 opt_SimpleListLiterals          = lookUp  (fsLit "-fsimple-list-literals")
276
277 opt_NoStateHack :: Bool
278 opt_NoStateHack                 = lookUp  (fsLit "-fno-state-hack")
279
280 opt_CprOff :: Bool
281 opt_CprOff                      = lookUp  (fsLit "-fcpr-off")
282         -- Switch off CPR analysis in the new demand analyser
283 opt_MaxWorkerArgs :: Int
284 opt_MaxWorkerArgs               = lookup_def_int "-fmax-worker-args" (10::Int)
285
286 opt_GranMacros :: Bool
287 opt_GranMacros                  = lookUp  (fsLit "-fgransim")
288
289 opt_HiVersion :: Integer
290 opt_HiVersion                   = read (cProjectVersionInt ++ cProjectPatchLevel) :: Integer
291
292 opt_HistorySize :: Int
293 opt_HistorySize                 = lookup_def_int "-fhistory-size" 20
294
295 opt_OmitBlackHoling :: Bool
296 opt_OmitBlackHoling             = lookUp  (fsLit "-dno-black-holing")
297
298 opt_StubDeadValues  :: Bool
299 opt_StubDeadValues              = lookUp  (fsLit "-dstub-dead-values")
300
301 -- Simplifier switches
302 opt_SimplNoPreInlining :: Bool
303 opt_SimplNoPreInlining          = lookUp  (fsLit "-fno-pre-inlining")
304         -- NoPreInlining is there just to see how bad things
305         -- get if you don't do it!
306 opt_SimplExcessPrecision :: Bool
307 opt_SimplExcessPrecision        = lookUp  (fsLit "-fexcess-precision")
308
309 -- Unfolding control
310 -- See Note [Discounts and thresholds] in CoreUnfold
311
312 opt_UF_CreationThreshold, opt_UF_UseThreshold :: Int
313 opt_UF_DearOp, opt_UF_FunAppDiscount, opt_UF_DictDiscount :: Int
314 opt_UF_KeenessFactor :: Float
315
316 opt_UF_CreationThreshold = lookup_def_int "-funfolding-creation-threshold" (45::Int)
317 opt_UF_UseThreshold      = lookup_def_int "-funfolding-use-threshold"      (6::Int)
318 opt_UF_FunAppDiscount    = lookup_def_int "-funfolding-fun-discount"       (6::Int)
319
320 opt_UF_DictDiscount      = lookup_def_int "-funfolding-dict-discount"      (3::Int)
321    -- Be fairly keen to inline a fuction if that means
322    -- we'll be able to pick the right method from a dictionary
323
324 opt_UF_KeenessFactor     = lookup_def_float "-funfolding-keeness-factor"   (1.5::Float)
325 opt_UF_DearOp            = ( 4 :: Int)
326
327
328 -- Related to linking
329 opt_PIC :: Bool
330 #if darwin_TARGET_OS && x86_64_TARGET_ARCH
331 opt_PIC                         = True
332 #elif darwin_TARGET_OS
333 opt_PIC                         = lookUp (fsLit "-fPIC") || not opt_Static
334 #else
335 opt_PIC                         = lookUp (fsLit "-fPIC")
336 #endif
337 opt_Static :: Bool
338 opt_Static                      = lookUp  (fsLit "-static")
339 opt_Unregisterised :: Bool
340 opt_Unregisterised              = lookUp  (fsLit "-funregisterised")
341
342 -- Derived, not a real option.  Determines whether we will be compiling
343 -- info tables that reside just before the entry code, or with an
344 -- indirection to the entry code.  See TABLES_NEXT_TO_CODE in 
345 -- includes/rts/storage/InfoTables.h.
346 tablesNextToCode :: Bool
347 tablesNextToCode                = not opt_Unregisterised
348                                   && cGhcEnableTablesNextToCode == "YES"
349
350 -- Include full span info in error messages, instead of just the start position.
351 opt_ErrorSpans :: Bool
352 opt_ErrorSpans                  = lookUp (fsLit "-ferror-spans")
353
354 opt_Ticky :: Bool
355 opt_Ticky                       = lookUp (fsLit "-ticky")
356
357 -- object files and libraries to be linked in are collected here.
358 -- ToDo: perhaps this could be done without a global, it wasn't obvious
359 -- how to do it though --SDM.
360 GLOBAL_VAR(v_Ld_inputs, [],      [String])
361
362 -----------------------------------------------------------------------------
363 -- Ways
364
365 -- The central concept of a "way" is that all objects in a given
366 -- program must be compiled in the same "way".  Certain options change
367 -- parameters of the virtual machine, eg. profiling adds an extra word
368 -- to the object header, so profiling objects cannot be linked with
369 -- non-profiling objects.
370
371 -- After parsing the command-line options, we determine which "way" we
372 -- are building - this might be a combination way, eg. profiling+threaded.
373
374 -- We then find the "build-tag" associated with this way, and this
375 -- becomes the suffix used to find .hi files and libraries used in
376 -- this compilation.
377
378 data WayName
379   = WayThreaded
380   | WayDebug
381   | WayProf
382   | WayEventLog
383   | WayPar
384   | WayGran
385   | WayNDP
386   | WayDyn
387   deriving (Eq,Ord)
388
389 GLOBAL_VAR(v_Ways, [] ,[Way])
390
391 allowed_combination :: [WayName] -> Bool
392 allowed_combination way = and [ x `allowedWith` y 
393                               | x <- way, y <- way, x < y ]
394   where
395         -- Note ordering in these tests: the left argument is
396         -- <= the right argument, according to the Ord instance
397         -- on Way above.
398
399         -- dyn is allowed with everything
400         _ `allowedWith` WayDyn                  = True
401         WayDyn `allowedWith` _                  = True
402
403         -- debug is allowed with everything
404         _ `allowedWith` WayDebug                = True
405         WayDebug `allowedWith` _                = True
406
407         WayProf `allowedWith` WayNDP            = True
408         WayThreaded `allowedWith` WayProf       = True
409         WayThreaded `allowedWith` WayEventLog   = True
410         _ `allowedWith` _                       = False
411
412
413 getWayFlags :: IO [String]  -- new options
414 getWayFlags = do
415   unsorted <- readIORef v_Ways
416   let ways = sortBy (compare `on` wayName) $
417              nubBy  ((==) `on` wayName) $ unsorted
418   writeIORef v_Ways ways
419
420   if not (allowed_combination (map wayName ways))
421       then ghcError (CmdLineError $
422                     "combination not supported: "  ++
423                     foldr1 (\a b -> a ++ '/':b) 
424                     (map wayDesc ways))
425       else
426            return (concatMap wayOpts ways)
427
428 mkBuildTag :: [Way] -> String
429 mkBuildTag ways = concat (intersperse "_" (map wayTag ways))
430
431 lkupWay :: WayName -> Way
432 lkupWay w = 
433    case listToMaybe (filter ((==) w . wayName) way_details) of
434         Nothing -> error "findBuildTag"
435         Just details -> details
436
437 isRTSWay :: WayName -> Bool
438 isRTSWay = wayRTSOnly . lkupWay 
439
440 data Way = Way {
441   wayName    :: WayName,
442   wayTag     :: String,
443   wayRTSOnly :: Bool,
444   wayDesc    :: String,
445   wayOpts    :: [String]
446   }
447
448 way_details :: [ Way ]
449 way_details =
450   [ Way WayThreaded "thr" True "Threaded" [
451 #if defined(freebsd_TARGET_OS)
452 --        "-optc-pthread"
453 --      , "-optl-pthread"
454         -- FreeBSD's default threading library is the KSE-based M:N libpthread,
455         -- which GHC has some problems with.  It's currently not clear whether
456         -- the problems are our fault or theirs, but it seems that using the
457         -- alternative 1:1 threading library libthr works around it:
458           "-optl-lthr"
459 #elif defined(openbsd_TARGET_OS)
460           "-optc-pthread"
461         , "-optl-pthread"
462 #elif defined(solaris2_TARGET_OS)
463           "-optl-lrt"
464 #endif
465         ],
466
467     Way WayDebug "debug" True "Debug" [],
468
469     Way WayDyn "dyn" False "Dynamic"
470         [ "-DDYNAMIC"
471         , "-optc-DDYNAMIC" 
472 #if defined(mingw32_TARGET_OS)
473         -- On Windows, code that is to be linked into a dynamic library must be compiled
474         --      with -fPIC. Labels not in the current package are assumed to be in a DLL 
475         --      different from the current one.
476         , "-fPIC"
477 #elif defined(openbsd_TARGET_OS)
478         -- Without this, linking the shared libHSffi fails because
479         -- it uses pthread mutexes.
480         , "-optl-pthread"
481 #endif
482         ],
483
484     Way WayProf "p" False "Profiling"
485         [ "-fscc-profiling"
486         , "-DPROFILING"
487         , "-optc-DPROFILING" ],
488
489     Way WayEventLog "l" True "RTS Event Logging"
490         [ "-DTRACING"
491         , "-optc-DTRACING" ],
492
493     Way WayPar "mp" False "Parallel" 
494         [ "-fparallel"
495         , "-D__PARALLEL_HASKELL__"
496         , "-optc-DPAR"
497         , "-package concurrent"
498         , "-optc-w"
499         , "-optl-L${PVM_ROOT}/lib/${PVM_ARCH}"
500         , "-optl-lpvm3"
501         , "-optl-lgpvm3" ],
502
503     -- at the moment we only change the RTS and could share compiler and libs!
504     Way WayPar "mt" False "Parallel ticky profiling" 
505         [ "-fparallel"
506         , "-D__PARALLEL_HASKELL__"
507         , "-optc-DPAR"
508         , "-optc-DPAR_TICKY"
509         , "-package concurrent"
510         , "-optc-w"
511         , "-optl-L${PVM_ROOT}/lib/${PVM_ARCH}"
512         , "-optl-lpvm3"
513         , "-optl-lgpvm3" ],
514
515     Way WayPar "md" False "Distributed" 
516         [ "-fparallel"
517         , "-D__PARALLEL_HASKELL__"
518         , "-D__DISTRIBUTED_HASKELL__"
519         , "-optc-DPAR"
520         , "-optc-DDIST"
521         , "-package concurrent"
522         , "-optc-w"
523         , "-optl-L${PVM_ROOT}/lib/${PVM_ARCH}"
524         , "-optl-lpvm3"
525         , "-optl-lgpvm3" ],
526
527     Way WayGran "mg" False "GranSim"
528         [ "-fgransim"
529         , "-D__GRANSIM__"
530         , "-optc-DGRAN"
531         , "-package concurrent" ],
532
533     Way WayNDP "ndp" False "Nested data parallelism"
534         [ "-XParr"
535         , "-fvectorise"]
536   ]