1 -----------------------------------------------------------------------------
2 -- $Id: DriverState.hs,v 1.33 2001/03/12 14:06:47 simonpj Exp $
4 -- Settings for the driver
6 -- (c) The University of Glasgow 2000
8 -----------------------------------------------------------------------------
10 module DriverState where
12 #include "HsVersions.h"
21 #ifdef mingw32_TARGET_OS
22 import TmpFiles ( newTempName )
23 import Directory ( removeFile )
31 -----------------------------------------------------------------------------
32 -- non-configured things
34 cHaskell1Version = "5" -- i.e., Haskell 98
36 -----------------------------------------------------------------------------
37 -- Global compilation flags
39 -- location of compiler-related files
40 GLOBAL_VAR(v_TopDir, clibdir, String)
43 v_Hs_source_cpp_opts = global
44 [ "-D__HASKELL1__="++cHaskell1Version
45 , "-D__GLASGOW_HASKELL__="++cProjectVersionInt
47 , "-D__CONCURRENT_HASKELL__"
49 {-# NOINLINE v_Hs_source_cpp_opts #-}
51 -- Keep output from intermediate phases
52 GLOBAL_VAR(v_Keep_hi_diffs, False, Bool)
53 GLOBAL_VAR(v_Keep_hc_files, False, Bool)
54 GLOBAL_VAR(v_Keep_s_files, False, Bool)
55 GLOBAL_VAR(v_Keep_raw_s_files, False, Bool)
56 GLOBAL_VAR(v_Keep_tmp_files, False, Bool)
59 GLOBAL_VAR(v_Scale_sizes_by, 1.0, Double)
60 GLOBAL_VAR(v_Dry_run, False, Bool)
61 GLOBAL_VAR(v_Static, True, Bool)
62 GLOBAL_VAR(v_NoHsMain, False, Bool)
63 GLOBAL_VAR(v_Recomp, True, Bool)
64 GLOBAL_VAR(v_Collect_ghc_timing, False, Bool)
65 GLOBAL_VAR(v_Do_asm_mangling, True, Bool)
66 GLOBAL_VAR(v_Excess_precision, False, Bool)
68 -----------------------------------------------------------------------------
69 -- Splitting object files (for libraries)
71 GLOBAL_VAR(v_Split_object_files, False, Bool)
72 GLOBAL_VAR(v_Split_prefix, "", String)
73 GLOBAL_VAR(v_N_split_files, 0, Int)
76 can_split = prefixMatch "i386" cTARGETPLATFORM
77 || prefixMatch "alpha" cTARGETPLATFORM
78 || prefixMatch "hppa" cTARGETPLATFORM
79 || prefixMatch "m68k" cTARGETPLATFORM
80 || prefixMatch "mips" cTARGETPLATFORM
81 || prefixMatch "powerpc" cTARGETPLATFORM
82 || prefixMatch "rs6000" cTARGETPLATFORM
83 || prefixMatch "sparc" cTARGETPLATFORM
85 -----------------------------------------------------------------------------
86 -- Compiler output options
89 | cGhcWithNativeCodeGen == "YES" &&
90 (prefixMatch "i386" cTARGETPLATFORM ||
91 prefixMatch "sparc" cTARGETPLATFORM) = HscAsm
94 GLOBAL_VAR(v_Output_dir, Nothing, Maybe String)
95 GLOBAL_VAR(v_Object_suf, Nothing, Maybe String)
96 GLOBAL_VAR(v_Output_file, Nothing, Maybe String)
97 GLOBAL_VAR(v_Output_hi, Nothing, Maybe String)
99 GLOBAL_VAR(v_Ld_inputs, [], [String])
101 odir_ify :: String -> IO String
103 odir_opt <- readIORef v_Output_dir
106 Just d -> return (newdir d f)
108 osuf_ify :: String -> IO String
110 osuf_opt <- readIORef v_Object_suf
113 Just s -> return (newsuf s f)
115 -----------------------------------------------------------------------------
118 GLOBAL_VAR(v_Hi_on_stdout, False, Bool)
119 GLOBAL_VAR(v_Hi_suf, "hi", String)
121 -----------------------------------------------------------------------------
122 -- Compiler optimisation options
124 GLOBAL_VAR(v_OptLevel, 0, Int)
126 setOptLevel :: String -> IO ()
127 setOptLevel "" = do { writeIORef v_OptLevel 1 }
128 setOptLevel "not" = writeIORef v_OptLevel 0
129 setOptLevel [c] | isDigit c = do
130 let level = ord c - ord '0'
131 writeIORef v_OptLevel level
132 setOptLevel s = unknownFlagErr ("-O"++s)
134 GLOBAL_VAR(v_minus_o2_for_C, False, Bool)
135 GLOBAL_VAR(v_MaxSimplifierIterations, 4, Int)
136 GLOBAL_VAR(v_StgStats, False, Bool)
137 GLOBAL_VAR(v_UsageSPInf, False, Bool) -- Off by default
138 GLOBAL_VAR(v_Strictness, True, Bool)
139 GLOBAL_VAR(v_CPR, True, Bool)
140 GLOBAL_VAR(v_CSE, True, Bool)
142 -- these are the static flags you get without -O.
145 "-fignore-interface-pragmas",
146 "-fomit-interface-pragmas",
147 "-fdo-lambda-eta-expansion", -- This one is important for a tiresome reason:
148 -- we want to make sure that the bindings for data
149 -- constructors are eta-expanded. This is probably
150 -- a good thing anyway, but it seems fragile.
154 -- these are the static flags you get when -O is on.
159 "-fdo-eta-reduction",
160 "-fdo-lambda-eta-expansion",
166 hsc_minusO2_flags = hsc_minusO_flags -- for now
168 getStaticOptimisationFlags 0 = hsc_minusNoO_flags
169 getStaticOptimisationFlags 1 = hsc_minusO_flags
170 getStaticOptimisationFlags n = hsc_minusO2_flags
172 buildCoreToDo :: IO [CoreToDo]
174 opt_level <- readIORef v_OptLevel
175 max_iter <- readIORef v_MaxSimplifierIterations
176 usageSP <- readIORef v_UsageSPInf
177 strictness <- readIORef v_Strictness
178 cpr <- readIORef v_CPR
179 cse <- readIORef v_CSE
181 if opt_level == 0 then return
183 CoreDoSimplify (isAmongSimpl [
184 MaxSimplifierIterations max_iter
188 else {- opt_level >= 1 -} return [
190 -- initial simplify: mk specialiser happy: minimum effort please
191 CoreDoSimplify (isAmongSimpl [
193 -- Don't inline anything till full laziness has bitten
194 -- In particular, inlining wrappers inhibits floating
195 -- e.g. ...(case f x of ...)...
196 -- ==> ...(case (case x of I# x# -> fw x#) of ...)...
197 -- ==> ...(case x of I# x# -> case fw x# of ...)...
198 -- and now the redex (f x) isn't floatable any more
200 -- Similarly, don't apply any rules until after full
201 -- laziness. Notably, list fusion can prevent floating.
203 -- Don't do case-of-case transformations.
204 -- This makes full laziness work better
205 MaxSimplifierIterations max_iter
208 -- Specialisation is best done before full laziness
209 -- so that overloaded functions have all their dictionary lambdas manifest
212 CoreDoFloatOutwards False{-not full-},
215 CoreDoSimplify (isAmongSimpl [
217 -- Want to run with inline phase 1 after the specialiser to give
218 -- maximum chance for fusion to work before we inline build/augment
219 -- in phase 2. This made a difference in 'ansi' where an
220 -- overloaded function wasn't inlined till too late.
221 MaxSimplifierIterations max_iter
224 -- infer usage information here in case we need it later.
225 -- (add more of these where you need them --KSW 1999-04)
226 if usageSP then CoreDoUSPInf else CoreDoNothing,
228 CoreDoSimplify (isAmongSimpl [
229 -- Need inline-phase2 here so that build/augment get
230 -- inlined. I found that spectral/hartel/genfft lost some useful
231 -- strictness in the function sumcode' if augment is not inlined
232 -- before strictness analysis runs
234 MaxSimplifierIterations max_iter
237 CoreDoSimplify (isAmongSimpl [
238 MaxSimplifierIterations 2
239 -- No -finline-phase: allow all Ids to be inlined now
240 -- This gets foldr inlined before strictness analysis
243 if strictness then CoreDoStrictness else CoreDoNothing,
244 if cpr then CoreDoCPResult else CoreDoNothing,
248 CoreDoSimplify (isAmongSimpl [
249 MaxSimplifierIterations max_iter
250 -- No -finline-phase: allow all Ids to be inlined now
253 CoreDoFloatOutwards False{-not full-},
254 -- nofib/spectral/hartel/wang doubles in speed if you
255 -- do full laziness late in the day. It only happens
256 -- after fusion and other stuff, so the early pass doesn't
257 -- catch it. For the record, the redex is
258 -- f_el22 (f_el21 r_midblock)
261 -- Leave out lambda lifting for now
262 -- "-fsimplify", -- Tidy up results of full laziness
264 -- "-fmax-simplifier-iterations2",
266 -- "-ffloat-outwards-full",
268 -- We want CSE to follow the final full-laziness pass, because it may
269 -- succeed in commoning up things floated out by full laziness.
270 -- CSE used to rely on the no-shadowing invariant, but it doesn't any more
272 if cse then CoreCSE else CoreDoNothing,
276 -- Case-liberation for -O2. This should be after
277 -- strictness analysis and the simplification which follows it.
279 if opt_level >= 2 then
283 if opt_level >= 2 then
288 -- Final clean-up simplification:
289 CoreDoSimplify (isAmongSimpl [
290 MaxSimplifierIterations max_iter
291 -- No -finline-phase: allow all Ids to be inlined now
295 buildStgToDo :: IO [ StgToDo ]
297 stg_stats <- readIORef v_StgStats
298 let flags1 | stg_stats = [ D_stg_stats ]
302 ways_ <- readIORef v_Ways
303 let flags2 | WayProf `elem` ways_ = StgDoMassageForProfiling : flags1
308 -----------------------------------------------------------------------------
311 split_marker = ':' -- not configurable (ToDo)
313 v_Import_paths, v_Include_paths, v_Library_paths :: IORef [String]
314 GLOBAL_VAR(v_Import_paths, ["."], [String])
315 GLOBAL_VAR(v_Include_paths, ["."], [String])
316 GLOBAL_VAR(v_Library_paths, [], [String])
318 GLOBAL_VAR(v_Cmdline_libraries, [], [String])
320 addToDirList :: IORef [String] -> String -> IO ()
321 addToDirList ref path
322 = do paths <- readIORef ref
323 writeIORef ref (paths ++ split split_marker path)
325 -----------------------------------------------------------------------------
328 GLOBAL_VAR(v_Path_package_config, error "path_package_config", String)
330 -- package list is maintained in dependency order
331 GLOBAL_VAR(v_Packages, ("std":"rts":"gmp":[]), [String])
333 addPackage :: String -> IO ()
335 = do pkg_details <- readIORef v_Package_details
336 case lookupPkg package pkg_details of
337 Nothing -> throwDyn (OtherError ("unknown package name: " ++ package))
339 ps <- readIORef v_Packages
340 unless (package `elem` ps) $ do
341 mapM_ addPackage (package_deps details)
342 ps <- readIORef v_Packages
343 writeIORef v_Packages (package:ps)
345 getPackageImportPath :: IO [String]
346 getPackageImportPath = do
348 return (nub (concat (map import_dirs ps)))
350 getPackageIncludePath :: IO [String]
351 getPackageIncludePath = do
353 return (nub (filter (not.null) (concatMap include_dirs ps)))
355 -- includes are in reverse dependency order (i.e. rts first)
356 getPackageCIncludes :: IO [String]
357 getPackageCIncludes = do
359 return (reverse (nub (filter (not.null) (concatMap c_includes ps))))
361 getPackageLibraryPath :: IO [String]
362 getPackageLibraryPath = do
364 return (nub (concat (map library_dirs ps)))
366 getPackageLibraries :: IO [String]
367 getPackageLibraries = do
369 tag <- readIORef v_Build_tag
370 let suffix = if null tag then "" else '_':tag
372 map (\p -> map (++suffix) (hs_libraries p) ++ extra_libraries p) ps
375 getPackageExtraGhcOpts :: IO [String]
376 getPackageExtraGhcOpts = do
378 return (concatMap extra_ghc_opts ps)
380 getPackageExtraCcOpts :: IO [String]
381 getPackageExtraCcOpts = do
383 return (concatMap extra_cc_opts ps)
385 getPackageExtraLdOpts :: IO [String]
386 getPackageExtraLdOpts = do
388 return (concatMap extra_ld_opts ps)
390 getPackageInfo :: IO [PackageConfig]
392 ps <- readIORef v_Packages
395 getPackageDetails :: [String] -> IO [PackageConfig]
396 getPackageDetails ps = do
397 pkg_details <- readIORef v_Package_details
398 return [ pkg | p <- ps, Just pkg <- [ lookupPkg p pkg_details ] ]
400 GLOBAL_VAR(v_Package_details, (error "package_details"), [PackageConfig])
402 lookupPkg :: String -> [PackageConfig] -> Maybe PackageConfig
404 = case [p | p <- ps, name p == nm] of
407 -----------------------------------------------------------------------------
410 -- The central concept of a "way" is that all objects in a given
411 -- program must be compiled in the same "way". Certain options change
412 -- parameters of the virtual machine, eg. profiling adds an extra word
413 -- to the object header, so profiling objects cannot be linked with
414 -- non-profiling objects.
416 -- After parsing the command-line options, we determine which "way" we
417 -- are building - this might be a combination way, eg. profiling+ticky-ticky.
419 -- We then find the "build-tag" associated with this way, and this
420 -- becomes the suffix used to find .hi files and libraries used in
423 GLOBAL_VAR(v_Build_tag, "", String)
452 GLOBAL_VAR(v_Ways, [] ,[WayName])
454 allowed_combination way = way `elem` combs
455 where -- the sub-lists must be ordered according to WayName,
456 -- because findBuildTag sorts them
457 combs = [ [WayProf,WayUnreg], [WayProf,WaySMP] ]
459 findBuildTag :: IO [String] -- new options
461 way_names <- readIORef v_Ways
462 case sort way_names of
463 [] -> do writeIORef v_Build_tag ""
466 [w] -> do let details = lkupWay w
467 writeIORef v_Build_tag (wayTag details)
468 return (wayOpts details)
470 ws -> if not (allowed_combination ws)
471 then throwDyn (OtherError $
472 "combination not supported: " ++
473 foldr1 (\a b -> a ++ '/':b)
474 (map (wayName . lkupWay) ws))
475 else let stuff = map lkupWay ws
476 tag = concat (map wayTag stuff)
477 flags = map wayOpts stuff
479 writeIORef v_Build_tag tag
480 return (concat flags)
483 case lookup w way_details of
484 Nothing -> error "findBuildTag"
485 Just details -> details
493 way_details :: [ (WayName, Way) ]
495 [ (WayProf, Way "p" "Profiling"
501 (WayTicky, Way "t" "Ticky-ticky Profiling"
504 , "-optc-DTICKY_TICKY"
507 (WayUnreg, Way "u" "Unregisterised"
510 (WayPar, Way "mp" "Parallel"
512 , "-D__PARALLEL_HASKELL__"
514 , "-package concurrent"
517 (WayGran, Way "mg" "Gransim"
521 , "-package concurrent"
524 (WaySMP, Way "s" "SMP"
531 (WayUser_a, Way "a" "User way 'a'" ["$WAY_a_REAL_OPTS"]),
532 (WayUser_b, Way "b" "User way 'b'" ["$WAY_b_REAL_OPTS"]),
533 (WayUser_c, Way "c" "User way 'c'" ["$WAY_c_REAL_OPTS"]),
534 (WayUser_d, Way "d" "User way 'd'" ["$WAY_d_REAL_OPTS"]),
535 (WayUser_e, Way "e" "User way 'e'" ["$WAY_e_REAL_OPTS"]),
536 (WayUser_f, Way "f" "User way 'f'" ["$WAY_f_REAL_OPTS"]),
537 (WayUser_g, Way "g" "User way 'g'" ["$WAY_g_REAL_OPTS"]),
538 (WayUser_h, Way "h" "User way 'h'" ["$WAY_h_REAL_OPTS"]),
539 (WayUser_i, Way "i" "User way 'i'" ["$WAY_i_REAL_OPTS"]),
540 (WayUser_j, Way "j" "User way 'j'" ["$WAY_j_REAL_OPTS"]),
541 (WayUser_k, Way "k" "User way 'k'" ["$WAY_k_REAL_OPTS"]),
542 (WayUser_l, Way "l" "User way 'l'" ["$WAY_l_REAL_OPTS"]),
543 (WayUser_m, Way "m" "User way 'm'" ["$WAY_m_REAL_OPTS"]),
544 (WayUser_n, Way "n" "User way 'n'" ["$WAY_n_REAL_OPTS"]),
545 (WayUser_o, Way "o" "User way 'o'" ["$WAY_o_REAL_OPTS"]),
546 (WayUser_A, Way "A" "User way 'A'" ["$WAY_A_REAL_OPTS"]),
547 (WayUser_B, Way "B" "User way 'B'" ["$WAY_B_REAL_OPTS"])
552 , "-optc-DUSE_MINIINTERPRETER"
553 , "-fno-asm-mangling"
557 -----------------------------------------------------------------------------
558 -- Programs for particular phases
560 GLOBAL_VAR(v_Pgm_L, error "pgm_L", String)
561 GLOBAL_VAR(v_Pgm_P, cRAWCPP, String)
562 GLOBAL_VAR(v_Pgm_c, cGCC, String)
563 GLOBAL_VAR(v_Pgm_m, error "pgm_m", String)
564 GLOBAL_VAR(v_Pgm_s, error "pgm_s", String)
565 GLOBAL_VAR(v_Pgm_a, cGCC, String)
566 GLOBAL_VAR(v_Pgm_l, cGCC, String)
567 GLOBAL_VAR(v_Pgm_dll, cMkDLL, String)
569 GLOBAL_VAR(v_Opt_dep, [], [String])
570 GLOBAL_VAR(v_Anti_opt_C, [], [String])
571 GLOBAL_VAR(v_Opt_C, [], [String])
572 GLOBAL_VAR(v_Opt_l, [], [String])
573 GLOBAL_VAR(v_Opt_dll, [], [String])
575 getStaticOpts :: IORef [String] -> IO [String]
576 getStaticOpts ref = readIORef ref >>= return . reverse