X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Fmain%2FDriverState.hs;h=c64e2f6152396e2533156c2d9f875c8726235ad8;hb=2cc5b907318f97e19b28b2ad8ed9ff8c1f401dcc;hp=48e683a41cda2abc5dafa09f6fb1ce6013dd0c07;hpb=47108330f6f832dd82aba3d125a1ad114f4a45e7;p=ghc-hetmet.git diff --git a/ghc/compiler/main/DriverState.hs b/ghc/compiler/main/DriverState.hs index 48e683a..c64e2f6 100644 --- a/ghc/compiler/main/DriverState.hs +++ b/ghc/compiler/main/DriverState.hs @@ -1,9 +1,9 @@ ----------------------------------------------------------------------------- --- $Id: DriverState.hs,v 1.46 2001/06/27 16:38:17 simonmar Exp $ +-- $Id: DriverState.hs,v 1.68 2002/02/12 15:17:15 simonmar Exp $ -- -- Settings for the driver -- --- (c) The University of Glasgow 2000 +-- (c) The University of Glasgow 2002 -- ----------------------------------------------------------------------------- @@ -12,7 +12,9 @@ module DriverState where #include "../includes/config.h" #include "HsVersions.h" -import Packages ( PackageConfig(..) ) +import SysTools ( getTopDir ) +import ParsePkgConf ( loadPackageConfig ) +import Packages ( PackageConfig(..), mungePackagePaths ) import CmdLineOpts import DriverPhases import DriverUtil @@ -25,6 +27,7 @@ import Panic import List import Char import Monad +import Directory ( doesDirectoryExist ) ----------------------------------------------------------------------------- -- non-configured things @@ -43,7 +46,22 @@ data GhcMode | DoLink -- [ the default ] deriving (Eq) -GLOBAL_VAR(v_GhcMode, error "mode not set", GhcMode) +GLOBAL_VAR(v_GhcMode, DoLink, GhcMode) +GLOBAL_VAR(v_GhcModeFlag, "", String) + +setMode :: GhcMode -> String -> IO () +setMode m flag = do + old_mode <- readIORef v_GhcMode + old_flag <- readIORef v_GhcModeFlag + when (not (null (old_flag))) $ + throwDyn (UsageError + ("cannot use `" ++ old_flag ++ "' with `" ++ flag ++ "'")) + writeIORef v_GhcMode m + writeIORef v_GhcModeFlag flag + +isCompManagerMode DoMake = True +isCompManagerMode DoInteractive = True +isCompManagerMode _ = False ----------------------------------------------------------------------------- -- Global compilation flags @@ -57,12 +75,17 @@ v_Hs_source_cpp_opts = global ] {-# NOINLINE v_Hs_source_cpp_opts #-} + -- Keep output from intermediate phases GLOBAL_VAR(v_Keep_hi_diffs, False, Bool) GLOBAL_VAR(v_Keep_hc_files, False, Bool) GLOBAL_VAR(v_Keep_s_files, False, Bool) GLOBAL_VAR(v_Keep_raw_s_files, False, Bool) GLOBAL_VAR(v_Keep_tmp_files, False, Bool) +#ifdef ILX +GLOBAL_VAR(v_Keep_il_files, False, Bool) +GLOBAL_VAR(v_Keep_ilx_files, False, Bool) +#endif -- Misc GLOBAL_VAR(v_Scale_sizes_by, 1.0, Double) @@ -72,6 +95,10 @@ GLOBAL_VAR(v_Recomp, True, Bool) GLOBAL_VAR(v_Collect_ghc_timing, False, Bool) GLOBAL_VAR(v_Do_asm_mangling, True, Bool) GLOBAL_VAR(v_Excess_precision, False, Bool) +GLOBAL_VAR(v_Read_DotGHCi, True, Bool) + +-- Preprocessor flags +GLOBAL_VAR(v_Hs_source_pp_opts, [], [String]) ----------------------------------------------------------------------------- -- Splitting object files (for libraries) @@ -130,21 +157,21 @@ osuf_ify f = do GLOBAL_VAR(v_OptLevel, 0, Int) -setOptLevel :: String -> IO () -setOptLevel "" = do { writeIORef v_OptLevel 1 } -setOptLevel "not" = writeIORef v_OptLevel 0 -setOptLevel [c] | isDigit c = do - let level = ord c - ord '0' - writeIORef v_OptLevel level -setOptLevel s = unknownFlagErr ("-O"++s) +setOptLevel :: Int -> IO () +setOptLevel n = do + when (n >= 1) $ setLang HscC -- turn on -fvia-C with -O + writeIORef v_OptLevel n GLOBAL_VAR(v_minus_o2_for_C, False, Bool) GLOBAL_VAR(v_MaxSimplifierIterations, 4, Int) GLOBAL_VAR(v_StgStats, False, Bool) GLOBAL_VAR(v_UsageSPInf, False, Bool) -- Off by default GLOBAL_VAR(v_Strictness, True, Bool) +#ifdef DEBUG GLOBAL_VAR(v_CPR, True, Bool) +#endif GLOBAL_VAR(v_CSE, True, Bool) +GLOBAL_VAR(v_RuleCheck, Nothing, Maybe String) -- these are the static flags you get without -O. hsc_minusNoO_flags = @@ -182,82 +209,97 @@ buildCoreToDo = do max_iter <- readIORef v_MaxSimplifierIterations usageSP <- readIORef v_UsageSPInf strictness <- readIORef v_Strictness +#ifdef DEBUG cpr <- readIORef v_CPR +#endif cse <- readIORef v_CSE + rule_check <- readIORef v_RuleCheck if opt_level == 0 then return [ - CoreDoSimplify (isAmongSimpl [ + CoreDoSimplify (SimplPhase 0) [ MaxSimplifierIterations max_iter - ]) + ] ] else {- opt_level >= 1 -} return [ -- initial simplify: mk specialiser happy: minimum effort please - CoreDoSimplify (isAmongSimpl [ - SimplInlinePhase 0, + CoreDoSimplify SimplGently [ + -- Simplify "gently" -- Don't inline anything till full laziness has bitten -- In particular, inlining wrappers inhibits floating -- e.g. ...(case f x of ...)... -- ==> ...(case (case x of I# x# -> fw x#) of ...)... -- ==> ...(case x of I# x# -> case fw x# of ...)... -- and now the redex (f x) isn't floatable any more - DontApplyRules, -- Similarly, don't apply any rules until after full -- laziness. Notably, list fusion can prevent floating. + NoCaseOfCase, -- Don't do case-of-case transformations. -- This makes full laziness work better MaxSimplifierIterations max_iter - ]), + ], -- Specialisation is best done before full laziness -- so that overloaded functions have all their dictionary lambdas manifest CoreDoSpecialising, - CoreDoFloatOutwards False{-not full-}, + CoreDoFloatOutwards (FloatOutSw False False), CoreDoFloatInwards, - CoreDoSimplify (isAmongSimpl [ - SimplInlinePhase 1, - -- Want to run with inline phase 1 after the specialiser to give + CoreDoSimplify (SimplPhase 2) [ + -- Want to run with inline phase 2 after the specialiser to give -- maximum chance for fusion to work before we inline build/augment - -- in phase 2. This made a difference in 'ansi' where an + -- in phase 1. This made a difference in 'ansi' where an -- overloaded function wasn't inlined till too late. MaxSimplifierIterations max_iter - ]), + ], + case rule_check of { Just pat -> CoreDoRuleCheck 2 pat; Nothing -> CoreDoNothing }, -- infer usage information here in case we need it later. -- (add more of these where you need them --KSW 1999-04) if usageSP then CoreDoUSPInf else CoreDoNothing, - CoreDoSimplify (isAmongSimpl [ + CoreDoSimplify (SimplPhase 1) [ -- Need inline-phase2 here so that build/augment get -- inlined. I found that spectral/hartel/genfft lost some useful -- strictness in the function sumcode' if augment is not inlined -- before strictness analysis runs - SimplInlinePhase 2, MaxSimplifierIterations max_iter - ]), + ], + case rule_check of { Just pat -> CoreDoRuleCheck 1 pat; Nothing -> CoreDoNothing }, - CoreDoSimplify (isAmongSimpl [ - MaxSimplifierIterations 2 - -- No -finline-phase: allow all Ids to be inlined now + CoreDoSimplify (SimplPhase 0) [ + -- Phase 0: allow all Ids to be inlined now -- This gets foldr inlined before strictness analysis - ]), - if strictness then CoreDoStrictness else CoreDoNothing, + MaxSimplifierIterations 3 + -- At least 3 iterations because otherwise we land up with + -- huge dead expressions because of an infelicity in the + -- simpifier. + -- let k = BIG in foldr k z xs + -- ==> let k = BIG in letrec go = \xs -> ...(k x).... in go xs + -- ==> let k = BIG in letrec go = \xs -> ...(BIG x).... in go xs + -- Don't stop now! + + ], + case rule_check of { Just pat -> CoreDoRuleCheck 0 pat; Nothing -> CoreDoNothing }, + +#ifdef DEBUG if cpr then CoreDoCPResult else CoreDoNothing, +#endif + if strictness then CoreDoStrictness else CoreDoNothing, CoreDoWorkerWrapper, CoreDoGlomBinds, - CoreDoSimplify (isAmongSimpl [ + CoreDoSimplify (SimplPhase 0) [ MaxSimplifierIterations max_iter - -- No -finline-phase: allow all Ids to be inlined now - ]), + ], - CoreDoFloatOutwards False{-not full-}, + CoreDoFloatOutwards (FloatOutSw False -- Not lambdas + True), -- Float constants -- nofib/spectral/hartel/wang doubles in speed if you -- do full laziness late in the day. It only happens -- after fusion and other stuff, so the early pass doesn't @@ -265,13 +307,6 @@ buildCoreToDo = do -- f_el22 (f_el21 r_midblock) --- Leave out lambda lifting for now --- "-fsimplify", -- Tidy up results of full laziness --- "[", --- "-fmax-simplifier-iterations2", --- "]", --- "-ffloat-outwards-full", - -- We want CSE to follow the final full-laziness pass, because it may -- succeed in commoning up things floated out by full laziness. -- CSE used to rely on the no-shadowing invariant, but it doesn't any more @@ -283,6 +318,8 @@ buildCoreToDo = do -- Case-liberation for -O2. This should be after -- strictness analysis and the simplification which follows it. + case rule_check of { Just pat -> CoreDoRuleCheck 0 pat; Nothing -> CoreDoNothing }, + if opt_level >= 2 then CoreLiberateCase else @@ -293,10 +330,9 @@ buildCoreToDo = do CoreDoNothing, -- Final clean-up simplification: - CoreDoSimplify (isAmongSimpl [ + CoreDoSimplify (SimplPhase 0) [ MaxSimplifierIterations max_iter - -- No -finline-phase: allow all Ids to be inlined now - ]) + ] ] buildStgToDo :: IO [ StgToDo ] @@ -326,8 +362,69 @@ GLOBAL_VAR(v_Cmdline_libraries, [], [String]) addToDirList :: IORef [String] -> String -> IO () addToDirList ref path - = do paths <- readIORef ref - writeIORef ref (paths ++ split split_marker path) + = do paths <- readIORef ref + shiny_new_ones <- splitUp path + writeIORef ref (paths ++ filter (not.null) shiny_new_ones) + -- empty paths are ignored: there might be a trailing + -- ':' in the initial list, for example. Empty paths can + -- cause confusion when they are translated into -I options + -- for passing to gcc. + where + splitUp ::String -> IO [String] +#ifdef mingw32_TARGET_OS + -- 'hybrid' support for DOS-style paths in directory lists. + -- + -- That is, if "foo:bar:baz" is used, this interpreted as + -- consisting of three entries, 'foo', 'bar', 'baz'. + -- However, with "c:/foo:c:\\foo;x:/bar", this is interpreted + -- as four elts, "c:/foo", "c:\\foo", "x", and "/bar" -- + -- *provided* c:/foo exists and x:/bar doesn't. + -- + -- Notice that no attempt is made to fully replace the 'standard' + -- split marker ':' with the Windows / DOS one, ';'. The reason being + -- that this will cause too much breakage for users & ':' will + -- work fine even with DOS paths, if you're not insisting on being silly. + -- So, use either. + splitUp [] = return [] + splitUp (x:':':div:xs) + | div `elem` dir_markers = do + let (p,rs) = findNextPath xs + ps <- splitUp rs + {- + Consult the file system to check the interpretation + of (x:':':div:p) -- this is arguably excessive, we + could skip this test & just say that it is a valid + dir path. + -} + flg <- doesDirectoryExist (x:':':div:p) + if flg then + return ((x:':':div:p):ps) + else + return ([x]:(div:p):ps) + splitUp xs = do + let (p,rs) = findNextPath xs + ps <- splitUp rs + return (cons p ps) + + cons "" xs = xs + cons x xs = x:xs + + -- will be called either when we've consumed nought or the ":/" part of + -- a DOS path, so splitting is just a Q of finding the next split marker. + findNextPath xs = + case break (`elem` split_markers) xs of + (p, d:ds) -> (p, ds) + (p, xs) -> (p, xs) + + split_markers :: [Char] + split_markers = [':', ';'] + + dir_markers :: [Char] + dir_markers = ['/', '\\'] + +#else + splitUp xs = return (split split_marker xs) +#endif GLOBAL_VAR(v_HCHeader, "", String) @@ -335,7 +432,20 @@ GLOBAL_VAR(v_HCHeader, "", String) -- Packages -- package list is maintained in dependency order -GLOBAL_VAR(v_Packages, ("std":"rts":"gmp":[]), [String]) +GLOBAL_VAR(v_Packages, ("haskell98":"base":"rts":[]), [String]) + +readPackageConf :: String -> IO () +readPackageConf conf_file = do + proto_pkg_details <- loadPackageConfig conf_file + top_dir <- getTopDir + let pkg_details = mungePackagePaths top_dir proto_pkg_details + old_pkg_details <- readIORef v_Package_details + let intersection = filter (`elem` map name old_pkg_details) + (map name pkg_details) + if (not (null intersection)) + then throwDyn (InstallationError ("package `" ++ head intersection ++ "' is already defined")) + else do + writeIORef v_Package_details (pkg_details ++ old_pkg_details) addPackage :: String -> IO () addPackage package @@ -376,8 +486,34 @@ getPackageLibraries = do tag <- readIORef v_Build_tag let suffix = if null tag then "" else '_':tag return (concat ( - map (\p -> map (++suffix) (hs_libraries p) ++ extra_libraries p) ps + map (\p -> map (++suffix) (hACK (hs_libraries p)) ++ extra_libraries p) ps )) + where + -- This is a totally horrible (temporary) hack, for Win32. Problem is + -- that package.conf for Win32 says that the main prelude lib is + -- split into HSbase1 and HSbase2, which is needed due to limitations in + -- the PEi386 file format, to make GHCi work. However, we still only + -- have HSbase.a for static linking, not HSbase1.a and HSbase2.a. + -- getPackageLibraries is called to find the .a's to add to the static + -- link line. On Win32, this hACK detects HSbase1 and HSbase2 and + -- replaces them with HSbase, so static linking still works. + -- Libraries needed for dynamic (GHCi) linking are discovered via + -- different route (in InteractiveUI.linkPackage). + -- See driver/PackageSrc.hs for the HSbase1/HSbase2 split definition. + -- THIS IS A STRICTLY TEMPORARY HACK (famous last words ...) + -- JRS 04 Sept 01: Same appalling hack for HSwin32[1,2] + hACK libs +# ifndef mingw32_TARGET_OS + = libs +# else + = if "HSbase1" `elem` libs && "HSbase2" `elem` libs + then "HSbase" : filter ((/= "HSbase").(take 5)) libs + else + if "HSwin321" `elem` libs && "HSwin322" `elem` libs + then "HSwin32" : filter ((/= "HSwin32").(take 7)) libs + else + libs +# endif getPackageExtraGhcOpts :: IO [String] getPackageExtraGhcOpts = do @@ -404,7 +540,7 @@ getPackageDetails ps = do pkg_details <- readIORef v_Package_details return [ pkg | p <- ps, Just pkg <- [ lookupPkg p pkg_details ] ] -GLOBAL_VAR(v_Package_details, (error "package_details"), [PackageConfig]) +GLOBAL_VAR(v_Package_details, [], [PackageConfig]) lookupPkg :: String -> [PackageConfig] -> Maybe PackageConfig lookupPkg nm ps @@ -437,6 +573,7 @@ data WayName | WayPar | WayGran | WaySMP + | WayNDP | WayDebug | WayUser_a | WayUser_b @@ -462,7 +599,9 @@ GLOBAL_VAR(v_Ways, [] ,[WayName]) allowed_combination way = way `elem` combs where -- the sub-lists must be ordered according to WayName, -- because findBuildTag sorts them - combs = [ [WayProf,WayUnreg], [WayProf,WaySMP] ] + combs = [ [WayProf, WayUnreg], + [WayProf, WaySMP] , + [WayProf, WayNDP] ] findBuildTag :: IO [String] -- new options findBuildTag = do @@ -567,6 +706,10 @@ way_details = , "-optc-DSMP" , "-fvia-C" ]), + (WayNDP, Way "ndp" "Nested data parallelism" + [ "-fparr" + , "-fflatten"]), + (WayUser_a, Way "a" "User way 'a'" ["$WAY_a_REAL_OPTS"]), (WayUser_b, Way "b" "User way 'b'" ["$WAY_b_REAL_OPTS"]), (WayUser_c, Way "c" "User way 'c'" ["$WAY_c_REAL_OPTS"]), @@ -594,7 +737,7 @@ unregFlags = , "-fvia-C" ] ----------------------------------------------------------------------------- --- Programs for particular phases +-- Options for particular phases GLOBAL_VAR(v_Opt_dep, [], [String]) GLOBAL_VAR(v_Anti_opt_C, [], [String])