X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fmain%2FPackages.lhs;h=38a1f9dce89cc3a952687b4489d2c7ad037e1caa;hb=72547264724117d689a7fa400104185557fb2a0c;hp=9904fdf609a82fb1d5348dec94d330c566d0dd30;hpb=d5b1999089dd4a45cf872f88dd0d49e1207a3161;p=ghc-hetmet.git diff --git a/compiler/main/Packages.lhs b/compiler/main/Packages.lhs index 9904fdf..38a1f9d 100644 --- a/compiler/main/Packages.lhs +++ b/compiler/main/Packages.lhs @@ -1,16 +1,8 @@ - % -% (c) The University of Glasgow, 2006 % -% Package manipulation +% (c) The University of Glasgow, 2006 % \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 - +-- | Package manipulation module Packages ( module PackageConfig, @@ -26,7 +18,6 @@ module Packages ( -- * Inspecting the set of packages in scope getPackageIncludePath, - getPackageCIncludes, getPackageLibraryPath, getPackageLinkOpts, getPackageExtraCcOpts, @@ -34,6 +25,9 @@ module Packages ( getPackageFrameworks, getPreloadPackagesAnd, + collectIncludeDirs, collectLibraryPaths, collectLinkOpts, + packageHsLibs, + -- * Utils isDllName ) @@ -44,63 +38,60 @@ where import PackageConfig import ParsePkgConf ( loadPackageConfig ) import DynFlags ( dopt, DynFlag(..), DynFlags(..), PackageFlag(..) ) -import StaticFlags ( opt_Static ) +import StaticFlags import Config ( cProjectVersion ) import Name ( Name, nameModule_maybe ) import UniqFM +import FiniteMap import Module import Util -import Maybes ( expectJust, MaybeErr(..) ) import Panic import Outputable - -#if __GLASGOW_HASKELL__ < 603 -import Compat.Directory ( getAppUserDataDirectory ) -#endif +import Maybes import System.Environment ( getEnv ) import Distribution.InstalledPackageInfo -import Distribution.Package -import Distribution.Version +import Distribution.Package hiding (PackageId,depends) 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 ) +import Data.List as List -- --------------------------------------------------------------------------- -- The Package state --- Package state is all stored in DynFlags, including the details of +-- | Package state is all stored in 'DynFlag's, including the details of -- all packages, which packages are exposed, and which modules they -- provide. - --- The package state is computed by initPackages, and kept in DynFlags. -- --- * -package causes to become exposed, and all other packages +-- The package state is computed by 'initPackages', and kept in DynFlags. +-- +-- * @-package @ causes @@ to become exposed, and all other packages -- with the same name to become hidden. -- --- * -hide-package causes to become hidden. +-- * @-hide-package @ causes @@ to become hidden. -- --- * Let exposedPackages be the set of packages thus exposed. --- Let depExposedPackages be the transitive closure from exposedPackages of +-- * Let @exposedPackages@ be the set of packages thus exposed. +-- Let @depExposedPackages@ be the transitive closure from @exposedPackages@ of -- their dependencies. -- -- * When searching for a module from an preload import declaration, --- only the exposed modules in exposedPackages are valid. +-- only the exposed modules in @exposedPackages@ are valid. -- -- * When searching for a module from an implicit import, all modules --- from depExposedPackages are valid. +-- from @depExposedPackages@ are valid. -- --- * When linking in a comp manager mode, we link in packages the +-- * When linking in a compilation manager mode, we link in packages the -- program depends on (the compiler knows this list by the -- time it gets to the link step). Also, we link in all packages --- which were mentioned with preload -package flags on the command-line, --- or are a transitive dependency of same, or are "base"/"rts". --- The reason for (b) is that we might need packages which don't +-- which were mentioned with preload @-package@ flags on the command-line, +-- or are a transitive dependency of same, or are \"base\"\/\"rts\". +-- The reason for this is that we might need packages which don't -- contain any Haskell modules, and therefore won't be discovered -- by the normal mechanism of dependency tracking. @@ -123,19 +114,22 @@ data PackageState = PackageState { -- should be in reverse dependency order; that is, a package -- is always mentioned before the packages it depends on. - moduleToPkgConfAll :: UniqFM [(PackageConfig,Bool)] -- ModuleEnv mapping + moduleToPkgConfAll :: UniqFM [(PackageConfig,Bool)], -- ModuleEnv mapping -- Derived from pkgIdMap. -- Maps Module to (pkgconf,exposed), where pkgconf is the -- PackageConfig for the package containing the module, and -- exposed is True if the package exposes that module. + + installedPackageIdMap :: FiniteMap InstalledPackageId PackageId } --- A PackageConfigMap maps a PackageId to a PackageConfig +-- | A PackageConfigMap maps a 'PackageId' to a 'PackageConfig' type PackageConfigMap = UniqFM PackageConfig emptyPackageConfigMap :: PackageConfigMap emptyPackageConfigMap = emptyUFM +-- | Find the package we know about with the given id (e.g. \"foo-1.0\"), if any lookupPackage :: PackageConfigMap -> PackageId -> Maybe PackageConfig lookupPackage = lookupUFM @@ -145,8 +139,10 @@ extendPackageConfigMap pkg_map new_pkgs = foldl add pkg_map new_pkgs where add pkg_map p = addToUFM pkg_map (packageConfigId p) p +-- | Looks up the package with the given id in the package state, panicing if it is +-- not found 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 @@ -158,11 +154,11 @@ getPackageDetails dflags ps = expectJust "getPackageDetails" (lookupPackage (pkg -- -- Returns a list of packages to link in if we're doing dynamic linking. -- This list contains the packages that the user explicitly mentioned with --- -package flags. +-- @-package@ flags. -- -- 'initPackages' can be called again subsequently after updating the -- 'packageFlags' field of the 'DynFlags', and it will update the --- 'packageState' in 'DynFlags' and return a list of packages to +-- 'pkgState' in 'DynFlags' and return a list of packages to -- link in. initPackages :: DynFlags -> IO (DynFlags, [PackageId]) initPackages dflags = do @@ -181,7 +177,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 @@ -210,30 +206,31 @@ getSystemPackageConfigs dflags = do -- 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" + 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 + return [ system_pkgconf_dir file | file <- files - , isSuffixOf ".conf" file] + , 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 <- handle (\_ -> return []) $ do + user_pkgconf <- do appdir <- getAppUserDataDirectory "ghc" let pkgconf = appdir - `joinFileName` (TARGET_ARCH ++ '-':TARGET_OS ++ '-':cProjectVersion) - `joinFileName` "package.conf" + (TARGET_ARCH ++ '-':TARGET_OS ++ '-':cProjectVersion) + "package.conf" flg <- doesFileExist pkgconf if (flg && dopt Opt_ReadUserPackageConf dflags) then return [pkgconf] else return [] + `catchIO` (\_ -> return []) return (user_pkgconf ++ system_pkgconfs ++ [system_pkgconf]) @@ -242,7 +239,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 @@ -263,14 +260,20 @@ mungePackagePaths top_dir ps = map munge_pkg ps munge_pkg p = p{ importDirs = munge_paths (importDirs p), includeDirs = munge_paths (includeDirs p), libraryDirs = munge_paths (libraryDirs p), - frameworkDirs = munge_paths (frameworkDirs p) } + frameworkDirs = munge_paths (frameworkDirs p), + haddockInterfaces = munge_paths (haddockInterfaces p), + haddockHTMLs = munge_paths (haddockHTMLs p) + } munge_paths = map munge_path munge_path p - | Just p' <- maybePrefixMatch "$topdir" p = top_dir ++ p' + | Just p' <- stripPrefix "$topdir" p = top_dir ++ p' + | Just p' <- stripPrefix "$httptopdir" p = toHttpPath top_dir ++ p' | otherwise = p + toHttpPath p = "file:///" ++ p + -- ----------------------------------------------------------------------------- -- Modify our copy of the package database based on a package flag @@ -286,6 +289,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) @@ -299,7 +303,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. @@ -314,21 +318,25 @@ applyPackageFlag pkgs flag = matchingPackages :: String -> [PackageConfig] -> Maybe ([PackageConfig], [PackageConfig]) matchingPackages str pkgs - = case partition (matches str) pkgs of + = case partition (packageMatches str) pkgs of ([],_) -> Nothing (ps,rest) -> Just (sortByVersion ps, rest) - where - -- 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) +-- 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)) +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 -- ----------------------------------------------------------------------------- @@ -346,10 +354,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) @@ -365,25 +373,27 @@ hideOldPackages dflags pkgs = mapM maybe_hide pkgs findWiredInPackages :: DynFlags -> [PackageConfig] -- database - -> [PackageIdentifier] -- preload packages - -> PackageId -- this package - -> IO ([PackageConfig], - [PackageIdentifier], - PackageId) + -> IO [PackageConfig] -findWiredInPackages dflags pkgs preload this_package = do +findWiredInPackages dflags pkgs = do -- -- Now we must find our wired-in packages, and rename them to -- 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 :: [String] + wired_in_pkgids = map packageIdString + [ primPackageId, + integerPackageId, + basePackageId, + rtsPackageId, + haskell98PackageId, + thPackageId, + dphSeqPackageId, + dphParPackageId ] + + matches :: PackageConfig -> String -> Bool + pc `matches` pid = display (pkgName (package pc)) == pid -- find which package corresponds to each wired-in package -- delete any other packages with the same name @@ -396,63 +406,63 @@ findWiredInPackages dflags pkgs preload this_package = do -- could be used to hide newer versions. -- findWiredInPackage :: [PackageConfig] -> String - -> IO (Maybe PackageIdentifier) + -> IO (Maybe InstalledPackageId) findWiredInPackage pkgs wired_pkg = - let all_ps = [ p | p <- pkgs, pkgName (package p) == wired_pkg ] in - case filter exposed all_ps of - [] -> case all_ps of - [] -> notfound - many -> pick (head (sortByVersion many)) - many -> pick (head (sortByVersion many)) + let all_ps = [ p | p <- pkgs, p `matches` wired_pkg ] in + case all_ps of + [] -> notfound + many -> pick (head (sortByVersion many)) where notfound = do debugTraceMsg dflags 2 $ - ptext SLIT("wired-in package ") + ptext (sLit "wired-in package ") <> text wired_pkg - <> ptext SLIT(" not found.") + <> ptext (sLit " not found.") return Nothing + pick :: InstalledPackageInfo_ ModuleName + -> IO (Maybe InstalledPackageId) pick pkg = do debugTraceMsg dflags 2 $ - ptext SLIT("wired-in package ") + ptext (sLit "wired-in package ") <> text wired_pkg - <> ptext SLIT(" mapped to ") - <> text (showPackageId (package pkg)) - return (Just (package pkg)) + <> ptext (sLit " mapped to ") + <> text (display (package pkg)) + return (Just (installedPackageId 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 + -- this is old: we used to assume that if there were + -- multiple versions of wired-in packages installed that + -- they were mutually exclusive. Now we're assuming that + -- you have one "main" version of each wired-in package + -- (the latest version), and the others are backward-compat + -- wrappers that depend on this one. e.g. base-4.0 is the + -- latest, base-3.0 is a compat wrapper depending on base-4.0. + {- + 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 - [] -> pid - (x:_) -> x{ pkgVersion = Version [] [] } - - pkgs1 = deleteOtherWiredInPackages pkgs - - pkgs2 = updateWiredInDependencies pkgs1 - - preload1 = map upd_pid preload + where upd_pkg p + | installedPackageId p `elem` wired_in_ids + = p { package = (package p){ pkgVersion = Version [] [] } } + | otherwise + = p - -- we must return an updated thisPackage, just in case we - -- are actually compiling one of the wired-in packages - Just old_this_pkg = unpackPackageId this_package - new_this_pkg = mkPackageId (upd_pid old_this_pkg) + return $ updateWiredInDependencies pkgs - return (pkgs2, preload1, new_this_pkg) - --- ----------------------------------------------------------------------------- +-- ---------------------------------------------------------------------------- -- --- Eliminate any packages which have dangling dependencies ( --- because the dependency was removed by -ignore-package). +-- Detect any packages that have missing dependencies, and also any +-- mutually-recursive groups of packages (loops in the package graph +-- are not allowed). We do this by taking the least fixpoint of the +-- dependency graph, repeatedly adding packages whose dependencies are +-- satisfied until no more can be added. -- elimDanglingDeps :: DynFlags @@ -460,22 +470,28 @@ elimDanglingDeps -> [PackageId] -- ignored packages -> IO [PackageConfig] -elimDanglingDeps dflags pkgs ignored = - case partition (not.null.snd) (map (getDanglingDeps pkgs ignored) pkgs) of - ([],ps) -> return (map fst ps) - (ps,qs) -> do - mapM_ reportElim ps - elimDanglingDeps dflags (map fst qs) - (ignored ++ map packageConfigId (map fst ps)) +elimDanglingDeps dflags pkgs ignored = go [] 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 + -> Either PackageConfig (PackageConfig, [InstalledPackageId]) + depsAvailable pkgs_ok pkg + | null dangling = Left pkg + | otherwise = Right (pkg, dangling) + where dangling = filter (`notElem` pids) (depends pkg) + pids = map installedPackageId pkgs_ok + reportElim (p, deps) = debugTraceMsg dflags 2 $ - (ptext SLIT("package") <+> pprPkg p <+> - ptext SLIT("will be ignored due to missing dependencies:") $$ - nest 2 (hsep (map (text.showPackageId) deps))) - - getDanglingDeps pkgs ignored p = (p, filter dangling (depends p)) - where dangling pid = mkPackageId pid `elem` ignored + (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 @@ -507,42 +523,53 @@ 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 new_preload_packages = - map package (pickPackages pkgs0 [ p | ExposePackage p <- flags ]) + let preload1 = map installedPackageId $ + pickPackages pkgs0 [ p | ExposePackage p <- flags ] -- hide packages that are subsumed by later versions pkgs2 <- hideOldPackages dflags pkgs1 -- sort out which packages are wired in - (pkgs3, preload1, new_this_pkg) - <- findWiredInPackages dflags pkgs2 new_preload_packages this_package + pkgs3 <- findWiredInPackages dflags pkgs2 let ignored = map packageConfigId $ pickPackages pkgs0 [ p | IgnorePackage p <- flags ] pkgs <- elimDanglingDeps dflags pkgs3 ignored let pkg_db = extendPackageConfigMap emptyPackageConfigMap pkgs - pkgids = map packageConfigId pkgs + ipid_map = listToFM [ (installedPackageId p, packageConfigId p) + | p <- pkgs ] + + lookupIPID ipid@(InstalledPackageId str) + | Just pid <- lookupFM ipid_map ipid = return pid + | otherwise = missingPackageErr str + + preload2 <- mapM lookupIPID preload1 + + let -- 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 - preload2 = nub (filter (/= new_this_pkg) - (basicLinkedPackages ++ map mkPackageId preload1)) + preload3 = nub $ filter (/= this_package) + $ (basicLinkedPackages ++ preload2) -- Close the preload packages with their dependencies - dep_preload <- closeDeps pkg_db (zip preload2 (repeat Nothing)) + dep_preload <- closeDeps pkg_db ipid_map (zip preload3 (repeat Nothing)) let new_dep_preload = filter (`notElem` preload0) dep_preload let pstate = PackageState{ preloadPackages = dep_preload, pkgIdMap = pkg_db, - moduleToPkgConfAll = mkModuleMap pkg_db + moduleToPkgConfAll = mkModuleMap pkg_db, + installedPackageIdMap = ipid_map } - return (pstate, new_dep_preload, new_this_pkg) + return (pstate, new_dep_preload, this_package) -- ----------------------------------------------------------------------------- @@ -557,15 +584,15 @@ mkModuleMap pkg_db = foldr extend_modmap emptyUFM pkgids extend_modmap pkgid modmap = addListToUFM_C (++) modmap - [(m, [(pkg, m `elem` exposed_mods)]) | m <- all_mods] + ([(m, [(pkg, True)]) | m <- exposed_mods] ++ + [(m, [(pkg, False)]) | m <- hidden_mods]) where pkg = expectJust "mkModuleMap" (lookupPackage pkg_db pkgid) - exposed_mods = map mkModuleName (exposedModules pkg) - hidden_mods = map mkModuleName (hiddenModules pkg) - all_mods = exposed_mods ++ hidden_mods + exposed_mods = exposedModules pkg + 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 @@ -578,32 +605,45 @@ pprPkg p = text (showPackageId (package p)) -- of preload (command-line) packages to determine which packages to -- use. +-- | Find all the include directories in these and the preload packages 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)) +-- | Find all the library paths in these and the preload packages 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)) +-- | Find all the link options in these and the preload packages 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 + libs p = packageHsLibs dflags p ++ extraLibraries p + all_opts p = map ("-l" ++) (libs p) ++ ldOptions p + +packageHsLibs :: DynFlags -> PackageConfig -> [String] +packageHsLibs dflags p = map (mkDynName . addSuffix) (hsLibraries p) + where + non_dyn_ways = filter ((/= WayDyn) . wayName) (ways dflags) + -- the name of a shared library is libHSfoo-ghc.so + -- we leave out the _dyn, because it is superfluous + + tag = mkBuildTag (filter (not . wayRTSOnly) non_dyn_ways) + rts_tag = mkBuildTag non_dyn_ways + mkDynName | opt_Static = id | otherwise = (++ ("-ghc" ++ cProjectVersion)) - libs p = map (mkDynName . addSuffix) (hsLibraries p) - ++ extraLibraries p - all_opts p = map ("-l" ++) (libs p) ++ ldOptions p addSuffix rts@"HSrts" = rts ++ (expandTag rts_tag) addSuffix other_lib = other_lib ++ (expandTag tag) @@ -611,18 +651,19 @@ getPackageLinkOpts dflags pkgs = do expandTag t | null t = "" | otherwise = '_':t - return (concat (map all_opts ps)) - +-- | Find all the C-compiler options in these and the preload packages getPackageExtraCcOpts :: DynFlags -> [PackageId] -> IO [String] getPackageExtraCcOpts dflags pkgs = do ps <- getPreloadPackagesAnd dflags pkgs return (concatMap ccOptions ps) +-- | Find all the package framework paths in these and the preload packages getPackageFrameworkPath :: DynFlags -> [PackageId] -> IO [String] getPackageFrameworkPath dflags pkgs = do ps <- getPreloadPackagesAnd dflags pkgs return (nub (filter notNull (concatMap frameworkDirs ps))) +-- | Find all the package frameworks in these and the preload packages getPackageFrameworks :: DynFlags -> [PackageId] -> IO [String] getPackageFrameworks dflags pkgs = do ps <- getPreloadPackagesAnd dflags pkgs @@ -631,45 +672,55 @@ getPackageFrameworks dflags pkgs = do -- ----------------------------------------------------------------------------- -- Package Utils --- | Takes a Module, and if the module is in a package returns --- @(pkgconf,exposed)@ where pkgconf is the PackageConfig for that package, --- and exposed is True if the package exposes the module. +-- | Takes a 'Module', and if the module is in a package returns +-- @(pkgconf, exposed)@ where pkgconf is the PackageConfig for that package, +-- and exposed is @True@ if the package exposes the module. lookupModuleInAllPackages :: DynFlags -> ModuleName -> [(PackageConfig,Bool)] lookupModuleInAllPackages dflags m = case lookupUFM (moduleToPkgConfAll (pkgState dflags)) m of Nothing -> [] Just ps -> ps +-- | Find all the 'PackageConfig' in both the preload packages from 'DynFlags' and corresponding to the list of +-- 'PackageConfig's getPreloadPackagesAnd :: DynFlags -> [PackageId] -> IO [PackageConfig] getPreloadPackagesAnd dflags pkgids = let state = pkgState dflags pkg_map = pkgIdMap state + ipid_map = installedPackageIdMap state preload = preloadPackages state pairs = zip pkgids (repeat Nothing) in do - all_pkgs <- throwErr (foldM (add_package pkg_map) preload pairs) + all_pkgs <- throwErr (foldM (add_package pkg_map ipid_map) preload pairs) return (map (getPackageDetails state) all_pkgs) -- Takes a list of packages, and returns the list with dependencies included, -- in reverse dependency order (a package appears before those it depends on). -closeDeps :: PackageConfigMap -> [(PackageId, Maybe PackageId)] - -> IO [PackageId] -closeDeps pkg_map ps = throwErr (closeDepsErr pkg_map ps) +closeDeps :: PackageConfigMap + -> FiniteMap InstalledPackageId PackageId + -> [(PackageId, Maybe PackageId)] + -> IO [PackageId] +closeDeps pkg_map ipid_map ps = throwErr (closeDepsErr pkg_map ipid_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)] - -> MaybeErr Message [PackageId] -closeDepsErr pkg_map ps = foldM (add_package pkg_map) [] ps +closeDepsErr :: PackageConfigMap + -> FiniteMap InstalledPackageId PackageId + -> [(PackageId,Maybe PackageId)] + -> MaybeErr Message [PackageId] +closeDepsErr pkg_map ipid_map ps = foldM (add_package pkg_map ipid_map) [] ps -- internal helper -add_package :: PackageConfigMap -> [PackageId] -> (PackageId,Maybe PackageId) - -> MaybeErr Message [PackageId] -add_package pkg_db ps (p, mb_parent) +add_package :: PackageConfigMap + -> FiniteMap InstalledPackageId PackageId + -> [PackageId] + -> (PackageId,Maybe PackageId) + -> MaybeErr Message [PackageId] +add_package pkg_db ipid_map ps (p, mb_parent) | p `elem` ps = return ps -- Check if we've already added this package | otherwise = case lookupPackage pkg_db p of @@ -677,19 +728,29 @@ add_package pkg_db ps (p, mb_parent) missingDependencyMsg mb_parent) Just pkg -> do -- Add the package's dependents also - let deps = map mkPackageId (depends pkg) - ps' <- foldM (add_package pkg_db) ps (zip deps (repeat (Just p))) + ps' <- foldM add_package_ipid ps (depends pkg) return (p : ps') + where + add_package_ipid ps ipid@(InstalledPackageId str) + | Just pid <- lookupFM ipid_map ipid + = add_package pkg_db ipid_map ps (pid, Just p) + | otherwise + = Failed (missingPackageMsg str <> missingDependencyMsg mb_parent) + +missingPackageErr :: String -> IO a +missingPackageErr p = ghcError (CmdLineError (showSDoc (missingPackageMsg p))) -missingPackageErr p = throwDyn (CmdLineError (showSDoc (missingPackageMsg p))) -missingPackageMsg p = ptext SLIT("unknown package:") <+> text 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)) -- ----------------------------------------------------------------------------- +-- | Will the 'Name' come from a dynamically linked library? isDllName :: PackageId -> Name -> Bool isDllName this_pkg name | opt_Static = False @@ -699,10 +760,12 @@ isDllName this_pkg name -- ----------------------------------------------------------------------------- -- Displaying packages +-- | Show package info on console, if verbosity is >= 3 dumpPackages :: DynFlags -> IO () --- Show package info on console, if verbosity is >= 3 dumpPackages dflags = do let pkg_map = pkgIdMap (pkgState dflags) putMsg dflags $ - vcat (map (text.showInstalledPackageInfo) (eltsUFM pkg_map)) + vcat (map (text . showInstalledPackageInfo + . packageConfigToInstalledPackageInfo) + (eltsUFM pkg_map)) \end{code}