X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Fmain%2FDriverState.hs;h=39934b99a552211020ea102aa63833041b3e44f2;hb=10fcd78ccde892feccda3f5eacd221c1de75feea;hp=e789e5ec25d414302fe9e2e9b5ede2421ccaf9d0;hpb=1211c4e59dd9c4f5e7b027649a1e3c6eb459f5e1;p=ghc-hetmet.git diff --git a/ghc/compiler/main/DriverState.hs b/ghc/compiler/main/DriverState.hs index e789e5e..39934b9 100644 --- a/ghc/compiler/main/DriverState.hs +++ b/ghc/compiler/main/DriverState.hs @@ -1,90 +1,33 @@ ----------------------------------------------------------------------------- --- $Id: DriverState.hs,v 1.3 2000/10/11 15:26:18 simonmar Exp $ +-- $Id: DriverState.hs,v 1.67 2002/02/11 08:20:41 chak Exp $ -- -- Settings for the driver -- --- (c) The University of Glasgow 2000 +-- (c) The University of Glasgow 2002 -- ----------------------------------------------------------------------------- module DriverState where +#include "../includes/config.h" #include "HsVersions.h" -import CmStaticInfo +import SysTools ( getTopDir ) +import ParsePkgConf ( loadPackageConfig ) +import Packages ( PackageConfig(..), mungePackagePaths ) import CmdLineOpts +import DriverPhases import DriverUtil import Util import Config -import Array - import Exception import IOExts +import Panic -import System -import IO import List import Char import Monad - ------------------------------------------------------------------------------ --- Driver state - --- certain flags can be specified on a per-file basis, in an OPTIONS --- pragma at the beginning of the source file. This means that when --- compiling mulitple files, we have to restore the global option --- settings before compiling a new file. --- --- The DriverState record contains the per-file-mutable state. - -data DriverState = DriverState { - - -- are we runing cpp on this file? - cpp_flag :: Bool, - - -- misc - stolen_x86_regs :: Int, - cmdline_hc_includes :: [String], - - -- options for a particular phase - opt_L :: [String], - opt_P :: [String], - opt_c :: [String], - opt_a :: [String], - opt_m :: [String] - } - -initDriverState = DriverState { - cpp_flag = False, - stolen_x86_regs = 4, - cmdline_hc_includes = [], - opt_L = [], - opt_P = [], - opt_c = [], - opt_a = [], - opt_m = [], - } - -GLOBAL_VAR(driver_state, initDriverState, DriverState) - -readState :: (DriverState -> a) -> IO a -readState f = readIORef driver_state >>= return . f - -updateState :: (DriverState -> DriverState) -> IO () -updateState f = readIORef driver_state >>= writeIORef driver_state . f - -addOpt_L a = updateState (\s -> s{opt_L = a : opt_L s}) -addOpt_P a = updateState (\s -> s{opt_P = a : opt_P s}) -addOpt_c a = updateState (\s -> s{opt_c = a : opt_c s}) -addOpt_a a = updateState (\s -> s{opt_a = a : opt_a s}) -addOpt_m a = updateState (\s -> s{opt_m = a : opt_m s}) - -addCmdlineHCInclude a = - updateState (\s -> s{cmdline_hc_includes = a : cmdline_hc_includes s}) - - -- we add to the options from the front, so we need to reverse the list -getOpts :: (DriverState -> [a]) -> IO [a] -getOpts opts = readState opts >>= return . reverse +import Directory ( doesDirectoryExist ) ----------------------------------------------------------------------------- -- non-configured things @@ -92,290 +35,282 @@ getOpts opts = readState opts >>= return . reverse cHaskell1Version = "5" -- i.e., Haskell 98 ----------------------------------------------------------------------------- --- Global compilation flags +-- GHC modes of operation + +data GhcMode + = DoMkDependHS -- ghc -M + | DoMkDLL -- ghc --mk-dll + | StopBefore Phase -- ghc -E | -C | -S | -c + | DoMake -- ghc --make + | DoInteractive -- ghc --interactive + | DoLink -- [ the default ] + deriving (Eq) + +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 --- location of compiler-related files -GLOBAL_VAR(topDir, clibdir, String) -GLOBAL_VAR(inplace, False, Bool) +----------------------------------------------------------------------------- +-- Global compilation flags -- Cpp-related flags -hs_source_cpp_opts = global +v_Hs_source_cpp_opts = global [ "-D__HASKELL1__="++cHaskell1Version , "-D__GLASGOW_HASKELL__="++cProjectVersionInt , "-D__HASKELL98__" , "-D__CONCURRENT_HASKELL__" ] +{-# NOINLINE v_Hs_source_cpp_opts #-} --- Verbose -GLOBAL_VAR(verbose, False, Bool) -is_verbose = do v <- readIORef verbose; if v then return "-v" else return "" - --- where to keep temporary files -GLOBAL_VAR(v_TmpDir, cDEFAULT_TMPDIR, String ) -- Keep output from intermediate phases -GLOBAL_VAR(keep_hi_diffs, False, Bool) -GLOBAL_VAR(keep_hc_files, False, Bool) -GLOBAL_VAR(keep_s_files, False, Bool) -GLOBAL_VAR(keep_raw_s_files, False, Bool) -GLOBAL_VAR(keep_tmp_files, False, Bool) +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(scale_sizes_by, 1.0, Double) -GLOBAL_VAR(dry_run, False, Bool) -#if !defined(HAVE_WIN32_DLL_SUPPORT) || defined(DONT_WANT_WIN32_DLL_SUPPORT) -GLOBAL_VAR(static, True, Bool) -#else -GLOBAL_VAR(static, False, Bool) -#endif -GLOBAL_VAR(recomp, True, Bool) -GLOBAL_VAR(collect_ghc_timing, False, Bool) -GLOBAL_VAR(do_asm_mangling, True, Bool) -GLOBAL_VAR(excess_precision, False, Bool) +GLOBAL_VAR(v_Scale_sizes_by, 1.0, Double) +GLOBAL_VAR(v_Static, True, Bool) +GLOBAL_VAR(v_NoHsMain, False, Bool) +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) -GLOBAL_VAR(split_object_files, False, Bool) -GLOBAL_VAR(split_prefix, "", String) -GLOBAL_VAR(n_split_files, 0, Int) +GLOBAL_VAR(v_Split_object_files, False, Bool) +GLOBAL_VAR(v_Split_info, ("",0), (String,Int)) + -- The split prefix and number of files + can_split :: Bool -can_split = prefixMatch "i386" cTARGETPLATFORM - || prefixMatch "alpha" cTARGETPLATFORM - || prefixMatch "hppa" cTARGETPLATFORM - || prefixMatch "m68k" cTARGETPLATFORM - || prefixMatch "mips" cTARGETPLATFORM +can_split = prefixMatch "i386" cTARGETPLATFORM + || prefixMatch "alpha" cTARGETPLATFORM + || prefixMatch "hppa" cTARGETPLATFORM + || prefixMatch "m68k" cTARGETPLATFORM + || prefixMatch "mips" cTARGETPLATFORM || prefixMatch "powerpc" cTARGETPLATFORM - || prefixMatch "rs6000" cTARGETPLATFORM - || prefixMatch "sparc" cTARGETPLATFORM + || prefixMatch "rs6000" cTARGETPLATFORM + || prefixMatch "sparc" cTARGETPLATFORM ----------------------------------------------------------------------------- -- Compiler output options -GLOBAL_VAR(hsc_lang, if cGhcWithNativeCodeGen == "YES" && - (prefixMatch "i386" cTARGETPLATFORM || - prefixMatch "sparc" cTARGETPLATFORM) - then HscAsm - else HscC, - HscLang) +defaultHscLang + | cGhcWithNativeCodeGen == "YES" && + (prefixMatch "i386" cTARGETPLATFORM || + prefixMatch "sparc" cTARGETPLATFORM) = HscAsm + | otherwise = HscC -GLOBAL_VAR(output_dir, Nothing, Maybe String) -GLOBAL_VAR(output_suf, Nothing, Maybe String) -GLOBAL_VAR(output_file, Nothing, Maybe String) -GLOBAL_VAR(output_hi, Nothing, Maybe String) +GLOBAL_VAR(v_Output_dir, Nothing, Maybe String) +GLOBAL_VAR(v_Output_file, Nothing, Maybe String) +GLOBAL_VAR(v_Output_hi, Nothing, Maybe String) -GLOBAL_VAR(ld_inputs, [], [String]) +GLOBAL_VAR(v_Object_suf, Nothing, Maybe String) +GLOBAL_VAR(v_HC_suf, Nothing, Maybe String) +GLOBAL_VAR(v_Hi_dir, Nothing, Maybe String) +GLOBAL_VAR(v_Hi_suf, "hi", String) + +GLOBAL_VAR(v_Ld_inputs, [], [String]) odir_ify :: String -> IO String odir_ify f = do - odir_opt <- readIORef output_dir + odir_opt <- readIORef v_Output_dir case odir_opt of Nothing -> return f Just d -> return (newdir d f) osuf_ify :: String -> IO String osuf_ify f = do - osuf_opt <- readIORef output_suf + osuf_opt <- readIORef v_Object_suf case osuf_opt of Nothing -> return f Just s -> return (newsuf s f) ----------------------------------------------------------------------------- --- Hi Files - -GLOBAL_VAR(produceHi, True, Bool) -GLOBAL_VAR(hi_on_stdout, False, Bool) -GLOBAL_VAR(hi_suf, "hi", String) - ------------------------------------------------------------------------------ --- Warnings & sanity checking - --- Warning packages that are controlled by -W and -Wall. The 'standard' --- warnings that you get all the time are --- --- -fwarn-overlapping-patterns --- -fwarn-missing-methods --- -fwarn-missing-fields --- -fwarn-deprecations --- -fwarn-duplicate-exports --- --- these are turned off by -Wnot. - - -standardWarnings = [ "-fwarn-overlapping-patterns" - , "-fwarn-missing-methods" - , "-fwarn-missing-fields" - , "-fwarn-deprecations" - , "-fwarn-duplicate-exports" - ] -minusWOpts = standardWarnings ++ - [ "-fwarn-unused-binds" - , "-fwarn-unused-matches" - , "-fwarn-incomplete-patterns" - , "-fwarn-unused-imports" - ] -minusWallOpts = minusWOpts ++ - [ "-fwarn-type-defaults" - , "-fwarn-name-shadowing" - , "-fwarn-missing-signatures" - , "-fwarn-hi-shadowing" - ] - -data WarningState = W_default | W_ | W_all | W_not -GLOBAL_VAR(warning_opt, W_default, WarningState) - ------------------------------------------------------------------------------ -- Compiler optimisation options -GLOBAL_VAR(opt_level, 0, Int) - -setOptLevel :: String -> IO () -setOptLevel "" = do { writeIORef opt_level 1; go_via_C } -setOptLevel "not" = writeIORef opt_level 0 -setOptLevel [c] | isDigit c = do - let level = ord c - ord '0' - writeIORef opt_level level - when (level >= 1) go_via_C -setOptLevel s = unknownFlagErr ("-O"++s) - -go_via_C = do - l <- readIORef hsc_lang - case l of { HscAsm -> writeIORef hsc_lang HscC; - _other -> return () } +GLOBAL_VAR(v_OptLevel, 0, Int) -GLOBAL_VAR(opt_minus_o2_for_C, False, Bool) +setOptLevel :: Int -> IO () +setOptLevel n = do + when (n >= 1) $ setLang HscC -- turn on -fvia-C with -O + writeIORef v_OptLevel n -GLOBAL_VAR(opt_MaxSimplifierIterations, 4, Int) -GLOBAL_VAR(opt_StgStats, False, Bool) -GLOBAL_VAR(opt_UsageSPInf, False, Bool) -- Off by default -GLOBAL_VAR(opt_Strictness, True, Bool) -GLOBAL_VAR(opt_CPR, True, Bool) - -hsc_minusO2_flags = hsc_minusO_flags -- for now +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) -hsc_minusNoO_flags = do - iter <- readIORef opt_MaxSimplifierIterations - return [ +-- these are the static flags you get without -O. +hsc_minusNoO_flags = + [ "-fignore-interface-pragmas", - "-fomit-interface-pragmas" + "-fomit-interface-pragmas", + "-fdo-lambda-eta-expansion", -- This one is important for a tiresome reason: + -- we want to make sure that the bindings for data + -- constructors are eta-expanded. This is probably + -- a good thing anyway, but it seems fragile. + "-flet-no-escape" ] -hsc_minusO_flags = do - stgstats <- readIORef opt_StgStats - - return [ +-- these are the static flags you get when -O is on. +hsc_minusO_flags = + [ + "-fignore-asserts", "-ffoldr-build-on", "-fdo-eta-reduction", "-fdo-lambda-eta-expansion", - "-fcase-of-case", "-fcase-merge", - "-flet-to-case" + "-flet-to-case", + "-flet-no-escape" ] -build_CoreToDo - :: Int -- opt level - -> Int -- max iterations - -> Bool -- do usageSP - -> Bool -- do strictness - -> Bool -- do CPR - -> Bool -- do CSE - -> [CoreToDo] - -build_CoreToDo level max_iter usageSP strictness cpr cse - | level == 0 = [ - CoreDoSimplify (isAmongSimpl [ +hsc_minusO2_flags = hsc_minusO_flags -- for now + +getStaticOptimisationFlags 0 = hsc_minusNoO_flags +getStaticOptimisationFlags 1 = hsc_minusO_flags +getStaticOptimisationFlags n = hsc_minusO2_flags + +buildCoreToDo :: IO [CoreToDo] +buildCoreToDo = do + opt_level <- readIORef v_OptLevel + 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 (SimplPhase 0) [ MaxSimplifierIterations max_iter - ]) + ] ] - | level >= 1 = [ + 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 -- catch it. For the record, the redex is -- 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 must immediately follow a simplification pass, because it relies - -- on the no-shadowing invariant. See comments at the top of CSE.lhs - -- So it must NOT follow float-inwards, which can give rise to shadowing, - -- even if its input doesn't have shadows. Hence putting it between - -- the two passes. + -- CSE used to rely on the no-shadowing invariant, but it doesn't any more + if cse then CoreCSE else CoreDoNothing, CoreDoFloatInwards, @@ -383,123 +318,236 @@ build_CoreToDo level max_iter usageSP strictness cpr cse -- Case-liberation for -O2. This should be after -- strictness analysis and the simplification which follows it. --- ( ($OptLevel != 2) --- ? "" --- : "-fliberate-case -fsimplify [ $Oopt_FB_Support -ffloat-lets-exposing-whnf -ffloat-primops-ok -fcase-of-case -fdo-case-elim -fcase-merge -fdo-lambda-eta-expansion -freuse-con -flet-to-case $Oopt_PedanticBottoms $Oopt_MaxSimplifierIterations $Oopt_ShowSimplifierProgress ]" ), --- --- "-fliberate-case", + case rule_check of { Just pat -> CoreDoRuleCheck 0 pat; Nothing -> CoreDoNothing }, + + if opt_level >= 2 then + CoreLiberateCase + else + CoreDoNothing, + if opt_level >= 2 then + CoreDoSpecConstr + else + 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 ] +buildStgToDo = do + stg_stats <- readIORef v_StgStats + let flags1 | stg_stats = [ D_stg_stats ] + | otherwise = [ ] + + -- STG passes + ways_ <- readIORef v_Ways + let flags2 | WayProf `elem` ways_ = StgDoMassageForProfiling : flags1 + | otherwise = flags1 + + return flags2 ----------------------------------------------------------------------------- -- Paths & Libraries split_marker = ':' -- not configurable (ToDo) -import_paths, include_paths, library_paths :: IORef [String] -GLOBAL_VAR(import_paths, ["."], [String]) -GLOBAL_VAR(include_paths, ["."], [String]) -GLOBAL_VAR(library_paths, [], [String]) +v_Import_paths, v_Include_paths, v_Library_paths :: IORef [String] +GLOBAL_VAR(v_Import_paths, ["."], [String]) +GLOBAL_VAR(v_Include_paths, ["."], [String]) +GLOBAL_VAR(v_Library_paths, [], [String]) -GLOBAL_VAR(cmdline_libraries, [], [String]) +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) ----------------------------------------------------------------------------- -- Packages -GLOBAL_VAR(path_package_config, error "path_package_config", String) - -- package list is maintained in dependency order -packages = global ["std", "rts", "gmp"] :: IORef [String] --- comma in value, so can't use macro, grrr -{-# NOINLINE packages #-} +GLOBAL_VAR(v_Packages, ("std":"rts":"gmp":[]), [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 - = do pkg_details <- readIORef package_details + = do pkg_details <- readIORef v_Package_details case lookupPkg package pkg_details of - Nothing -> throwDyn (OtherError ("unknown package name: " ++ package)) + Nothing -> throwDyn (CmdLineError ("unknown package name: " ++ package)) Just details -> do - ps <- readIORef packages + ps <- readIORef v_Packages unless (package `elem` ps) $ do mapM_ addPackage (package_deps details) - ps <- readIORef packages - writeIORef packages (package:ps) + ps <- readIORef v_Packages + writeIORef v_Packages (package:ps) getPackageImportPath :: IO [String] getPackageImportPath = do - ps <- readIORef packages - ps' <- getPackageDetails ps - return (nub (concat (map import_dirs ps'))) + ps <- getPackageInfo + return (nub (filter (not.null) (concatMap import_dirs ps))) getPackageIncludePath :: IO [String] getPackageIncludePath = do - ps <- readIORef packages - ps' <- getPackageDetails ps - return (nub (filter (not.null) (concatMap include_dirs ps'))) + ps <- getPackageInfo + return (nub (filter (not.null) (concatMap include_dirs ps))) -- includes are in reverse dependency order (i.e. rts first) getPackageCIncludes :: IO [String] getPackageCIncludes = do - ps <- readIORef packages - ps' <- getPackageDetails ps - return (reverse (nub (filter (not.null) (concatMap c_includes ps')))) + ps <- getPackageInfo + return (reverse (nub (filter (not.null) (concatMap c_includes ps)))) getPackageLibraryPath :: IO [String] getPackageLibraryPath = do - ps <- readIORef packages - ps' <- getPackageDetails ps - return (nub (concat (map library_dirs ps'))) + ps <- getPackageInfo + return (nub (filter (not.null) (concatMap library_dirs ps))) getPackageLibraries :: IO [String] getPackageLibraries = do - ps <- readIORef packages - ps' <- getPackageDetails ps - tag <- readIORef build_tag + ps <- getPackageInfo + 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 HSstd1 and HSstd2, which is needed due to limitations in + -- the PEi386 file format, to make GHCi work. However, we still only + -- have HSstd.a for static linking, not HSstd1.a and HSstd2.a. + -- getPackageLibraries is called to find the .a's to add to the static + -- link line. On Win32, this hACK detects HSstd1 and HSstd2 and + -- replaces them with HSstd, 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 HSstd1/HSstd2 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 "HSstd1" `elem` libs && "HSstd2" `elem` libs + then "HSstd" : filter ((/= "HSstd").(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 - ps <- readIORef packages - ps' <- getPackageDetails ps - return (concatMap extra_ghc_opts ps') + ps <- getPackageInfo + return (concatMap extra_ghc_opts ps) getPackageExtraCcOpts :: IO [String] getPackageExtraCcOpts = do - ps <- readIORef packages - ps' <- getPackageDetails ps - return (concatMap extra_cc_opts ps') + ps <- getPackageInfo + return (concatMap extra_cc_opts ps) getPackageExtraLdOpts :: IO [String] getPackageExtraLdOpts = do - ps <- readIORef packages - ps' <- getPackageDetails ps - return (concatMap extra_ld_opts ps') + ps <- getPackageInfo + return (concatMap extra_ld_opts ps) + +getPackageInfo :: IO [PackageConfig] +getPackageInfo = do + ps <- readIORef v_Packages + getPackageDetails ps -getPackageDetails :: [String] -> IO [Package] +getPackageDetails :: [String] -> IO [PackageConfig] getPackageDetails ps = do - pkg_details <- readIORef package_details + pkg_details <- readIORef v_Package_details return [ pkg | p <- ps, Just pkg <- [ lookupPkg p pkg_details ] ] -GLOBAL_VAR(package_details, (error "package_details"), [Package]) +GLOBAL_VAR(v_Package_details, [], [PackageConfig]) -lookupPkg :: String -> [Package] -> Maybe Package +lookupPkg :: String -> [PackageConfig] -> Maybe PackageConfig lookupPkg nm ps = case [p | p <- ps, name p == nm] of [] -> Nothing (p:_) -> Just p + ----------------------------------------------------------------------------- -- Ways @@ -516,16 +564,16 @@ lookupPkg nm ps -- becomes the suffix used to find .hi files and libraries used in -- this compilation. -GLOBAL_VAR(build_tag, "", String) +GLOBAL_VAR(v_Build_tag, "", String) data WayName = WayProf | WayUnreg - | WayDll | WayTicky | WayPar | WayGran | WaySMP + | WayNDP | WayDebug | WayUser_a | WayUser_b @@ -546,28 +594,28 @@ data WayName | WayUser_B deriving (Eq,Ord) -GLOBAL_VAR(ways, [] ,[WayName]) - --- ToDo: allow WayDll with any other allowed combination +GLOBAL_VAR(v_Ways, [] ,[WayName]) -allowed_combinations = - [ [WayProf,WayUnreg], - [WayProf,WaySMP] -- works??? - ] +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] , + [WayProf, WayNDP] ] findBuildTag :: IO [String] -- new options findBuildTag = do - way_names <- readIORef ways + way_names <- readIORef v_Ways case sort way_names of - [] -> do writeIORef build_tag "" + [] -> do -- writeIORef v_Build_tag "" return [] [w] -> do let details = lkupWay w - writeIORef build_tag (wayTag details) + writeIORef v_Build_tag (wayTag details) return (wayOpts details) - ws -> if ws `notElem` allowed_combinations - then throwDyn (OtherError $ + ws -> if not (allowed_combination ws) + then throwDyn (CmdLineError $ "combination not supported: " ++ foldr1 (\a b -> a ++ '/':b) (map (wayName . lkupWay) ws)) @@ -575,7 +623,7 @@ findBuildTag = do tag = concat (map wayTag stuff) flags = map wayOpts stuff in do - writeIORef build_tag tag + writeIORef v_Build_tag tag return (concat flags) lkupWay w = @@ -604,23 +652,47 @@ way_details = , "-fvia-C" ]), (WayUnreg, Way "u" "Unregisterised" - [ "-optc-DNO_REGS" - , "-optc-DUSE_MINIINTERPRETER" - , "-fno-asm-mangling" - , "-funregisterised" + unregFlags ), + + -- optl's below to tell linker where to find the PVM library -- HWL + (WayPar, Way "mp" "Parallel" + [ "-fparallel" + , "-D__PARALLEL_HASKELL__" + , "-optc-DPAR" + , "-package concurrent" + , "-optc-w" + , "-optl-L${PVM_ROOT}/lib/${PVM_ARCH}" + , "-optl-lpvm3" + , "-optl-lgpvm3" , "-fvia-C" ]), - (WayDll, Way "dll" "DLLized" - [ ]), + -- at the moment we only change the RTS and could share compiler and libs! + (WayPar, Way "mt" "Parallel ticky profiling" + [ "-fparallel" + , "-D__PARALLEL_HASKELL__" + , "-optc-DPAR" + , "-optc-DPAR_TICKY" + , "-package concurrent" + , "-optc-w" + , "-optl-L${PVM_ROOT}/lib/${PVM_ARCH}" + , "-optl-lpvm3" + , "-optl-lgpvm3" + , "-fvia-C" ]), - (WayPar, Way "mp" "Parallel" + (WayPar, Way "md" "Distributed" [ "-fparallel" , "-D__PARALLEL_HASKELL__" + , "-D__DISTRIBUTED_HASKELL__" , "-optc-DPAR" + , "-optc-DDIST" , "-package concurrent" + , "-optc-w" + , "-optl-L${PVM_ROOT}/lib/${PVM_ARCH}" + , "-optl-lpvm3" + , "-optl-lgpvm3" , "-fvia-C" ]), - (WayGran, Way "mg" "Gransim" + (WayGran, Way "mg" "GranSim" [ "-fgransim" , "-D__GRANSIM__" , "-optc-DGRAN" @@ -634,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"]), @@ -653,109 +729,21 @@ way_details = (WayUser_B, Way "B" "User way 'B'" ["$WAY_B_REAL_OPTS"]) ] ------------------------------------------------------------------------------ --- Programs for particular phases - -GLOBAL_VAR(pgm_L, error "pgm_L", String) -GLOBAL_VAR(pgm_P, cRAWCPP, String) -GLOBAL_VAR(pgm_C, error "pgm_L", String) -GLOBAL_VAR(pgm_c, cGCC, String) -GLOBAL_VAR(pgm_m, error "pgm_m", String) -GLOBAL_VAR(pgm_s, error "pgm_s", String) -GLOBAL_VAR(pgm_a, cGCC, String) -GLOBAL_VAR(pgm_l, cGCC, String) - -GLOBAL_VAR(opt_dep, [], [String]) -GLOBAL_VAR(anti_opt_C, [], [String]) -GLOBAL_VAR(opt_C, [], [String]) -GLOBAL_VAR(opt_l, [], [String]) -GLOBAL_VAR(opt_dll, [], [String]) - -getStaticOpts :: IORef [String] -> IO [String] -getStaticOpts ref = readIORef ref >>= return . reverse - ------------------------------------------------------------------------------ --- Via-C compilation stuff - --- flags returned are: ( all C compilations --- , registerised HC compilations --- ) - -machdepCCOpts - | prefixMatch "alpha" cTARGETPLATFORM - = return ( ["-static"], [] ) - - | prefixMatch "hppa" cTARGETPLATFORM - -- ___HPUX_SOURCE, not _HPUX_SOURCE, is #defined if -ansi! - -- (very nice, but too bad the HP /usr/include files don't agree.) - = return ( ["-static", "-D_HPUX_SOURCE"], [] ) - - | prefixMatch "m68k" cTARGETPLATFORM - -- -fno-defer-pop : for the .hc files, we want all the pushing/ - -- popping of args to routines to be explicit; if we let things - -- be deferred 'til after an STGJUMP, imminent death is certain! - -- - -- -fomit-frame-pointer : *don't* - -- It's better to have a6 completely tied up being a frame pointer - -- rather than let GCC pick random things to do with it. - -- (If we want to steal a6, then we would try to do things - -- as on iX86, where we *do* steal the frame pointer [%ebp].) - = return ( [], ["-fno-defer-pop", "-fno-omit-frame-pointer"] ) - - | prefixMatch "i386" cTARGETPLATFORM - -- -fno-defer-pop : basically the same game as for m68k - -- - -- -fomit-frame-pointer : *must* in .hc files; because we're stealing - -- the fp (%ebp) for our register maps. - = do n_regs <- readState stolen_x86_regs - sta <- readIORef static - return ( [ if sta then "-DDONT_WANT_WIN32_DLL_SUPPORT" else "" ], - [ "-fno-defer-pop", "-fomit-frame-pointer", - "-DSTOLEN_X86_REGS="++show n_regs ] - ) - - | prefixMatch "mips" cTARGETPLATFORM - = return ( ["static"], [] ) - - | prefixMatch "powerpc" cTARGETPLATFORM || prefixMatch "rs6000" cTARGETPLATFORM - = return ( ["static"], ["-finhibit-size-directive"] ) - - | otherwise - = return ( [], [] ) - +unregFlags = + [ "-optc-DNO_REGS" + , "-optc-DUSE_MINIINTERPRETER" + , "-fno-asm-mangling" + , "-funregisterised" + , "-fvia-C" ] ----------------------------------------------------------------------------- --- Running an external program - -run_something phase_name cmd - = do - verb <- readIORef verbose - when verb $ do - putStr phase_name - putStrLn ":" - putStrLn cmd - hFlush stdout - - -- test for -n flag - n <- readIORef dry_run - unless n $ do - - -- and run it! -#ifndef mingw32_TARGET_OS - exit_code <- system cmd `catchAllIO` - (\_ -> throwDyn (PhaseFailed phase_name (ExitFailure 1))) -#else - tmp <- newTempName "sh" - h <- openFile tmp WriteMode - hPutStrLn h cmd - hClose h - exit_code <- system ("sh - " ++ tmp) `catchAllIO` - (\e -> throwDyn (PhaseFailed phase_name (ExitFailure 1))) - removeFile tmp -#endif +-- Options for particular phases - if exit_code /= ExitSuccess - then throwDyn (PhaseFailed phase_name exit_code) - else do when verb (putStr "\n") - return () +GLOBAL_VAR(v_Opt_dep, [], [String]) +GLOBAL_VAR(v_Anti_opt_C, [], [String]) +GLOBAL_VAR(v_Opt_C, [], [String]) +GLOBAL_VAR(v_Opt_l, [], [String]) +GLOBAL_VAR(v_Opt_dll, [], [String]) +getStaticOpts :: IORef [String] -> IO [String] +getStaticOpts ref = readIORef ref >>= return . reverse