X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Fmain%2FDriverState.hs;h=4f953eb2612f7c39a76067bf43654ec85c08ad28;hb=153b9cb9b11e05c4edb1b6bc0a7b972660e41f70;hp=b6b527e23e005118918034c557ca42214815e126;hpb=cd20fd58e77d3593cd5870a7345285869b2e32f3;p=ghc-hetmet.git diff --git a/ghc/compiler/main/DriverState.hs b/ghc/compiler/main/DriverState.hs index b6b527e..4f953eb 100644 --- a/ghc/compiler/main/DriverState.hs +++ b/ghc/compiler/main/DriverState.hs @@ -1,5 +1,4 @@ ----------------------------------------------------------------------------- --- $Id: DriverState.hs,v 1.98 2004/02/24 17:33:34 simonmar Exp $ -- -- Settings for the driver -- @@ -9,16 +8,11 @@ module DriverState where -#include "../includes/config.h" #include "HsVersions.h" -import ParsePkgConf ( loadPackageConfig ) -import SysTools ( getTopDir ) -import Packages import CmdLineOpts import DriverPhases import DriverUtil -import UniqFM ( eltsUFM ) import Util import Config import Panic @@ -48,7 +42,7 @@ data GhcMode | DoInteractive -- ghc --interactive | DoLink -- [ the default ] | DoEval String -- ghc -e - deriving (Eq,Show) + deriving (Show) GLOBAL_VAR(v_GhcMode, DoLink, GhcMode) GLOBAL_VAR(v_GhcModeFlag, "", String) @@ -63,21 +57,39 @@ setMode m flag = do writeIORef v_GhcMode m writeIORef v_GhcModeFlag flag +isInteractiveMode, isInterpretiveMode :: GhcMode -> Bool +isMakeMode, isLinkMode, isCompManagerMode :: GhcMode -> Bool + +isInteractiveMode DoInteractive = True +isInteractiveMode _ = False + +-- isInterpretiveMode: byte-code compiler involved +isInterpretiveMode DoInteractive = True +isInterpretiveMode (DoEval _) = True +isInterpretiveMode _ = False + +isMakeMode DoMake = True +isMakeMode _ = False + +isLinkMode DoLink = True +isLinkMode DoMkDLL = True +isLinkMode _ = False + isCompManagerMode DoMake = True isCompManagerMode DoInteractive = True +isCompManagerMode (DoEval _) = True isCompManagerMode _ = False ----------------------------------------------------------------------------- -- Global compilation flags --- Cpp-related flags -v_Hs_source_cpp_opts = global +-- Default CPP defines in Haskell source +hsSourceCppOpts = [ "-D__HASKELL1__="++cHaskell1Version , "-D__GLASGOW_HASKELL__="++cProjectVersionInt , "-D__HASKELL98__" , "-D__CONCURRENT_HASKELL__" ] -{-# NOINLINE v_Hs_source_cpp_opts #-} -- Keep output from intermediate phases @@ -98,7 +110,6 @@ 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) @@ -116,14 +127,19 @@ GLOBAL_VAR(v_Split_info, ("",0), (String,Int)) can_split :: Bool -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 +can_split = +#if defined(i386_TARGET_ARCH) \ + || defined(alpha_TARGET_ARCH) \ + || defined(hppa_TARGET_ARCH) \ + || defined(m68k_TARGET_ARCH) \ + || defined(mips_TARGET_ARCH) \ + || defined(powerpc_TARGET_ARCH) \ + || defined(rs6000_TARGET_ARCH) \ + || defined(sparc_TARGET_ARCH) + True +#else + False +#endif ----------------------------------------------------------------------------- -- Compiler output options @@ -162,8 +178,8 @@ verifyOutputFiles = do 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_Object_suf, phaseInputExt StopLn, String) +GLOBAL_VAR(v_HC_suf, phaseInputExt HCc, String) GLOBAL_VAR(v_Hi_dir, Nothing, Maybe String) GLOBAL_VAR(v_Hi_suf, "hi", String) @@ -201,9 +217,8 @@ buildStgToDo = do split_marker = ':' -- not configurable (ToDo) -v_Import_paths, v_Include_paths, v_Library_paths :: IORef [String] -GLOBAL_VAR(v_Import_paths, ["."], [String]) -GLOBAL_VAR(v_Include_paths, ["."], [String]) +v_Include_paths, v_Library_paths :: IORef [String] +GLOBAL_VAR(v_Include_paths, [], [String]) GLOBAL_VAR(v_Library_paths, [], [String]) #ifdef darwin_TARGET_OS @@ -214,14 +229,17 @@ GLOBAL_VAR(v_Cmdline_frameworks, [], [String]) addToDirList :: IORef [String] -> String -> IO () addToDirList ref path = do paths <- readIORef ref - shiny_new_ones <- splitUp path - writeIORef ref (paths ++ filter notNull shiny_new_ones) + shiny_new_ones <- splitPathList path + writeIORef ref (paths ++ shiny_new_ones) + + +splitPathList :: String -> IO [String] +splitPathList s = do ps <- splitUp s; return (filter notNull ps) -- 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. -- @@ -277,194 +295,6 @@ addToDirList ref path splitUp xs = return (split split_marker xs) #endif --- ---------------------------------------------------------------------------- --- Loading the package config file - -readPackageConf :: String -> IO () -readPackageConf conf_file = do - 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' <- maybePrefixMatch "$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 <- 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 <- 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 :: [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 :: [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 - rts_tag <- readIORef v_RTS_Build_tag - static <- readIORef v_Static - let - imp = if static then "" else "_imp" - libs p = map addSuffix (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 - - suffix = if null tag then "" else '_':tag - rts_suffix = if null rts_tag then "" else '_':rts_tag - - addSuffix rts@"HSrts" = rts ++ rts_suffix - addSuffix other_lib = other_lib ++ suffix - - 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 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 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 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 -# if !defined(mingw32_TARGET_OS) && !defined(cygwin32_TARGET_OS) - = libs -# else - = 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 (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 <- getExplicitAndAutoPackageConfigs - return (concatMap extra_ghc_opts ps) - -getPackageExtraCcOpts :: [PackageName] -> IO [String] -getPackageExtraCcOpts pkgs = do - ps <- getExplicitPackagesAnd pkgs - return (concatMap extra_cc_opts ps) - -#ifdef darwin_TARGET_OS -getPackageFrameworkPath :: [PackageName] -> IO [String] -getPackageFrameworkPath pkgs = do - ps <- getExplicitPackagesAnd pkgs - return (nub (filter notNull (concatMap framework_dirs ps))) - -getPackageFrameworks :: [PackageName] -> IO [String] -getPackageFrameworks pkgs = do - ps <- getExplicitPackagesAnd pkgs - return (concatMap extra_frameworks ps) -#endif - --- ----------------------------------------------------------------------------- --- Package Utils - -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 - --- 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 @@ -521,14 +351,19 @@ GLOBAL_VAR(v_Ways, [] ,[WayName]) allowed_combination way = and [ x `allowedWith` y | x <- way, y <- way, x < y ] where + -- Note ordering in these tests: the left argument is + -- <= the right argument, according to the Ord instance + -- on Way above. + -- debug is allowed with everything _ `allowedWith` WayDebug = True WayDebug `allowedWith` _ = True - WayProf `allowedWith` WayThreaded = True + WayThreaded `allowedWith` WayProf = True WayProf `allowedWith` WayUnreg = True WayProf `allowedWith` WaySMP = True WayProf `allowedWith` WayNDP = True + _ `allowedWith` _ = False findBuildTag :: IO [String] -- new options @@ -540,15 +375,18 @@ findBuildTag = do "combination not supported: " ++ foldr1 (\a b -> a ++ '/':b) (map (wayName . lkupWay) ws)) - else let stuff = map lkupWay ws - tag = concat [ wayTag w | w <- stuff, not (wayRTSOnly w) ] - rts_tag = concat (map wayTag stuff) - flags = map wayOpts stuff + else let ways = map lkupWay ws + tag = mkBuildTag (filter (not.wayRTSOnly) ways) + rts_tag = mkBuildTag ways + flags = map wayOpts ways in do writeIORef v_Build_tag tag writeIORef v_RTS_Build_tag rts_tag return (concat flags) +mkBuildTag :: [Way] -> String +mkBuildTag ways = concat (intersperse "_" (map wayTag ways)) + lkupWay w = case lookup w way_details of Nothing -> error "findBuildTag" @@ -565,7 +403,8 @@ way_details :: [ (WayName, Way) ] way_details = [ (WayThreaded, Way "thr" True "Threaded" [ #if defined(freebsd_TARGET_OS) - , "-optc-pthread" + "-optc-pthread" + , "-optl-pthread" #endif ] ),