X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Fmain%2FDriverState.hs;h=a3defcb68217a7bd0cc4adad04b0379ee12b1c5e;hb=b768e242a4934facfd73f24dacd7ef854f85211d;hp=01b03e890afc2b380f2f6e766597e1a0b0fc9903;hpb=2dbdd850a75eba264f1f362fd80aac3527ce141e;p=ghc-hetmet.git diff --git a/ghc/compiler/main/DriverState.hs b/ghc/compiler/main/DriverState.hs index 01b03e8..a3defcb 100644 --- a/ghc/compiler/main/DriverState.hs +++ b/ghc/compiler/main/DriverState.hs @@ -1,5 +1,5 @@ ----------------------------------------------------------------------------- --- $Id: DriverState.hs,v 1.73 2002/03/29 20:14:31 krasimir Exp $ +-- $Id: DriverState.hs,v 1.85 2002/10/25 16:54:58 simonpj Exp $ -- -- Settings for the driver -- @@ -14,19 +14,25 @@ module DriverState where import SysTools ( getTopDir ) import ParsePkgConf ( loadPackageConfig ) -import Packages ( PackageConfig(..), mungePackagePaths ) +import Packages ( PackageConfig(..), PackageConfigMap, + PackageName, mkPackageName, packageNameString, + packageDependents, + mungePackagePaths, emptyPkgMap, extendPkgMap, lookupPkg, + basePackage, rtsPackage, haskell98Package ) import CmdLineOpts import DriverPhases import DriverUtil 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 Maybe ( fromJust, isJust ) import Directory ( doesDirectoryExist ) ----------------------------------------------------------------------------- @@ -44,7 +50,7 @@ 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) @@ -53,7 +59,7 @@ setMode :: GhcMode -> String -> IO () setMode m flag = do old_mode <- readIORef v_GhcMode old_flag <- readIORef v_GhcModeFlag - when (not (null (old_flag))) $ + when (notNull old_flag && flag /= old_flag) $ throwDyn (UsageError ("cannot use `" ++ old_flag ++ "' with `" ++ flag ++ "'")) writeIORef v_GhcMode m @@ -125,7 +131,37 @@ 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) @@ -137,14 +173,12 @@ 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 @@ -161,9 +195,6 @@ 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 OLD_STRICTNESS -GLOBAL_VAR(v_CPR, True, Bool) -#endif GLOBAL_VAR(v_CSE, True, Bool) GLOBAL_VAR(v_RuleCheck, Nothing, Maybe String) @@ -203,9 +234,6 @@ buildCoreToDo = do max_iter <- readIORef v_MaxSimplifierIterations usageSP <- readIORef v_UsageSPInf strictness <- readIORef v_Strictness -#ifdef OLD_STRICTNESS - cpr <- readIORef v_CPR -#endif cse <- readIORef v_CSE rule_check <- readIORef v_RuleCheck @@ -282,7 +310,7 @@ buildCoreToDo = do case rule_check of { Just pat -> CoreDoRuleCheck 0 pat; Nothing -> CoreDoNothing }, #ifdef OLD_STRICTNESS - if cpr then CoreDoCPResult else CoreDoNothing, + CoreDoOldStrictness #endif if strictness then CoreDoStrictness else CoreDoNothing, CoreDoWorkerWrapper, @@ -354,11 +382,16 @@ 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 ++ filter (not.null) 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 @@ -425,55 +458,82 @@ GLOBAL_VAR(v_HCHeader, "", String) ----------------------------------------------------------------------------- -- Packages --- package list is maintained in dependency order -GLOBAL_VAR(v_Packages, ("haskell98":"base":"rts":[]), [String]) +------------------------ +-- The PackageConfigMap is read in from the configuration file +-- It doesn't change during a run +GLOBAL_VAR(v_Package_details, emptyPkgMap, PackageConfigMap) 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 + proto_pkg_configs <- loadPackageConfig conf_file + top_dir <- getTopDir + old_pkg_map <- readIORef v_Package_details + + let pkg_configs = mungePackagePaths top_dir proto_pkg_configs + new_pkg_map = extendPkgMap old_pkg_map pkg_configs + + writeIORef v_Package_details new_pkg_map - let -- new package override old ones - new_pkg_names = map name pkg_details - filtered_old_pkg_details = - filter (\p -> name p `notElem` new_pkg_names) old_pkg_details +getPackageConfigMap :: IO PackageConfigMap +getPackageConfigMap = readIORef v_Package_details - writeIORef v_Package_details (pkg_details ++ filtered_old_pkg_details) + +------------------------ +-- The package list reflects what was given as command-line options, +-- plus their dependent packages. +-- It is maintained in dependency order; +-- earlier ones depend on later ones, but not vice versa +GLOBAL_VAR(v_Packages, initPackageList, [PackageName]) + +getPackages :: IO [PackageName] +getPackages = readIORef v_Packages + +initPackageList = [haskell98Package, + basePackage, + rtsPackage] 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) + = do { pkg_details <- getPackageConfigMap + ; ps <- readIORef v_Packages + ; ps' <- add_package pkg_details ps (mkPackageName package) + -- Throws an exception if it fails + ; writeIORef v_Packages ps' } + +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 + = do { -- Add the package's dependents first + ps' <- foldM (add_package pkg_details) ps + (packageDependents details) + ; return (p : ps') } + + | otherwise + = throwDyn (CmdLineError ("unknown package name: " ++ packageNameString p)) getPackageImportPath :: IO [String] getPackageImportPath = do ps <- getPackageInfo - return (nub (filter (not.null) (concatMap import_dirs ps))) + return (nub (filter notNull (concatMap import_dirs ps))) getPackageIncludePath :: IO [String] getPackageIncludePath = do ps <- getPackageInfo - return (nub (filter (not.null) (concatMap include_dirs ps))) + 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)))) + return (reverse (nub (filter notNull (concatMap c_includes ps)))) getPackageLibraryPath :: IO [String] getPackageLibraryPath = do ps <- getPackageInfo - return (nub (filter (not.null) (concatMap library_dirs ps))) + return (nub (filter notNull (concatMap library_dirs ps))) getPackageLibraries :: IO [String] getPackageLibraries = do @@ -486,11 +546,11 @@ getPackageLibraries = do 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. + -- 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 HSbase1 and HSbase2 and + -- 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). @@ -499,10 +559,10 @@ getPackageLibraries = do -- 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 "HSbase1" `elem` libs && "HSbase2" `elem` 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 @@ -529,23 +589,27 @@ getPackageExtraLdOpts = do ps <- getPackageInfo return (concatMap extra_ld_opts ps) +#ifdef darwin_TARGET_OS +getPackageFrameworkPath :: IO [String] +getPackageFrameworkPath = do + ps <- getPackageInfo + return (nub (filter notNull (concatMap framework_dirs ps))) + +getPackageFrameworks :: IO [String] +getPackageFrameworks = do + ps <- getPackageInfo + return (concatMap extra_frameworks ps) +#endif + getPackageInfo :: IO [PackageConfig] -getPackageInfo = do - ps <- readIORef v_Packages - getPackageDetails ps +getPackageInfo = do ps <- getPackages + getPackageDetails ps -getPackageDetails :: [String] -> IO [PackageConfig] +getPackageDetails :: [PackageName] -> IO [PackageConfig] getPackageDetails ps = do - pkg_details <- readIORef v_Package_details - return [ pkg | p <- ps, Just pkg <- [ lookupPkg p pkg_details ] ] - -GLOBAL_VAR(v_Package_details, [], [PackageConfig]) + pkg_details <- getPackageConfigMap + return [ pkg | Just pkg <- map (lookupPkg pkg_details) ps ] -lookupPkg :: String -> [PackageConfig] -> Maybe PackageConfig -lookupPkg nm ps - = case [p | p <- ps, name p == nm] of - [] -> Nothing - (p:_) -> Just p ----------------------------------------------------------------------------- -- Ways