X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fmain%2FPackages.lhs;h=44ad7d15b252539bab967a02bf37baa8b6b0e386;hb=6084fb5517da34f65034370a3695e2af3b85ce2b;hp=2647a5fab0d9530e317cb90ff7f0f95b119e2d72;hpb=a9c09ca0546d62408356bc83bca92d8e88a5df7f;p=ghc-hetmet.git diff --git a/compiler/main/Packages.lhs b/compiler/main/Packages.lhs index 2647a5f..44ad7d1 100644 --- a/compiler/main/Packages.lhs +++ b/compiler/main/Packages.lhs @@ -4,13 +4,6 @@ % Package manipulation % \begin{code} -{-# OPTIONS -w #-} --- The above warning supression flag is a temporary kludge. --- While working on this module you are encouraged to remove it and fix --- any warnings in the module. See --- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings --- for details - module Packages ( module PackageConfig, @@ -26,7 +19,6 @@ module Packages ( -- * Inspecting the set of packages in scope getPackageIncludePath, - getPackageCIncludes, getPackageLibraryPath, getPackageLinkOpts, getPackageExtraCcOpts, @@ -34,6 +26,8 @@ module Packages ( getPackageFrameworks, getPreloadPackagesAnd, + collectIncludeDirs, collectLibraryPaths, collectLinkOpts, + -- * Utils isDllName ) @@ -55,18 +49,19 @@ import Panic import Outputable import System.Environment ( getEnv ) -import Distribution.InstalledPackageInfo -import Distribution.Package +import Distribution.InstalledPackageInfo hiding (depends) +import Distribution.Package hiding (depends) +import Distribution.Text import Distribution.Version import FastString import ErrUtils ( debugTraceMsg, putMsg, Message ) +import Exception import System.Directory import System.FilePath import Data.Maybe import Control.Monad import Data.List -import Control.Exception ( throwDyn ) -- --------------------------------------------------------------------------- -- The Package state @@ -143,7 +138,7 @@ extendPackageConfigMap pkg_map new_pkgs where add pkg_map p = addToUFM pkg_map (packageConfigId p) p getPackageDetails :: PackageState -> PackageId -> PackageConfig -getPackageDetails dflags ps = expectJust "getPackageDetails" (lookupPackage (pkgIdMap dflags) ps) +getPackageDetails ps pid = expectJust "getPackageDetails" (lookupPackage (pkgIdMap ps) pid) -- ---------------------------------------------------------------------------- -- Loading the package config files and building up the package state @@ -178,7 +173,7 @@ initPackages dflags = do readPackageConfigs :: DynFlags -> IO PackageConfigMap readPackageConfigs dflags = do - e_pkg_path <- try (getEnv "GHC_PACKAGE_PATH") + e_pkg_path <- tryIO (getEnv "GHC_PACKAGE_PATH") system_pkgconfs <- getSystemPackageConfigs dflags let pkgconfs = case e_pkg_path of @@ -221,7 +216,7 @@ getSystemPackageConfigs dflags = do -- unless the -no-user-package-conf flag was given. -- We only do this when getAppUserDataDirectory is available -- (GHC >= 6.3). - user_pkgconf <- handle (\_ -> return []) $ do + user_pkgconf <- do appdir <- getAppUserDataDirectory "ghc" let pkgconf = appdir @@ -231,6 +226,7 @@ getSystemPackageConfigs dflags = do if (flg && dopt Opt_ReadUserPackageConf dflags) then return [pkgconf] else return [] + `catchIO` (\_ -> return []) return (user_pkgconf ++ system_pkgconfs ++ [system_pkgconf]) @@ -239,7 +235,7 @@ readPackageConfig :: DynFlags -> PackageConfigMap -> FilePath -> IO PackageConfigMap readPackageConfig dflags pkg_map conf_file = do debugTraceMsg dflags 2 (text "Using package config file:" <+> text conf_file) - proto_pkg_configs <- loadPackageConfig conf_file + proto_pkg_configs <- loadPackageConfig dflags conf_file let top_dir = topDir dflags pkg_configs1 = mungePackagePaths top_dir proto_pkg_configs pkg_configs2 = maybeHidePackages dflags pkg_configs1 @@ -289,6 +285,7 @@ applyPackageFlag pkgs flag = ExposePackage str -> case matchingPackages str pkgs of Nothing -> missingPackageErr str + Just ([], _) -> panic "applyPackageFlag" Just (p:ps,qs) -> return (p':ps') where p' = p {exposed=True} ps' = hideAll (pkgName (package p)) (ps++qs) @@ -302,7 +299,7 @@ applyPackageFlag pkgs flag = IgnorePackage str -> case matchingPackages str pkgs of Nothing -> return pkgs - Just (ps,qs) -> return qs + Just (_, qs) -> return qs -- missing package is not an error for -ignore-package, -- because a common usage is to -ignore-package P as -- a preventative measure just in case P exists. @@ -324,14 +321,17 @@ matchingPackages str pkgs -- A package named on the command line can either include the -- version, or just the name if it is unambiguous. matches str p - = str == showPackageId (package p) - || str == pkgName (package p) - + = str == display (package p) + || str == display (pkgName (package p)) +pickPackages :: [PackageConfig] -> [String] -> [PackageConfig] pickPackages pkgs strs = - [ p | p <- strs, Just (p:ps,_) <- [matchingPackages p pkgs] ] + [ p | p <- strs, Just (p:_, _) <- [matchingPackages p pkgs] ] +sortByVersion :: [InstalledPackageInfo_ m] -> [InstalledPackageInfo_ m] sortByVersion = sortBy (flip (comparing (pkgVersion.package))) + +comparing :: Ord a => (t -> a) -> t -> t -> Ordering comparing f a b = f a `compare` f b -- ----------------------------------------------------------------------------- @@ -349,10 +349,10 @@ hideOldPackages dflags pkgs = mapM maybe_hide pkgs | not (exposed p) = return p | (p' : _) <- later_versions = do debugTraceMsg dflags 2 $ - (ptext SLIT("hiding package") <+> - text (showPackageId (package p)) <+> - ptext SLIT("to avoid conflict with later version") <+> - text (showPackageId (package p'))) + (ptext (sLit "hiding package") <+> + text (display (package p)) <+> + ptext (sLit "to avoid conflict with later version") <+> + text (display (package p'))) return (p {exposed=False}) | otherwise = return p where myname = pkgName (package p) @@ -380,13 +380,21 @@ findWiredInPackages dflags pkgs preload this_package = do -- their canonical names (eg. base-1.0 ==> base). -- let - wired_in_pkgids = [ basePackageId, - rtsPackageId, - haskell98PackageId, - thPackageId, - ndpPackageId ] - - wired_in_names = map packageIdString wired_in_pkgids + wired_in_pkgids :: [(PackageId, [String])] + wired_in_pkgids = [ (primPackageId, [""]), + (integerPackageId, [""]), + (basePackageId, [""]), + (rtsPackageId, [""]), + (haskell98PackageId, [""]), + (thPackageId, [""]), + (dphSeqPackageId, [""]), + (dphParPackageId, [""]), + (ndpPackageId, ["-seq", "-par"]) ] + + matches :: PackageConfig -> (PackageId, [String]) -> Bool + pc `matches` (pid, suffixes) + = display (pkgName (package pc)) `elem` + (map (packageIdString pid ++) suffixes) -- find which package corresponds to each wired-in package -- delete any other packages with the same name @@ -398,46 +406,53 @@ findWiredInPackages dflags pkgs preload this_package = do -- version. To override the default choice, -hide-package -- could be used to hide newer versions. -- - findWiredInPackage :: [PackageConfig] -> String - -> IO (Maybe PackageIdentifier) + findWiredInPackage :: [PackageConfig] -> (PackageId, [String]) + -> IO (Maybe (PackageIdentifier, PackageId)) findWiredInPackage pkgs wired_pkg = - let all_ps = [ p | p <- pkgs, pkgName (package p) == wired_pkg ] in + let all_ps = [ p | p <- pkgs, p `matches` wired_pkg ] in case filter exposed all_ps of [] -> case all_ps of [] -> notfound many -> pick (head (sortByVersion many)) many -> pick (head (sortByVersion many)) where + suffixes = snd wired_pkg notfound = do debugTraceMsg dflags 2 $ - ptext SLIT("wired-in package ") - <> text wired_pkg - <> ptext SLIT(" not found.") + ptext (sLit "wired-in package ") + <> ppr (fst wired_pkg) + <> (if null suffixes + then empty + else text (show suffixes)) + <> ptext (sLit " not found.") return Nothing + pick :: InstalledPackageInfo_ ModuleName + -> IO (Maybe (PackageIdentifier, PackageId)) pick pkg = do debugTraceMsg dflags 2 $ - ptext SLIT("wired-in package ") - <> text wired_pkg - <> ptext SLIT(" mapped to ") - <> text (showPackageId (package pkg)) - return (Just (package pkg)) + ptext (sLit "wired-in package ") + <> ppr (fst wired_pkg) + <> ptext (sLit " mapped to ") + <> text (display (package pkg)) + return (Just (package pkg, fst wired_pkg)) - mb_wired_in_ids <- mapM (findWiredInPackage pkgs) wired_in_names + mb_wired_in_ids <- mapM (findWiredInPackage pkgs) wired_in_pkgids let wired_in_ids = catMaybes mb_wired_in_ids - deleteOtherWiredInPackages pkgs = filter ok pkgs - where ok p = pkgName (package p) `notElem` wired_in_names - || package p `elem` wired_in_ids + deleteOtherWiredInPackages pkgs = filterOut bad pkgs + where bad p = any (p `matches`) wired_in_pkgids + && package p `notElem` map fst wired_in_ids updateWiredInDependencies pkgs = map upd_pkg pkgs where upd_pkg p = p{ package = upd_pid (package p), depends = map upd_pid (depends p) } - upd_pid pid = case filter (== pid) wired_in_ids of + upd_pid pid = case filter ((== pid) . fst) wired_in_ids of [] -> pid - (x:_) -> x{ pkgVersion = Version [] [] } + ((x, y):_) -> x{ pkgName = PackageName (packageIdString y), + pkgVersion = Version [] [] } pkgs1 = deleteOtherWiredInPackages pkgs @@ -485,9 +500,9 @@ elimDanglingDeps dflags pkgs ignored = go [] pkgs' reportElim (p, deps) = debugTraceMsg dflags 2 $ - (ptext SLIT("package") <+> pprPkg p <+> - ptext SLIT("will be ignored due to missing or recursive dependencies:") $$ - nest 2 (hsep (map (text.showPackageId) deps))) + (ptext (sLit "package") <+> pprPkg p <+> + ptext (sLit "will be ignored due to missing or recursive dependencies:") $$ + nest 2 (hsep (map (text.display) deps))) -- ----------------------------------------------------------------------------- -- When all the command-line options are in, we can process our package @@ -534,11 +549,12 @@ mkPackageState dflags orig_pkg_db preload0 this_package = do pkgs <- elimDanglingDeps dflags pkgs3 ignored let pkg_db = extendPackageConfigMap emptyPackageConfigMap pkgs - pkgids = map packageConfigId pkgs -- add base & rts to the preload packages - basicLinkedPackages = filter (flip elemUFM pkg_db) - [basePackageId,rtsPackageId] + basicLinkedPackages + | dopt Opt_AutoLinkPackages dflags + = filter (flip elemUFM pkg_db) [basePackageId, rtsPackageId] + | otherwise = [] -- but in any case remove the current package from the set of -- preloaded packages so that base/rts does not end up in the -- set up preloaded package when we are just building it @@ -577,7 +593,7 @@ mkModuleMap pkg_db = foldr extend_modmap emptyUFM pkgids hidden_mods = hiddenModules pkg pprPkg :: PackageConfig -> SDoc -pprPkg p = text (showPackageId (package p)) +pprPkg p = text (display (package p)) -- ----------------------------------------------------------------------------- -- Extracting information from the packages in scope @@ -591,26 +607,29 @@ pprPkg p = text (showPackageId (package p)) -- use. getPackageIncludePath :: DynFlags -> [PackageId] -> IO [String] -getPackageIncludePath dflags pkgs = do - ps <- getPreloadPackagesAnd dflags pkgs - return (nub (filter notNull (concatMap includeDirs ps))) +getPackageIncludePath dflags pkgs = + collectIncludeDirs `fmap` getPreloadPackagesAnd dflags pkgs - -- includes are in reverse dependency order (i.e. rts first) -getPackageCIncludes :: [PackageConfig] -> IO [String] -getPackageCIncludes pkg_configs = do - return (reverse (nub (filter notNull (concatMap includes pkg_configs)))) +collectIncludeDirs :: [PackageConfig] -> [FilePath] +collectIncludeDirs ps = nub (filter notNull (concatMap includeDirs ps)) getPackageLibraryPath :: DynFlags -> [PackageId] -> IO [String] -getPackageLibraryPath dflags pkgs = do - ps <- getPreloadPackagesAnd dflags pkgs - return (nub (filter notNull (concatMap libraryDirs ps))) +getPackageLibraryPath dflags pkgs = + collectLibraryPaths `fmap` getPreloadPackagesAnd dflags pkgs + +collectLibraryPaths :: [PackageConfig] -> [FilePath] +collectLibraryPaths ps = nub (filter notNull (concatMap libraryDirs ps)) getPackageLinkOpts :: DynFlags -> [PackageId] -> IO [String] -getPackageLinkOpts dflags pkgs = do - ps <- getPreloadPackagesAnd dflags pkgs - let tag = buildTag dflags - rts_tag = rtsBuildTag dflags - let +getPackageLinkOpts dflags pkgs = + collectLinkOpts dflags `fmap` getPreloadPackagesAnd dflags pkgs + +collectLinkOpts :: DynFlags -> [PackageConfig] -> [String] +collectLinkOpts dflags ps = concat (map all_opts ps) + where + tag = buildTag dflags + rts_tag = rtsBuildTag dflags + mkDynName | opt_Static = id | otherwise = (++ ("-ghc" ++ cProjectVersion)) libs p = map (mkDynName . addSuffix) (hsLibraries p) @@ -623,8 +642,6 @@ getPackageLinkOpts dflags pkgs = do expandTag t | null t = "" | otherwise = '_':t - return (concat (map all_opts ps)) - getPackageExtraCcOpts :: DynFlags -> [PackageId] -> IO [String] getPackageExtraCcOpts dflags pkgs = do ps <- getPreloadPackagesAnd dflags pkgs @@ -671,7 +688,7 @@ closeDeps pkg_map ps = throwErr (closeDepsErr pkg_map ps) throwErr :: MaybeErr Message a -> IO a throwErr m = case m of - Failed e -> throwDyn (CmdLineError (showSDoc e)) + Failed e -> ghcError (CmdLineError (showSDoc e)) Succeeded r -> return r closeDepsErr :: PackageConfigMap -> [(PackageId,Maybe PackageId)] @@ -693,12 +710,16 @@ add_package pkg_db ps (p, mb_parent) ps' <- foldM (add_package pkg_db) ps (zip deps (repeat (Just p))) return (p : ps') -missingPackageErr p = throwDyn (CmdLineError (showSDoc (missingPackageMsg p))) -missingPackageMsg p = ptext SLIT("unknown package:") <+> text p +missingPackageErr :: String -> IO [PackageConfig] +missingPackageErr p = ghcError (CmdLineError (showSDoc (missingPackageMsg p))) +missingPackageMsg :: String -> SDoc +missingPackageMsg p = ptext (sLit "unknown package:") <+> text p + +missingDependencyMsg :: Maybe PackageId -> SDoc missingDependencyMsg Nothing = empty missingDependencyMsg (Just parent) - = space <> parens (ptext SLIT("dependency of") <+> ftext (packageIdFS parent)) + = space <> parens (ptext (sLit "dependency of") <+> ftext (packageIdFS parent)) -- ----------------------------------------------------------------------------- @@ -716,10 +737,7 @@ dumpPackages :: DynFlags -> IO () dumpPackages dflags = do let pkg_map = pkgIdMap (pkgState dflags) putMsg dflags $ - vcat (map (text.showInstalledPackageInfo.to_ipi) (eltsUFM pkg_map)) - where - to_ipi pkgconf@InstalledPackageInfo_{ exposedModules = e, - hiddenModules = h } = - pkgconf{ exposedModules = map moduleNameString e, - hiddenModules = map moduleNameString h } + vcat (map (text . showInstalledPackageInfo + . packageConfigToInstalledPackageInfo) + (eltsUFM pkg_map)) \end{code}