X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fmain%2FPackages.lhs;h=0cfd00f9ff7eda6f8084905c2f2f88e7ebbab7a9;hb=930421d4ed09e5389e0ef4c5eef36075a6809cc0;hp=38a1f9dce89cc3a952687b4489d2c7ad037e1caa;hpb=72547264724117d689a7fa400104185557fb2a0c;p=ghc-hetmet.git diff --git a/compiler/main/Packages.lhs b/compiler/main/Packages.lhs index 38a1f9d..0cfd00f 100644 --- a/compiler/main/Packages.lhs +++ b/compiler/main/Packages.lhs @@ -51,6 +51,7 @@ import Maybes import System.Environment ( getEnv ) import Distribution.InstalledPackageInfo +import Distribution.InstalledPackageInfo.Binary import Distribution.Package hiding (PackageId,depends) import FastString import ErrUtils ( debugTraceMsg, putMsg, Message ) @@ -58,7 +59,6 @@ import Exception import System.Directory import System.FilePath -import Data.Maybe import Control.Monad import Data.List as List @@ -120,12 +120,14 @@ data PackageState = PackageState { -- PackageConfig for the package containing the module, and -- exposed is True if the package exposes that module. - installedPackageIdMap :: FiniteMap InstalledPackageId PackageId + installedPackageIdMap :: InstalledPackageIdMap } -- | A PackageConfigMap maps a 'PackageId' to a 'PackageConfig' type PackageConfigMap = UniqFM PackageConfig +type InstalledPackageIdMap = FiniteMap InstalledPackageId PackageId + emptyPackageConfigMap :: PackageConfigMap emptyPackageConfigMap = emptyUFM @@ -175,7 +177,7 @@ initPackages dflags = do -- ----------------------------------------------------------------------------- -- Reading the package database(s) -readPackageConfigs :: DynFlags -> IO PackageConfigMap +readPackageConfigs :: DynFlags -> IO [PackageConfig] readPackageConfigs dflags = do e_pkg_path <- tryIO (getEnv "GHC_PACKAGE_PATH") system_pkgconfs <- getSystemPackageConfigs dflags @@ -189,11 +191,13 @@ readPackageConfigs dflags = do -- if the path ends in a separator (eg. "/foo/bar:") -- the we tack on the system paths. - -- Read all the ones mentioned in -package-conf flags - pkg_map <- foldM (readPackageConfig dflags) emptyPackageConfigMap - (reverse pkgconfs ++ extraPkgConfs dflags) + pkgs <- mapM (readPackageConfig dflags) + (reverse pkgconfs ++ reverse (extraPkgConfs dflags)) + -- later packages shadow earlier ones. extraPkgConfs + -- is in the opposite order to the flags on the + -- command line. - return pkg_map + return (concat pkgs) getSystemPackageConfigs :: DynFlags -> IO [FilePath] @@ -201,49 +205,46 @@ getSystemPackageConfigs dflags = do -- System one always comes first let system_pkgconf = systemPackageConfig dflags - -- allow package.conf.d to contain a bunch of .conf files - -- containing package specifications. This is an easier way - -- to maintain the package database on systems with a package - -- management system, or systems that don't want to run ghc-pkg - -- to register or unregister packages. Undocumented feature for now. - let system_pkgconf_dir = system_pkgconf <.> "d" - system_pkgconf_dir_exists <- doesDirectoryExist system_pkgconf_dir - system_pkgconfs <- - if system_pkgconf_dir_exists - then do files <- getDirectoryContents system_pkgconf_dir - return [ system_pkgconf_dir file - | file <- files - , takeExtension file == ".conf" ] - else return [] - -- Read user's package conf (eg. ~/.ghc/i386-linux-6.3/package.conf) -- unless the -no-user-package-conf flag was given. - -- We only do this when getAppUserDataDirectory is available - -- (GHC >= 6.3). user_pkgconf <- do + if not (dopt Opt_ReadUserPackageConf dflags) then return [] else do appdir <- getAppUserDataDirectory "ghc" let - pkgconf = appdir - (TARGET_ARCH ++ '-':TARGET_OS ++ '-':cProjectVersion) - "package.conf" - flg <- doesFileExist pkgconf - if (flg && dopt Opt_ReadUserPackageConf dflags) - then return [pkgconf] - else return [] + dir = appdir (TARGET_ARCH ++ '-':TARGET_OS ++ '-':cProjectVersion) + pkgconf = dir "package.conf.d" + -- + exist <- doesDirectoryExist pkgconf + if exist then return [pkgconf] else return [] `catchIO` (\_ -> return []) - return (user_pkgconf ++ system_pkgconfs ++ [system_pkgconf]) + return (user_pkgconf ++ [system_pkgconf]) + +readPackageConfig :: DynFlags -> FilePath -> IO [PackageConfig] +readPackageConfig dflags conf_file = do + isdir <- doesDirectoryExist conf_file + proto_pkg_configs <- + if isdir + then do let filename = conf_file "package.cache" + debugTraceMsg dflags 2 (text "Using binary package database:" <+> text filename) + conf <- readBinPackageDB filename + return (map installedPackageInfoToPackageConfig conf) -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 dflags conf_file - let top_dir = topDir dflags + else do + isfile <- doesFileExist conf_file + when (not isfile) $ + ghcError $ InstallationError $ + "can't find a package database at " ++ conf_file + debugTraceMsg dflags 2 (text "Using package config file:" <+> text conf_file) + loadPackageConfig dflags conf_file + + let + top_dir = topDir dflags pkg_configs1 = mungePackagePaths top_dir proto_pkg_configs pkg_configs2 = maybeHidePackages dflags pkg_configs1 - return (extendPackageConfigMap pkg_map pkg_configs2) + -- + return pkg_configs2 maybeHidePackages :: DynFlags -> [PackageConfig] -> [PackageConfig] maybeHidePackages dflags pkgs @@ -280,65 +281,92 @@ mungePackagePaths top_dir ps = map munge_pkg ps -- (-package, -hide-package, -ignore-package). applyPackageFlag - :: [PackageConfig] -- Initial database + :: UnusablePackages + -> [PackageConfig] -- Initial database -> PackageFlag -- flag to apply -> IO [PackageConfig] -- new database -applyPackageFlag pkgs flag = +applyPackageFlag unusable pkgs flag = case flag of - 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) - - HidePackage str -> - case matchingPackages str pkgs of - Nothing -> missingPackageErr str - Just (ps,qs) -> return (map hide ps ++ qs) - where hide p = p {exposed=False} - - IgnorePackage str -> - case matchingPackages str pkgs of - Nothing -> return pkgs - 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. + ExposePackage str -> + case selectPackages (matchingStr str) pkgs unusable of + Left ps -> packageFlagErr flag ps + Right (p:ps,qs) -> return (p':ps') + where p' = p {exposed=True} + ps' = hideAll (pkgName (sourcePackageId p)) (ps++qs) + _ -> panic "applyPackageFlag" + + ExposePackageId str -> + case selectPackages (matchingId str) pkgs unusable of + Left ps -> packageFlagErr flag ps + Right (p:ps,qs) -> return (p':ps') + where p' = p {exposed=True} + ps' = hideAll (pkgName (sourcePackageId p)) (ps++qs) + _ -> panic "applyPackageFlag" + + HidePackage str -> + case selectPackages (matchingStr str) pkgs unusable of + Left ps -> packageFlagErr flag ps + Right (ps,qs) -> return (map hide ps ++ qs) + where hide p = p {exposed=False} + + _ -> panic "applyPackageFlag" + where -- When a package is requested to be exposed, we hide all other -- packages with the same name. hideAll name ps = map maybe_hide ps - where maybe_hide p | pkgName (package p) == name = p {exposed=False} - | otherwise = p - - -matchingPackages :: String -> [PackageConfig] - -> Maybe ([PackageConfig], [PackageConfig]) -matchingPackages str pkgs - = case partition (packageMatches str) pkgs of - ([],_) -> Nothing - (ps,rest) -> Just (sortByVersion ps, rest) + where maybe_hide p + | pkgName (sourcePackageId p) == name = p {exposed=False} + | otherwise = p + + +selectPackages :: (PackageConfig -> Bool) -> [PackageConfig] + -> UnusablePackages + -> Either [(PackageConfig, UnusablePackageReason)] + ([PackageConfig], [PackageConfig]) +selectPackages matches pkgs unusable + = let + (ps,rest) = partition matches pkgs + reasons = [ (p, lookupFM unusable (installedPackageId p)) + | p <- ps ] + in + if all (isJust.snd) reasons + then Left [ (p, reason) | (p,Just reason) <- reasons ] + else Right (sortByVersion [ p | (p,Nothing) <- reasons ], rest) -- A package named on the command line can either include the -- version, or just the name if it is unambiguous. -packageMatches :: String -> PackageConfig -> Bool -packageMatches str p - = str == display (package p) - || str == display (pkgName (package p)) +matchingStr :: String -> PackageConfig -> Bool +matchingStr str p + = str == display (sourcePackageId p) + || str == display (pkgName (sourcePackageId p)) -pickPackages :: [PackageConfig] -> [String] -> [PackageConfig] -pickPackages pkgs strs = - [ p | p <- strs, Just (p:_, _) <- [matchingPackages p pkgs] ] +matchingId :: String -> PackageConfig -> Bool +matchingId str p = InstalledPackageId str == installedPackageId p sortByVersion :: [InstalledPackageInfo_ m] -> [InstalledPackageInfo_ m] -sortByVersion = sortBy (flip (comparing (pkgVersion.package))) +sortByVersion = sortBy (flip (comparing (pkgVersion.sourcePackageId))) comparing :: Ord a => (t -> a) -> t -> t -> Ordering comparing f a b = f a `compare` f b +packageFlagErr :: PackageFlag + -> [(PackageConfig, UnusablePackageReason)] + -> IO a +packageFlagErr flag reasons = ghcError (CmdLineError (showSDoc $ err)) + where err = text "cannot satisfy " <> ppr_flag <> + (if null reasons then empty else text ": ") $$ + nest 4 (ppr_reasons $$ + text "(use -v for more information)") + ppr_flag = case flag of + IgnorePackage p -> text "-ignore-package " <> text p + HidePackage p -> text "-hide-package " <> text p + ExposePackage p -> text "-package " <> text p + ExposePackageId p -> text "-package-id " <> text p + ppr_reasons = vcat (map ppr_reason reasons) + ppr_reason (p, reason) = pprReason (pprIPkg p <+> text "is") reason + -- ----------------------------------------------------------------------------- -- Hide old versions of packages @@ -354,16 +382,15 @@ hideOldPackages dflags pkgs = mapM maybe_hide pkgs | not (exposed p) = return p | (p' : _) <- later_versions = do debugTraceMsg dflags 2 $ - (ptext (sLit "hiding package") <+> - text (display (package p)) <+> + (ptext (sLit "hiding package") <+> pprSPkg p <+> ptext (sLit "to avoid conflict with later version") <+> - text (display (package p'))) + pprSPkg p') return (p {exposed=False}) | otherwise = return p - where myname = pkgName (package p) - myversion = pkgVersion (package p) + where myname = pkgName (sourcePackageId p) + myversion = pkgVersion (sourcePackageId p) later_versions = [ p | p <- pkgs, exposed p, - let pkg = package p, + let pkg = sourcePackageId p, pkgName pkg == myname, pkgVersion pkg > myversion ] @@ -393,7 +420,7 @@ findWiredInPackages dflags pkgs = do dphParPackageId ] matches :: PackageConfig -> String -> Bool - pc `matches` pid = display (pkgName (package pc)) == pid + pc `matches` pid = display (pkgName (sourcePackageId pc)) == pid -- find which package corresponds to each wired-in package -- delete any other packages with the same name @@ -426,7 +453,7 @@ findWiredInPackages dflags pkgs = do ptext (sLit "wired-in package ") <> text wired_pkg <> ptext (sLit " mapped to ") - <> text (display (package pkg)) + <> pprIPkg pkg return (Just (installedPackageId pkg)) @@ -450,13 +477,42 @@ findWiredInPackages dflags pkgs = do updateWiredInDependencies pkgs = map upd_pkg pkgs where upd_pkg p | installedPackageId p `elem` wired_in_ids - = p { package = (package p){ pkgVersion = Version [] [] } } + = p { sourcePackageId = (sourcePackageId p){ pkgVersion = Version [] [] } } | otherwise = p return $ updateWiredInDependencies pkgs -- ---------------------------------------------------------------------------- + +data UnusablePackageReason + = IgnoredWithFlag + | MissingDependencies [InstalledPackageId] + | ShadowedBy InstalledPackageId + +type UnusablePackages = FiniteMap InstalledPackageId UnusablePackageReason + +pprReason :: SDoc -> UnusablePackageReason -> SDoc +pprReason pref reason = case reason of + IgnoredWithFlag -> + pref <+> ptext (sLit "ignored due to an -ignore-package flag") + MissingDependencies deps -> + pref <+> + ptext (sLit "unusable due to missing or recursive dependencies:") $$ + nest 2 (hsep (map (text.display) deps)) + ShadowedBy ipid -> + pref <+> ptext (sLit "shadowed by package ") <> text (display ipid) + +reportUnusable :: DynFlags -> UnusablePackages -> IO () +reportUnusable dflags pkgs = mapM_ report (fmToList pkgs) + where + report (ipid, reason) = + debugTraceMsg dflags 2 $ + pprReason + (ptext (sLit "package") <+> + text (display ipid) <+> text "is") reason + +-- ---------------------------------------------------------------------------- -- -- Detect any packages that have missing dependencies, and also any -- mutually-recursive groups of packages (loops in the package graph @@ -464,34 +520,60 @@ findWiredInPackages dflags pkgs = do -- dependency graph, repeatedly adding packages whose dependencies are -- satisfied until no more can be added. -- -elimDanglingDeps - :: DynFlags - -> [PackageConfig] - -> [PackageId] -- ignored packages - -> IO [PackageConfig] - -elimDanglingDeps dflags pkgs ignored = go [] pkgs' +findBroken :: [PackageConfig] -> UnusablePackages +findBroken pkgs = go [] emptyFM pkgs where - pkgs' = filter (\p -> packageConfigId p `notElem` ignored) pkgs - - go avail not_avail = - case partitionWith (depsAvailable avail) not_avail of - ([], not_avail) -> do mapM_ reportElim not_avail; return avail - (new_avail, not_avail) -> go (new_avail ++ avail) (map fst not_avail) - - depsAvailable :: [PackageConfig] -> PackageConfig + go avail ipids not_avail = + case partitionWith (depsAvailable ipids) not_avail of + ([], not_avail) -> + listToFM [ (installedPackageId p, MissingDependencies deps) + | (p,deps) <- not_avail ] + (new_avail, not_avail) -> + go (new_avail ++ avail) new_ipids (map fst not_avail) + where new_ipids = addListToFM ipids + [ (installedPackageId p, p) | p <- new_avail ] + + depsAvailable :: FiniteMap InstalledPackageId PackageConfig + -> PackageConfig -> Either PackageConfig (PackageConfig, [InstalledPackageId]) - depsAvailable pkgs_ok pkg + depsAvailable ipids pkg | null dangling = Left pkg | otherwise = Right (pkg, dangling) - where dangling = filter (`notElem` pids) (depends pkg) - pids = map installedPackageId pkgs_ok + where dangling = filter (not . (`elemFM` ipids)) (depends pkg) - 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.display) deps))) +-- ----------------------------------------------------------------------------- +-- Eliminate shadowed packages, giving the user some feedback + +-- later packages in the list should shadow earlier ones with the same +-- package name/version. +shadowPackages :: [PackageConfig] -> UnusablePackages +shadowPackages pkgs + = let (_,shadowed) = foldl check (emptyUFM,[]) pkgs + in listToFM shadowed + where + check (pkgmap,shadowed) pkg + = (addToUFM pkgmap (packageConfigId pkg) pkg, shadowed') + where + shadowed' + | Just oldpkg <- lookupUFM pkgmap (packageConfigId pkg) + = (installedPackageId oldpkg, ShadowedBy (installedPackageId pkg)) + :shadowed + | otherwise + = shadowed + +-- ----------------------------------------------------------------------------- + +ignorePackages :: [PackageFlag] -> [PackageConfig] -> UnusablePackages +ignorePackages flags pkgs = listToFM (concatMap doit flags) + where + doit (IgnorePackage str) = + case partition (matchingStr str) pkgs of + (ps, _) -> [ (installedPackageId p, IgnoredWithFlag) + | p <- ps ] + -- 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. + doit _ = panic "ignorePackages" -- ----------------------------------------------------------------------------- -- When all the command-line options are in, we can process our package @@ -499,7 +581,7 @@ elimDanglingDeps dflags pkgs ignored = go [] pkgs' mkPackageState :: DynFlags - -> PackageConfigMap -- initial database + -> [PackageConfig] -- initial database -> [PackageId] -- preloaded packages -> PackageId -- this package -> IO (PackageState, @@ -508,14 +590,29 @@ mkPackageState -- package is a wired-in package. -mkPackageState dflags orig_pkg_db preload0 this_package = do +mkPackageState dflags pkgs0 preload0 this_package = do + + let + flags = reverse (packageFlags dflags) + (ignore_flags, other_flags) = partition is_ignore flags + is_ignore IgnorePackage{} = True + is_ignore _ = False + + shadowed = shadowPackages pkgs0 + ignored = ignorePackages ignore_flags pkgs0 + + pkgs0' = filter (not . (`elemFM` (plusFM shadowed ignored)) . installedPackageId) pkgs0 + broken = findBroken pkgs0' + unusable = shadowed `plusFM` ignored `plusFM` broken + + reportUnusable dflags unusable + -- -- Modify the package database according to the command-line flags -- (-package, -hide-package, -ignore-package, -hide-all-packages). -- - let flags = reverse (packageFlags dflags) - let pkgs0 = eltsUFM orig_pkg_db - pkgs1 <- foldM applyPackageFlag pkgs0 flags + pkgs1 <- foldM (applyPackageFlag unusable) pkgs0 other_flags + let pkgs2 = filter (not . (`elemFM` unusable) . installedPackageId) pkgs1 -- Here we build up a set of the packages mentioned in -package -- flags on the command line; these are called the "preload" @@ -523,23 +620,22 @@ mkPackageState dflags orig_pkg_db preload0 this_package = do -- should contain at least rts & base, which is why we pretend that -- the command line contains -package rts & -package base. -- - let preload1 = map installedPackageId $ - pickPackages pkgs0 [ p | ExposePackage p <- flags ] + let preload1 = [ installedPackageId p | f <- flags, p <- get_exposed f ] + + get_exposed (ExposePackage s) = filter (matchingStr s) pkgs2 + get_exposed (ExposePackageId s) = filter (matchingId s) pkgs2 + get_exposed _ = [] -- hide packages that are subsumed by later versions - pkgs2 <- hideOldPackages dflags pkgs1 + pkgs3 <- hideOldPackages dflags pkgs2 -- sort out which packages are wired in - pkgs3 <- findWiredInPackages dflags pkgs2 + pkgs4 <- findWiredInPackages dflags pkgs3 - let ignored = map packageConfigId $ - pickPackages pkgs0 [ p | IgnorePackage p <- flags ] - pkgs <- elimDanglingDeps dflags pkgs3 ignored - - let pkg_db = extendPackageConfigMap emptyPackageConfigMap pkgs + let pkg_db = extendPackageConfigMap emptyPackageConfigMap pkgs4 ipid_map = listToFM [ (installedPackageId p, packageConfigId p) - | p <- pkgs ] + | p <- pkgs4 ] lookupIPID ipid@(InstalledPackageId str) | Just pid <- lookupFM ipid_map ipid = return pid @@ -591,8 +687,11 @@ mkModuleMap pkg_db = foldr extend_modmap emptyUFM pkgids exposed_mods = exposedModules pkg hidden_mods = hiddenModules pkg -pprPkg :: PackageConfig -> SDoc -pprPkg p = text (display (package p)) +pprSPkg :: PackageConfig -> SDoc +pprSPkg p = text (display (sourcePackageId p)) + +pprIPkg :: PackageConfig -> SDoc +pprIPkg p = text (display (installedPackageId p)) -- ----------------------------------------------------------------------------- -- Extracting information from the packages in scope