X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Fmain%2FDriverState.hs;h=93ac6b72da3276c7f479cf6a36a90c035b8060ab;hb=d28ba8c800901bea01f70c4719278c2a364cf9fc;hp=ca4f05a4fae7c2a9bfdc4bc58a2b90c1444a7f2f;hpb=e0d750bedbd33f7a133c8c82c35fd8db537ab649;p=ghc-hetmet.git diff --git a/ghc/compiler/main/DriverState.hs b/ghc/compiler/main/DriverState.hs index ca4f05a..93ac6b7 100644 --- a/ghc/compiler/main/DriverState.hs +++ b/ghc/compiler/main/DriverState.hs @@ -1,9 +1,9 @@ ----------------------------------------------------------------------------- --- $Id: DriverState.hs,v 1.58 2001/09/26 15:12:34 simonpj Exp $ +-- $Id: DriverState.hs,v 1.92 2003/06/23 10:35:17 simonpj Exp $ -- -- Settings for the driver -- --- (c) The University of Glasgow 2000 +-- (c) The University of Glasgow 2002 -- ----------------------------------------------------------------------------- @@ -12,22 +12,25 @@ module DriverState where #include "../includes/config.h" #include "HsVersions.h" -import SysTools ( getTopDir ) import ParsePkgConf ( loadPackageConfig ) -import Packages ( PackageConfig(..), mungePackagePaths ) +import SysTools ( getTopDir ) +import Packages import CmdLineOpts import DriverPhases import DriverUtil +import UniqFM ( eltsUFM ) import Util import Config -import Exception -import IOExts import Panic +import DATA_IOREF ( IORef, readIORef, writeIORef ) +import EXCEPTION + import List import Char import Monad -import Directory ( doesDirectoryExist ) +import Maybe ( fromJust, isJust ) +import Directory ( doesDirectoryExist ) ----------------------------------------------------------------------------- -- non-configured things @@ -44,9 +47,24 @@ data GhcMode | DoMake -- ghc --make | DoInteractive -- ghc --interactive | DoLink -- [ the default ] - deriving (Eq) + deriving (Eq,Show) + +GLOBAL_VAR(v_GhcMode, DoLink, GhcMode) +GLOBAL_VAR(v_GhcModeFlag, "", String) -GLOBAL_VAR(v_GhcMode, error "mode not set", GhcMode) +setMode :: GhcMode -> String -> IO () +setMode m flag = do + old_mode <- readIORef v_GhcMode + old_flag <- readIORef v_GhcModeFlag + when (notNull old_flag && flag /= 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 @@ -60,23 +78,34 @@ 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) GLOBAL_VAR(v_Static, True, Bool) +GLOBAL_VAR(v_NoLink, False, Bool) GLOBAL_VAR(v_NoHsMain, False, Bool) +GLOBAL_VAR(v_MainModIs, Nothing, Maybe String) +GLOBAL_VAR(v_MainFunIs, Nothing, Maybe String) 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) @@ -98,17 +127,41 @@ can_split = prefixMatch "i386" cTARGETPLATFORM ----------------------------------------------------------------------------- -- Compiler output options -defaultHscLang - | cGhcWithNativeCodeGen == "YES" && - (prefixMatch "i386" cTARGETPLATFORM || - prefixMatch "sparc" cTARGETPLATFORM) = HscAsm - | otherwise = HscC - 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(v_Object_suf, Nothing, Maybe String) +-- called to verify that the output files & directories +-- point somewhere valid. +-- +-- The assumption is that the directory portion of these output +-- options will have to exist by the time 'verifyOutputFiles' +-- is invoked. +-- +verifyOutputFiles :: IO () +verifyOutputFiles = do + odir <- readIORef v_Output_dir + when (isJust odir) $ do + let dir = fromJust odir + flg <- doesDirectoryExist dir + when (not flg) (nonExistentDir "-odir" dir) + ofile <- readIORef v_Output_file + when (isJust ofile) $ do + let fn = fromJust ofile + flg <- doesDirNameExist fn + when (not flg) (nonExistentDir "-o" fn) + ohi <- readIORef v_Output_hi + when (isJust ohi) $ do + let hi = fromJust ohi + flg <- doesDirNameExist hi + when (not flg) (nonExistentDir "-ohi" hi) + where + nonExistentDir flg dir = + throwDyn (CmdLineError ("error: directory portion of " ++ + show dir ++ " does not exist (used with " ++ + show flg ++ " option.)")) + +GLOBAL_VAR(v_Object_suf, phaseInputExt Ln, String) GLOBAL_VAR(v_HC_suf, Nothing, Maybe String) GLOBAL_VAR(v_Hi_dir, Nothing, Maybe String) GLOBAL_VAR(v_Hi_suf, "hi", String) @@ -120,34 +173,27 @@ odir_ify f = do odir_opt <- readIORef v_Output_dir case odir_opt of Nothing -> return f - Just d -> return (newdir d f) + Just d -> return (replaceFilenameDirectory f d) osuf_ify :: String -> IO String osuf_ify f = do - osuf_opt <- readIORef v_Object_suf - case osuf_opt of - Nothing -> return f - Just s -> return (newsuf s f) + osuf <- readIORef v_Object_suf + return (replaceFilenameSuffix f osuf) ----------------------------------------------------------------------------- -- Compiler optimisation options 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) -GLOBAL_VAR(v_CPR, True, Bool) GLOBAL_VAR(v_CSE, True, Bool) GLOBAL_VAR(v_RuleCheck, Nothing, Maybe String) @@ -185,9 +231,7 @@ buildCoreToDo :: IO [CoreToDo] buildCoreToDo = do opt_level <- readIORef v_OptLevel max_iter <- readIORef v_MaxSimplifierIterations - usageSP <- readIORef v_UsageSPInf strictness <- readIORef v_Strictness - cpr <- readIORef v_CPR cse <- readIORef v_CSE rule_check <- readIORef v_RuleCheck @@ -222,7 +266,7 @@ buildCoreToDo = do -- so that overloaded functions have all their dictionary lambdas manifest CoreDoSpecialising, - CoreDoFloatOutwards False{-not full-}, + CoreDoFloatOutwards (FloatOutSw False False), CoreDoFloatInwards, CoreDoSimplify (SimplPhase 2) [ @@ -234,10 +278,6 @@ buildCoreToDo = do ], 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 (SimplPhase 1) [ -- Need inline-phase2 here so that build/augment get -- inlined. I found that spectral/hartel/genfft lost some useful @@ -263,7 +303,9 @@ buildCoreToDo = do ], case rule_check of { Just pat -> CoreDoRuleCheck 0 pat; Nothing -> CoreDoNothing }, - if cpr then CoreDoCPResult else CoreDoNothing, +#ifdef OLD_STRICTNESS + CoreDoOldStrictness +#endif if strictness then CoreDoStrictness else CoreDoNothing, CoreDoWorkerWrapper, CoreDoGlomBinds, @@ -272,7 +314,8 @@ buildCoreToDo = do MaxSimplifierIterations max_iter ], - 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 @@ -280,13 +323,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 @@ -338,14 +374,20 @@ GLOBAL_VAR(v_Import_paths, ["."], [String]) GLOBAL_VAR(v_Include_paths, ["."], [String]) GLOBAL_VAR(v_Library_paths, [], [String]) -GLOBAL_VAR(v_Cmdline_libraries, [], [String]) +#ifdef darwin_TARGET_OS +GLOBAL_VAR(v_Framework_paths, [], [String]) +GLOBAL_VAR(v_Cmdline_frameworks, [], [String]) +#endif addToDirList :: IORef [String] -> String -> IO () addToDirList ref path = do paths <- readIORef ref shiny_new_ones <- splitUp path - writeIORef ref (paths ++ shiny_new_ones) - + writeIORef ref (paths ++ filter notNull 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 @@ -403,127 +445,186 @@ addToDirList ref path splitUp xs = return (split split_marker xs) #endif -GLOBAL_VAR(v_HCHeader, "", String) - ------------------------------------------------------------------------------ --- Packages - --- package list is maintained in dependency order -GLOBAL_VAR(v_Packages, ("std":"rts":"gmp":[]), [String]) +-- ---------------------------------------------------------------------------- +-- Loading the package config file 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) + proto_pkg_configs <- loadPackageConfig conf_file + top_dir <- getTopDir + let pkg_configs = mungePackagePaths top_dir proto_pkg_configs + extendPackageConfigMap pkg_configs + +mungePackagePaths :: String -> [PackageConfig] -> [PackageConfig] +-- Replace the string "$libdir" at the beginning of a path +-- with the current libdir (obtained from the -B option). +mungePackagePaths top_dir ps = map munge_pkg ps + where + munge_pkg p = p{ import_dirs = munge_paths (import_dirs p), + include_dirs = munge_paths (include_dirs p), + library_dirs = munge_paths (library_dirs p), + framework_dirs = munge_paths (framework_dirs p) } + + munge_paths = map munge_path + + munge_path p + | Just p' <- my_prefix_match "$libdir" p = top_dir ++ p' + | otherwise = p + +-- ----------------------------------------------------------------------------- +-- The list of packages requested on the command line + +-- The package list reflects what packages were given as command-line options, +-- plus their dependent packages. It is maintained in dependency order; +-- earlier packages may depend on later ones, but not vice versa +GLOBAL_VAR(v_ExplicitPackages, initPackageList, [PackageName]) + +initPackageList = [basePackage, rtsPackage] + -- basePackage is part of this list entirely because of + -- wired-in names in GHCi. See the notes on wired-in names in + -- Linker.linkExpr. By putting the base backage in initPackageList + -- we make sure that it'll always by linked. + + +-- add a package requested from the command-line addPackage :: String -> IO () -addPackage package - = do pkg_details <- readIORef v_Package_details - case lookupPkg package pkg_details of - Nothing -> throwDyn (CmdLineError ("unknown package name: " ++ package)) - Just details -> do - ps <- readIORef v_Packages - unless (package `elem` ps) $ do - mapM_ addPackage (package_deps details) - ps <- readIORef v_Packages - writeIORef v_Packages (package:ps) - -getPackageImportPath :: IO [String] +addPackage package = do + pkg_details <- getPackageConfigMap + ps <- readIORef v_ExplicitPackages + ps' <- add_package pkg_details ps (mkPackageName package) + -- Throws an exception if it fails + writeIORef v_ExplicitPackages ps' + +-- internal helper +add_package :: PackageConfigMap -> [PackageName] + -> PackageName -> IO [PackageName] +add_package pkg_details ps p + | p `elem` ps -- Check if we've already added this package + = return ps + | Just details <- lookupPkg pkg_details p + -- Add the package's dependents also + = do ps' <- foldM (add_package pkg_details) ps (packageDependents details) + return (p : ps') + | otherwise + = throwDyn (CmdLineError ("unknown package name: " ++ packageNameString p)) + + +-- ----------------------------------------------------------------------------- +-- Extracting information from the packages in scope + +-- Many of these functions take a list of packages: in those cases, +-- the list is expected to contain the "dependent packages", +-- i.e. those packages that were found to be depended on by the +-- current module/program. These can be auto or non-auto packages, it +-- doesn't really matter. The list is always combined with the list +-- of explicit (command-line) packages to determine which packages to +-- use. + +getPackageImportPath :: IO [String] getPackageImportPath = do - ps <- getPackageInfo - return (nub (filter (not.null) (concatMap import_dirs ps))) + ps <- getExplicitAndAutoPackageConfigs + -- import dirs are always derived from the 'auto' + -- packages as well as the explicit ones + return (nub (filter notNull (concatMap import_dirs ps))) -getPackageIncludePath :: IO [String] -getPackageIncludePath = do - ps <- getPackageInfo - return (nub (filter (not.null) (concatMap include_dirs ps))) +getPackageIncludePath :: [PackageName] -> IO [String] +getPackageIncludePath pkgs = do + ps <- getExplicitPackagesAnd pkgs + return (nub (filter notNull (concatMap include_dirs ps))) -- includes are in reverse dependency order (i.e. rts first) -getPackageCIncludes :: IO [String] -getPackageCIncludes = do - ps <- getPackageInfo - return (reverse (nub (filter (not.null) (concatMap c_includes ps)))) - -getPackageLibraryPath :: IO [String] -getPackageLibraryPath = do - ps <- getPackageInfo - return (nub (filter (not.null) (concatMap library_dirs ps))) - -getPackageLibraries :: IO [String] -getPackageLibraries = do - ps <- getPackageInfo +getPackageCIncludes :: [PackageConfig] -> IO [String] +getPackageCIncludes pkg_configs = do + return (reverse (nub (filter notNull (concatMap c_includes pkg_configs)))) + +getPackageLibraryPath :: [PackageName] -> IO [String] +getPackageLibraryPath pkgs = do + ps <- getExplicitPackagesAnd pkgs + return (nub (filter notNull (concatMap library_dirs ps))) + +getPackageLinkOpts :: [PackageName] -> IO [String] +getPackageLinkOpts pkgs = do + ps <- getExplicitPackagesAnd pkgs tag <- readIORef v_Build_tag - let suffix = if null tag then "" else '_':tag - return (concat ( - map (\p -> map (++suffix) (hACK (hs_libraries p)) ++ extra_libraries p) ps - )) + static <- readIORef v_Static + let + imp = if static then "" else "_imp" + suffix = if null tag then "" else '_':tag + libs p = map (++suffix) (hACK (hs_libraries p)) ++ extra_libraries p + imp_libs p = map (++imp) (libs p) + all_opts p = map ("-l" ++) (imp_libs p) ++ extra_ld_opts p + + return (concat (map all_opts 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. + -- split into HSbase1, HSbase2 and HSbase3, which is needed due to a bug + -- in the GNU linker (PEi386 backend). However, we still only + -- have HSbase.a for static linking, not HSbase{1,2,3}.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. + -- link line. On Win32, this hACK detects HSbase{1,2,3} 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 HSstd1/HSstd2 split definition. + -- 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] + -- KAA 29 Mar 02: Same appalling hack for HSobjectio[1,2,3,4] hACK libs -# ifndef mingw32_TARGET_OS +# if !defined(mingw32_TARGET_OS) && !defined(cygwin32_TARGET_OS) = libs # else - = if "HSstd1" `elem` libs && "HSstd2" `elem` libs - then "HSstd" : filter ((/= "HSstd").(take 5)) libs + = if "HSbase1" `elem` libs && "HSbase2" `elem` libs && "HSbase3" `elem` libs + then "HSbase" : filter (not.(isPrefixOf "HSbase")) libs else if "HSwin321" `elem` libs && "HSwin322" `elem` libs - then "HSwin32" : filter ((/= "HSwin32").(take 7)) libs + then "HSwin32" : filter (not.(isPrefixOf "HSwin32")) libs + else + if "HSobjectio1" `elem` libs && "HSobjectio2" `elem` libs && "HSobjectio3" `elem` libs && "HSobjectio4" `elem` libs + then "HSobjectio" : filter (not.(isPrefixOf "HSobjectio")) libs else libs # endif getPackageExtraGhcOpts :: IO [String] getPackageExtraGhcOpts = do - ps <- getPackageInfo + ps <- getExplicitAndAutoPackageConfigs return (concatMap extra_ghc_opts ps) -getPackageExtraCcOpts :: IO [String] -getPackageExtraCcOpts = do - ps <- getPackageInfo +getPackageExtraCcOpts :: [PackageName] -> IO [String] +getPackageExtraCcOpts pkgs = do + ps <- getExplicitPackagesAnd pkgs return (concatMap extra_cc_opts ps) -getPackageExtraLdOpts :: IO [String] -getPackageExtraLdOpts = do - ps <- getPackageInfo - return (concatMap extra_ld_opts ps) +#ifdef darwin_TARGET_OS +getPackageFrameworkPath :: [PackageName] -> IO [String] +getPackageFrameworkPath pkgs = do + ps <- getExplicitPackagesAnd pkgs + return (nub (filter notNull (concatMap framework_dirs ps))) -getPackageInfo :: IO [PackageConfig] -getPackageInfo = do - ps <- readIORef v_Packages - getPackageDetails ps +getPackageFrameworks :: [PackageName] -> IO [String] +getPackageFrameworks pkgs = do + ps <- getExplicitPackagesAnd pkgs + return (concatMap extra_frameworks ps) +#endif -getPackageDetails :: [String] -> IO [PackageConfig] -getPackageDetails ps = do - pkg_details <- readIORef v_Package_details - return [ pkg | p <- ps, Just pkg <- [ lookupPkg p pkg_details ] ] +-- ----------------------------------------------------------------------------- +-- Package Utils -GLOBAL_VAR(v_Package_details, [], [PackageConfig]) +getExplicitPackagesAnd :: [PackageName] -> IO [PackageConfig] +getExplicitPackagesAnd pkg_names = do + pkg_map <- getPackageConfigMap + expl <- readIORef v_ExplicitPackages + all_pkgs <- foldM (add_package pkg_map) expl pkg_names + getPackageDetails all_pkgs -lookupPkg :: String -> [PackageConfig] -> Maybe PackageConfig -lookupPkg nm ps - = case [p | p <- ps, name p == nm] of - [] -> Nothing - (p:_) -> Just p +-- return all packages, including both the auto packages and the explicit ones +getExplicitAndAutoPackageConfigs :: IO [PackageConfig] +getExplicitAndAutoPackageConfigs = do + pkg_map <- getPackageConfigMap + let auto_packages = [ mkPackageName (name p) | p <- eltsUFM pkg_map, auto p ] + getExplicitPackagesAnd auto_packages ----------------------------------------------------------------------------- -- Ways @@ -550,6 +651,7 @@ data WayName | WayPar | WayGran | WaySMP + | WayNDP | WayDebug | WayUser_a | WayUser_b @@ -575,7 +677,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 @@ -680,6 +784,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"]),