X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fmain%2FPackages.lhs;h=06cd573bc96f27b31e8403dc0950e30ca7ee07e6;hb=636c2750c90e540ed3d4fb66c8dd4dae876945e7;hp=92a5153b97338fd63e5a423752fe344b211efdcd;hpb=1dc3f29333773551f60dce638ed7309041d7c800;p=ghc-hetmet.git diff --git a/compiler/main/Packages.lhs b/compiler/main/Packages.lhs index 92a5153..06cd573 100644 --- a/compiler/main/Packages.lhs +++ b/compiler/main/Packages.lhs @@ -60,6 +60,7 @@ import System.Directory import System.FilePath import Control.Monad import Data.List as List +import qualified Data.Set as Set -- --------------------------------------------------------------------------- -- The Package state @@ -127,6 +128,8 @@ type PackageConfigMap = UniqFM PackageConfig type InstalledPackageIdMap = FiniteMap InstalledPackageId PackageId +type InstalledPackageIndex = FiniteMap InstalledPackageId PackageConfig + emptyPackageConfigMap :: PackageConfigMap emptyPackageConfigMap = emptyUFM @@ -191,7 +194,7 @@ readPackageConfigs dflags = do -- the we tack on the system paths. pkgs <- mapM (readPackageConfig dflags) - (reverse pkgconfs ++ reverse (extraPkgConfs dflags)) + (pkgconfs ++ reverse (extraPkgConfs dflags)) -- later packages shadow earlier ones. extraPkgConfs -- is in the opposite order to the flags on the -- command line. @@ -217,7 +220,7 @@ getSystemPackageConfigs dflags = do if exist then return [pkgconf] else return [] `catchIO` (\_ -> return []) - return (user_pkgconf ++ [system_pkgconf]) + return (system_pkgconf : user_pkgconf) readPackageConfig :: DynFlags -> FilePath -> IO [PackageConfig] readPackageConfig dflags conf_file = do @@ -533,7 +536,7 @@ findBroken pkgs = go [] emptyFM pkgs where new_ipids = addListToFM ipids [ (installedPackageId p, p) | p <- new_avail ] - depsAvailable :: FiniteMap InstalledPackageId PackageConfig + depsAvailable :: InstalledPackageIndex -> PackageConfig -> Either PackageConfig (PackageConfig, [InstalledPackageId]) depsAvailable ipids pkg @@ -545,21 +548,28 @@ findBroken pkgs = go [] emptyFM pkgs -- 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 +-- package name/version. Additionally, a package may be preferred if +-- it is in the transitive closure of packages selected using -package-id +-- flags. +shadowPackages :: [PackageConfig] -> [InstalledPackageId] -> UnusablePackages +shadowPackages pkgs preferred + = let (shadowed,_) = foldl check ([],emptyUFM) pkgs in listToFM shadowed where - check (pkgmap,shadowed) pkg - = (addToUFM pkgmap (packageConfigId pkg) pkg, shadowed') - where - shadowed' + check (shadowed,pkgmap) pkg | Just oldpkg <- lookupUFM pkgmap (packageConfigId pkg) - = (installedPackageId oldpkg, ShadowedBy (installedPackageId pkg)) - :shadowed + , let + ipid_new = installedPackageId pkg + ipid_old = installedPackageId oldpkg + -- + , ipid_old /= ipid_new + = if ipid_old `elem` preferred + then ( (ipid_new, ShadowedBy ipid_old) : shadowed, pkgmap ) + else ( (ipid_old, ShadowedBy ipid_new) : shadowed, pkgmap' ) | otherwise - = shadowed + = (shadowed, pkgmap') + where + pkgmap' = addToUFM pkgmap (packageConfigId pkg) pkg -- ----------------------------------------------------------------------------- @@ -576,6 +586,20 @@ ignorePackages flags pkgs = listToFM (concatMap doit flags) doit _ = panic "ignorePackages" -- ----------------------------------------------------------------------------- + +depClosure :: InstalledPackageIndex + -> [InstalledPackageId] + -> [InstalledPackageId] +depClosure index ipids = closure emptyFM ipids + where + closure set [] = keysFM set + closure set (ipid : ipids) + | ipid `elemFM` set = closure set ipids + | Just p <- lookupFM index ipid = closure (addToFM set ipid p) + (depends p ++ ipids) + | otherwise = closure set ipids + +-- ----------------------------------------------------------------------------- -- When all the command-line options are in, we can process our package -- settings and populate the package state. @@ -592,16 +616,77 @@ mkPackageState mkPackageState dflags pkgs0 preload0 this_package = do +{- + Plan. + + 1. P = transitive closure of packages selected by -package-id + + 2. Apply shadowing. When there are multiple packages with the same + sourcePackageId, + * if one is in P, use that one + * otherwise, use the one highest in the package stack + [ + rationale: we cannot use two packages with the same sourcePackageId + in the same program, because sourcePackageId is the symbol prefix. + Hence we must select a consistent set of packages to use. We have + a default algorithm for doing this: packages higher in the stack + shadow those lower down. This default algorithm can be overriden + by giving explicit -package-id flags; then we have to take these + preferences into account when selecting which other packages are + made available. + + Our simple algorithm throws away some solutions: there may be other + consistent sets that would satisfy the -package flags, but it's + not GHC's job to be doing constraint solving. + ] + + 3. remove packages selected by -ignore-package + + 4. remove any packages with missing dependencies, or mutually recursive + dependencies. + + 5. report (with -v) any packages that were removed by steps 2-4 + + 6. apply flags to set exposed/hidden on the resulting packages + - if any flag refers to a package which was removed by 2-4, then + we can give an error message explaining why + + 7. hide any packages which are superseded by later exposed packages +-} + let flags = reverse (packageFlags dflags) + + -- pkgs0 with duplicate packages filtered out. This is + -- important: it is possible for a package in the global package + -- DB to have the same IPID as a package in the user DB, and + -- we want the latter to take precedence. This is not the same + -- as shadowing (below), since in this case the two packages + -- have the same ABI and are interchangeable. + -- + -- #4072: note that we must retain the ordering of the list here + -- so that shadowing behaves as expected when we apply it later. + pkgs0_unique = snd $ foldr del (Set.empty,[]) pkgs0 + where del p (s,ps) + | pid `Set.member` s = (s,ps) + | otherwise = (Set.insert pid s, p:ps) + where pid = installedPackageId p + -- XXX this is just a variant of nub + + ipid_map = listToFM [ (installedPackageId p, p) | p <- pkgs0 ] + + ipid_selected = depClosure ipid_map [ InstalledPackageId i + | ExposePackageId i <- flags ] + (ignore_flags, other_flags) = partition is_ignore flags is_ignore IgnorePackage{} = True is_ignore _ = False - shadowed = shadowPackages pkgs0 - ignored = ignorePackages ignore_flags pkgs0 + shadowed = shadowPackages pkgs0_unique ipid_selected + + ignored = ignorePackages ignore_flags pkgs0_unique - pkgs0' = filter (not . (`elemFM` (plusFM shadowed ignored)) . installedPackageId) pkgs0 + pkgs0' = filter (not . (`elemFM` (plusFM shadowed ignored)) . installedPackageId) pkgs0_unique broken = findBroken pkgs0' unusable = shadowed `plusFM` ignored `plusFM` broken @@ -611,7 +696,7 @@ mkPackageState dflags pkgs0 preload0 this_package = do -- Modify the package database according to the command-line flags -- (-package, -hide-package, -ignore-package, -hide-all-packages). -- - pkgs1 <- foldM (applyPackageFlag unusable) pkgs0 other_flags + pkgs1 <- foldM (applyPackageFlag unusable) pkgs0_unique other_flags let pkgs2 = filter (not . (`elemFM` unusable) . installedPackageId) pkgs1 -- Here we build up a set of the packages mentioned in -package @@ -734,12 +819,20 @@ collectLinkOpts dflags ps = concat (map all_opts ps) packageHsLibs :: DynFlags -> PackageConfig -> [String] packageHsLibs dflags p = map (mkDynName . addSuffix) (hsLibraries p) where - non_dyn_ways = filter ((/= WayDyn) . wayName) (ways dflags) + ways0 = ways dflags + + ways1 = filter ((/= WayDyn) . wayName) ways0 -- 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 + -- debug RTS includes support for -eventlog + ways2 | WayDebug `elem` map wayName ways1 + = filter ((/= WayEventLog) . wayName) ways1 + | otherwise + = ways1 + + tag = mkBuildTag (filter (not . wayRTSOnly) ways2) + rts_tag = mkBuildTag ways2 mkDynName | opt_Static = id | otherwise = (++ ("-ghc" ++ cProjectVersion))