diff options
author | Edward Z. Yang <ezyang@cs.stanford.edu> | 2015-08-25 11:24:28 -0700 |
---|---|---|
committer | Edward Z. Yang <ezyang@cs.stanford.edu> | 2015-10-14 21:39:47 -0700 |
commit | 5b0191f74ab05b187f81ea037623338a615b1619 (patch) | |
tree | 5f46c51ec53b5ecf16e4ca224aa13d19ebbe9df3 | |
parent | 729bf08e8311736aec7dc894b640a3a8d7dd24ad (diff) | |
download | haskell-5b0191f74ab05b187f81ea037623338a615b1619.tar.gz |
Update Cabal to HEAD, IPID renamed to Component ID.
This commit contains a Cabal submodule update which unifies installed
package IDs and package keys under a single notion, a Component ID.
We update GHC to keep follow this unification. However, this commit
does NOT rename installed package ID to component ID and package key to
unit ID; the plan is to do that in a companion commit.
- Compiler info now has "Requires unified installed package IDs"
- 'exposed' is now expected to contain unit keys, not IPIDs.
- Shadowing is no more. We now just have a very simple strategy
to deal with duplicate unit keys in combined package databases:
if their ABIs are the same, use the latest one; otherwise error.
Package databases maintain the invariant that there can only
be one entry of a unit ID.
Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu>
Test Plan: validate
Reviewers: simonpj, austin, bgamari, hvr, goldfire
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1184
GHC Trac Issues: #10714
44 files changed, 325 insertions, 412 deletions
diff --git a/compiler/ghci/Linker.hs b/compiler/ghci/Linker.hs index 29968f5b1a..6a07e44a93 100644 --- a/compiler/ghci/Linker.hs +++ b/compiler/ghci/Linker.hs @@ -1091,8 +1091,7 @@ linkPackages' dflags new_pks pls = do | Just pkg_cfg <- lookupPackage dflags new_pkg = do { -- Link dependents first - pkgs' <- link pkgs [ resolveInstalledPackageId dflags ipid - | ipid <- depends pkg_cfg ] + pkgs' <- link pkgs (depends pkg_cfg) -- Now link the package itself ; linkPackage dflags pkg_cfg ; return (new_pkg : pkgs') } diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 1f04f60562..c03f076ef0 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -1913,7 +1913,7 @@ parseSigOf str = case filter ((=="").snd) (readP_to_S parse str) of m <- tok $ parseModule return (n, m) parseModule = do - pk <- munch1 (\c -> isAlphaNum c || c `elem` "-_") + pk <- munch1 (\c -> isAlphaNum c || c `elem` "-_.") _ <- R.char ':' m <- parseModuleName return (mkModule (stringToPackageKey pk) m) @@ -4072,6 +4072,7 @@ compilerInfo dflags ("Support parallel --make", "YES"), ("Support reexported-modules", "YES"), ("Support thinning and renaming package flags", "YES"), + ("Requires unified installed package IDs", "YES"), ("Uses package keys", "YES"), ("Dynamic by default", if dYNAMIC_BY_DEFAULT dflags then "YES" else "NO"), diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs index 2c426d9b36..31d22eb3f0 100644 --- a/compiler/main/HscTypes.hs +++ b/compiler/main/HscTypes.hs @@ -1543,15 +1543,8 @@ Note [Printing package keys] In the old days, original names were tied to PackageIds, which directly corresponded to the entities that users wrote in Cabal files, and were perfectly suitable for printing when we need to disambiguate packages. However, with -PackageKey, the situation is different. First, the key is not a human readable -at all, so we need to consult the package database to find the appropriate -PackageId to display. Second, there may be multiple copies of a library visible -with the same PackageId, in which case we need to disambiguate. For now, -we just emit the actual package key (which the user can go look up); however, -another scheme is to (recursively) say which dependencies are different. - -NB: When we extend package keys to also have holes, we will have to disambiguate -those as well. +PackageKey, the situation can be different: if the key is instantiated with +some holes, we should try to give the user some more useful information. -} -- | Creates some functions that work out the best ways to format diff --git a/compiler/main/PackageConfig.hs b/compiler/main/PackageConfig.hs index 9e9775bc04..4ba8344e77 100644 --- a/compiler/main/PackageConfig.hs +++ b/compiler/main/PackageConfig.hs @@ -128,7 +128,6 @@ pprPackageConfig InstalledPackageInfo {..} = field "name" (ppr packageName), field "version" (text (showVersion packageVersion)), field "id" (ppr installedPackageId), - field "key" (ppr packageKey), field "exposed" (ppr exposed), field "exposed-modules" (if all isExposedModule exposedModules diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs index bb0aba241e..3b9526129f 100644 --- a/compiler/main/Packages.hs +++ b/compiler/main/Packages.hs @@ -18,7 +18,6 @@ module Packages ( -- * Querying the package config lookupPackage, - resolveInstalledPackageId, searchPackageId, getPackageDetails, listVisibleModuleNames, @@ -249,24 +248,17 @@ data PackageState = PackageState { -- | This is a full map from 'ModuleName' to all modules which may possibly -- be providing it. These providers may be hidden (but we'll still want -- to report them in error messages), or it may be an ambiguous import. - moduleToPkgConfAll :: ModuleToPkgConfAll, - - -- | This is a map from 'InstalledPackageId' to 'PackageKey', since GHC - -- internally deals in package keys but the database may refer to installed - -- package IDs. - installedPackageIdMap :: InstalledPackageIdMap + moduleToPkgConfAll :: ModuleToPkgConfAll } emptyPackageState :: PackageState emptyPackageState = PackageState { pkgIdMap = emptyUFM, preloadPackages = [], - moduleToPkgConfAll = Map.empty, - installedPackageIdMap = Map.empty + moduleToPkgConfAll = Map.empty } -type InstalledPackageIdMap = Map InstalledPackageId PackageKey -type InstalledPackageIndex = Map InstalledPackageId PackageConfig +type InstalledPackageIndex = Map PackageKey PackageConfig -- | Empty package configuration map emptyPackageConfigMap :: PackageConfigMap @@ -304,12 +296,6 @@ getPackageDetails dflags pid = listPackageConfigMap :: DynFlags -> [PackageConfig] listPackageConfigMap dflags = eltsUFM (pkgIdMap (pkgState dflags)) --- | Looks up a 'PackageKey' given an 'InstalledPackageId' -resolveInstalledPackageId :: DynFlags -> InstalledPackageId -> PackageKey -resolveInstalledPackageId dflags ipid = - expectJust "resolveInstalledPackageId" - (Map.lookup ipid (installedPackageIdMap (pkgState dflags))) - -- ---------------------------------------------------------------------------- -- Loading the package db files and building up the package state @@ -602,7 +588,7 @@ packageFlagErr dflags flag reasons text "(use -v for more information)") ppr_reasons = vcat (map ppr_reason reasons) ppr_reason (p, reason) = - pprReason (ppr (installedPackageId p) <+> text "is") reason + pprReason (ppr (packageKey p) <+> text "is") reason pprFlag :: PackageFlag -> SDoc pprFlag flag = case flag of @@ -628,11 +614,13 @@ pprFlag flag = case flag of wired_in_pkgids :: [String] wired_in_pkgids = map packageKeyString wiredInPackageKeys +type WiredPackagesMap = Map PackageKey PackageKey + findWiredInPackages :: DynFlags -> [PackageConfig] -- database -> VisibilityMap -- info on what packages are visible - -> IO ([PackageConfig], VisibilityMap) + -> IO ([PackageConfig], VisibilityMap, WiredPackagesMap) findWiredInPackages dflags pkgs vis_map = do -- @@ -686,14 +674,14 @@ findWiredInPackages dflags pkgs vis_map = do ptext (sLit "wired-in package ") <> text wired_pkg <> ptext (sLit " mapped to ") - <> ppr (installedPackageId pkg) + <> ppr (packageKey pkg) return (Just pkg) mb_wired_in_pkgs <- mapM (findWiredInPackage pkgs) wired_in_pkgids let wired_in_pkgs = catMaybes mb_wired_in_pkgs - wired_in_ids = map installedPackageId wired_in_pkgs + wired_in_ids = map packageKey wired_in_pkgs -- this is old: we used to assume that if there were -- multiple versions of wired-in packages installed that @@ -708,14 +696,28 @@ findWiredInPackages dflags pkgs vis_map = do && package p `notElem` map fst wired_in_ids -} - updateWiredInDependencies pkgs = map upd_pkg pkgs + wiredInMap :: Map PackageKey PackageKey + wiredInMap = foldl' add_mapping Map.empty pkgs + where add_mapping m pkg + | let key = packageKey pkg + , key `elem` wired_in_ids + = Map.insert key (stringToPackageKey (packageNameString pkg)) m + | otherwise = m + + updateWiredInDependencies pkgs = map (upd_deps . upd_pkg) pkgs where upd_pkg pkg - | installedPackageId pkg `elem` wired_in_ids + | packageKey pkg `elem` wired_in_ids = pkg { packageKey = stringToPackageKey (packageNameString pkg) } | otherwise = pkg + upd_deps pkg = pkg { + depends = map upd_wired_in (depends pkg) + } + upd_wired_in key + | Just key' <- Map.lookup key wiredInMap = key' + | otherwise = key updateVisibilityMap vis_map = foldl' f vis_map wired_in_pkgs where f vm p = case lookupUFM vis_map (packageConfigId p) of @@ -724,16 +726,15 @@ findWiredInPackages dflags pkgs vis_map = do (packageNameString p)) r - return (updateWiredInDependencies pkgs, updateVisibilityMap vis_map) + return (updateWiredInDependencies pkgs, updateVisibilityMap vis_map, wiredInMap) -- ---------------------------------------------------------------------------- data UnusablePackageReason = IgnoredWithFlag - | MissingDependencies [InstalledPackageId] - | ShadowedBy InstalledPackageId + | MissingDependencies [PackageKey] -type UnusablePackages = Map InstalledPackageId +type UnusablePackages = Map PackageKey (PackageConfig, UnusablePackageReason) pprReason :: SDoc -> UnusablePackageReason -> SDoc @@ -744,8 +745,6 @@ pprReason pref reason = case reason of pref <+> ptext (sLit "unusable due to missing or recursive dependencies:") $$ nest 2 (hsep (map ppr deps)) - ShadowedBy ipid -> - pref <+> ptext (sLit "shadowed by package ") <> ppr ipid reportUnusable :: DynFlags -> UnusablePackages -> IO () reportUnusable dflags pkgs = mapM_ report (Map.toList pkgs) @@ -770,62 +769,31 @@ findBroken pkgs = go [] Map.empty pkgs go avail ipids not_avail = case partitionWith (depsAvailable ipids) not_avail of ([], not_avail) -> - Map.fromList [ (installedPackageId p, (p, MissingDependencies deps)) + Map.fromList [ (packageKey p, (p, MissingDependencies deps)) | (p,deps) <- not_avail ] (new_avail, not_avail) -> go (new_avail ++ avail) new_ipids (map fst not_avail) where new_ipids = Map.insertList - [ (installedPackageId p, p) | p <- new_avail ] + [ (packageKey p, p) | p <- new_avail ] ipids depsAvailable :: InstalledPackageIndex -> PackageConfig - -> Either PackageConfig (PackageConfig, [InstalledPackageId]) + -> Either PackageConfig (PackageConfig, [PackageKey]) depsAvailable ipids pkg | null dangling = Left pkg | otherwise = Right (pkg, dangling) where dangling = filter (not . (`Map.member` ipids)) (depends pkg) -- ----------------------------------------------------------------------------- --- Eliminate shadowed packages, giving the user some feedback - --- later packages in the list should shadow earlier ones with the same --- package name/version. Additionally, a package may be preferred if --- it is in the transitive closure of packages selected using -package-id --- flags. -type UnusablePackage = (PackageConfig, UnusablePackageReason) -shadowPackages :: [PackageConfig] -> [InstalledPackageId] -> UnusablePackages -shadowPackages pkgs preferred - = let (shadowed,_) = foldl check ([],emptyUFM) pkgs - in Map.fromList shadowed - where - check :: ([(InstalledPackageId, UnusablePackage)], UniqFM PackageConfig) - -> PackageConfig - -> ([(InstalledPackageId, UnusablePackage)], UniqFM PackageConfig) - check (shadowed,pkgmap) pkg - | Just oldpkg <- lookupUFM pkgmap pkgid - , let - ipid_new = installedPackageId pkg - ipid_old = installedPackageId oldpkg - -- - , ipid_old /= ipid_new - = if ipid_old `elem` preferred - then ((ipid_new, (pkg, ShadowedBy ipid_old)) : shadowed, pkgmap) - else ((ipid_old, (oldpkg, ShadowedBy ipid_new)) : shadowed, pkgmap') - | otherwise - = (shadowed, pkgmap') - where - pkgid = packageKeyFS (packageKey pkg) - pkgmap' = addToUFM pkgmap pkgid pkg - --- ----------------------------------------------------------------------------- +-- Ignore packages ignorePackages :: [PackageFlag] -> [PackageConfig] -> UnusablePackages ignorePackages flags pkgs = Map.fromList (concatMap doit flags) where doit (IgnorePackage str) = case partition (matchingStr str) pkgs of - (ps, _) -> [ (installedPackageId p, (p, IgnoredWithFlag)) + (ps, _) -> [ (packageKey p, (p, IgnoredWithFlag)) | p <- ps ] -- missing package is not an error for -ignore-package, -- because a common usage is to -ignore-package P as @@ -833,20 +801,6 @@ ignorePackages flags pkgs = Map.fromList (concatMap doit flags) doit _ = panic "ignorePackages" -- ----------------------------------------------------------------------------- - -depClosure :: InstalledPackageIndex - -> [InstalledPackageId] - -> [InstalledPackageId] -depClosure index ipids = closure Map.empty ipids - where - closure set [] = Map.keys set - closure set (ipid : ipids) - | ipid `Map.member` set = closure set ipids - | Just p <- Map.lookup ipid index = closure (Map.insert ipid p set) - (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. @@ -868,80 +822,66 @@ mkPackageState dflags0 pkgs0 preload0 = do {- Plan. - 1. P = transitive closure of packages selected by -package-id - - 2. Apply shadowing. When there are multiple packages with the same - packageKey, - * 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 packageKey - in the same program, because packageKey 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 + 1. When there are multiple packages with the same + installed package ID, if they have the same ABI hash, use the one + highest in the package stack. Otherwise, error. + + 2. remove packages selected by -ignore-package + + 3. remove any packages with missing dependencies, or mutually recursive dependencies. - 5. report (with -v) any packages that were removed by steps 2-4 + 4. report (with -v) any packages that were removed by steps 2-4 - 6. apply flags to set exposed/hidden on the resulting packages + 5. 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 + 6. 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. + -- DB to have the same key as a package in the user DB, and + -- we want the latter to take precedence. -- - -- #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 = Map.fromList [ (installedPackageId p, p) | p <- pkgs0 ] - - ipid_selected = depClosure ipid_map - [ InstalledPackageId (mkFastString i) - | ExposePackage (PackageIdArg i) _ <- flags ] - + -- NB: We have to check that the ABIs of the old and new packages + -- are equal; if they are not that's a fatal error. + -- + -- TODO: might be useful to report when this shadowing occurs + (_, pkgs0_unique, abis) = foldr del (Set.empty,[],Map.empty) pkgs0 + where del p (s,ps,a) + | key `Set.member` s = (s,ps,a') + | otherwise = (Set.insert key s, p:ps, a') + where key = packageKey p + a' = Map.insertWith Set.union key + (Set.singleton (abiHash p)) a + failed_abis = [ (key, Set.toList as) + | (key, as) <- Map.toList abis + , Set.size as > 1 ] + + unless (null failed_abis) $ do + throwGhcException (CmdLineError (showSDoc dflags + (text "package db: duplicate packages with incompatible ABIs:" $$ + nest 4 (vcat [ ppr key <+> text "has ABIs" <> colon <+> + hsep (punctuate comma (map text as)) + | (key, as) <- failed_abis])))) + + let flags = reverse (packageFlags dflags) (ignore_flags, other_flags) = partition is_ignore flags is_ignore IgnorePackage{} = True is_ignore _ = False - shadowed = shadowPackages pkgs0_unique ipid_selected ignored = ignorePackages ignore_flags pkgs0_unique - isBroken = (`Map.member` (Map.union shadowed ignored)).installedPackageId + isBroken = (`Map.member` ignored).packageKey pkgs0' = filter (not . isBroken) pkgs0_unique broken = findBroken pkgs0' - unusable = shadowed `Map.union` ignored `Map.union` broken - pkgs1 = filter (not . (`Map.member` unusable) . installedPackageId) pkgs0' + unusable = ignored `Map.union` broken + pkgs1 = filter (not . (`Map.member` unusable) . packageKey) pkgs0' reportUnusable dflags unusable @@ -980,7 +920,7 @@ mkPackageState dflags0 pkgs0 preload0 = do -- package arguments we need to key against the old versions. We also -- have to update the visibility map in the process. -- - (pkgs3, vis_map) <- findWiredInPackages dflags pkgs2 vis_map2 + (pkgs3, vis_map, wired_map) <- findWiredInPackages dflags pkgs2 vis_map2 -- -- Here we build up a set of the packages mentioned in -package @@ -989,7 +929,9 @@ mkPackageState dflags0 pkgs0 preload0 = do -- should contain at least rts & base, which is why we pretend that -- the command line contains -package rts & -package base. -- - let preload1 = [ installedPackageId p | f <- flags, p <- get_exposed f ] + let preload1 = [ let key = packageKey p + in fromMaybe key (Map.lookup key wired_map) + | f <- flags, p <- get_exposed f ] get_exposed (ExposePackage a _) = take 1 . sortByVersion . filter (matching a) @@ -998,14 +940,7 @@ mkPackageState dflags0 pkgs0 preload0 = do let pkg_db = extendPackageConfigMap emptyPackageConfigMap pkgs3 - ipid_map = Map.fromList [ (installedPackageId p, packageConfigId p) - | p <- pkgs3 ] - - lookupIPID ipid - | Just pid <- Map.lookup ipid ipid_map = return pid - | otherwise = missingPackageErr dflags ipid - - preload2 <- mapM lookupIPID preload1 + let preload2 = preload1 let -- add base & rts to the preload packages @@ -1021,14 +956,13 @@ mkPackageState dflags0 pkgs0 preload0 = do $ (basicLinkedPackages ++ preload2) -- Close the preload packages with their dependencies - dep_preload <- closeDeps dflags pkg_db ipid_map (zip preload3 (repeat Nothing)) + dep_preload <- closeDeps dflags pkg_db (zip preload3 (repeat Nothing)) let new_dep_preload = filter (`notElem` preload0) dep_preload let pstate = PackageState{ preloadPackages = dep_preload, pkgIdMap = pkg_db, - moduleToPkgConfAll = mkModuleToPkgConfAll dflags pkg_db ipid_map vis_map, - installedPackageIdMap = ipid_map + moduleToPkgConfAll = mkModuleToPkgConfAll dflags pkg_db vis_map } return (pstate, new_dep_preload, this_package) @@ -1039,10 +973,9 @@ mkPackageState dflags0 pkgs0 preload0 = do mkModuleToPkgConfAll :: DynFlags -> PackageConfigMap - -> InstalledPackageIdMap -> VisibilityMap -> ModuleToPkgConfAll -mkModuleToPkgConfAll dflags pkg_db ipid_map vis_map = +mkModuleToPkgConfAll dflags pkg_db vis_map = foldl' extend_modmap emptyMap (eltsUFM pkg_db) where emptyMap = Map.empty @@ -1078,9 +1011,8 @@ mkModuleToPkgConfAll dflags pkg_db ipid_map vis_map = let (pk', m', pkg', origin') = case exposedReexport of Nothing -> (pk, m, pkg, fromExposedModules e) - Just (OriginalModule ipid' m') -> - let pk' = expectJust "mkModuleToPkgConf" (Map.lookup ipid' ipid_map) - pkg' = pkg_lookup pk' + Just (OriginalModule pk' m') -> + let pkg' = pkg_lookup pk' in (pk', m', pkg', fromReexportedModules e pkg') return (m, sing pk' m' pkg' origin') @@ -1298,22 +1230,20 @@ 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 dflags (foldM (add_package pkg_map ipid_map) preload pairs) + all_pkgs <- throwErr dflags (foldM (add_package pkg_map) preload pairs) return (map (getPackageDetails dflags) 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 :: DynFlags -> PackageConfigMap - -> Map InstalledPackageId PackageKey -> [(PackageKey, Maybe PackageKey)] -> IO [PackageKey] -closeDeps dflags pkg_map ipid_map ps - = throwErr dflags (closeDepsErr pkg_map ipid_map ps) +closeDeps dflags pkg_map ps + = throwErr dflags (closeDepsErr pkg_map ps) throwErr :: DynFlags -> MaybeErr MsgDoc a -> IO a throwErr dflags m @@ -1322,18 +1252,16 @@ throwErr dflags m Succeeded r -> return r closeDepsErr :: PackageConfigMap - -> Map InstalledPackageId PackageKey -> [(PackageKey,Maybe PackageKey)] -> MaybeErr MsgDoc [PackageKey] -closeDepsErr pkg_map ipid_map ps = foldM (add_package pkg_map ipid_map) [] ps +closeDepsErr pkg_map ps = foldM (add_package pkg_map) [] ps -- internal helper add_package :: PackageConfigMap - -> Map InstalledPackageId PackageKey -> [PackageKey] -> (PackageKey,Maybe PackageKey) -> MaybeErr MsgDoc [PackageKey] -add_package pkg_db ipid_map ps (p, mb_parent) +add_package pkg_db ps (p, mb_parent) | p `elem` ps = return ps -- Check if we've already added this package | otherwise = case lookupPackage' pkg_db p of @@ -1341,19 +1269,11 @@ add_package pkg_db ipid_map ps (p, mb_parent) missingDependencyMsg mb_parent) Just pkg -> do -- Add the package's dependents also - ps' <- foldM add_package_ipid ps (depends pkg) + ps' <- foldM add_unit_key ps (depends pkg) return (p : ps') where - add_package_ipid ps ipid - | Just pid <- Map.lookup ipid ipid_map - = add_package pkg_db ipid_map ps (pid, Just p) - | otherwise - = Failed (missingPackageMsg ipid - <> missingDependencyMsg mb_parent) - -missingPackageErr :: Outputable pkgid => DynFlags -> pkgid -> IO a -missingPackageErr dflags p - = throwGhcExceptionIO (CmdLineError (showSDoc dflags (missingPackageMsg p))) + add_unit_key ps key + = add_package pkg_db ps (key, Just p) missingPackageMsg :: Outputable pkgid => pkgid -> SDoc missingPackageMsg p = ptext (sLit "unknown package:") <+> ppr p @@ -1420,7 +1340,7 @@ pprPackagesWith pprIPI dflags = -- be different from the package databases (exposure, trust) pprPackagesSimple :: DynFlags -> SDoc pprPackagesSimple = pprPackagesWith pprIPI - where pprIPI ipi = let InstalledPackageId i = installedPackageId ipi + where pprIPI ipi = let i = packageKeyFS (packageKey ipi) e = if exposed ipi then text "E" else text " " t = if trusted ipi then text "T" else text " " in e <> t <> text " " <> ftext i diff --git a/libraries/Cabal b/libraries/Cabal -Subproject e6304ff660ca629b1b664f0848a601959e31cb3 +Subproject b083151f2a01ad7245f21502fd20f21189ab766 diff --git a/libraries/ghc-boot/GHC/PackageDb.hs b/libraries/ghc-boot/GHC/PackageDb.hs index 672b7ebbe3..1f6b54f151 100644 --- a/libraries/ghc-boot/GHC/PackageDb.hs +++ b/libraries/ghc-boot/GHC/PackageDb.hs @@ -73,7 +73,8 @@ data InstalledPackageInfo instpkgid srcpkgid srcpkgname pkgkey modulename packageName :: srcpkgname, packageVersion :: Version, packageKey :: pkgkey, - depends :: [instpkgid], + abiHash :: String, + depends :: [pkgkey], importDirs :: [FilePath], hsLibraries :: [String], extraLibraries :: [String], @@ -87,9 +88,9 @@ data InstalledPackageInfo instpkgid srcpkgid srcpkgname pkgkey modulename includeDirs :: [FilePath], haddockInterfaces :: [FilePath], haddockHTMLs :: [FilePath], - exposedModules :: [ExposedModule instpkgid modulename], + exposedModules :: [ExposedModule pkgkey modulename], hiddenModules :: [modulename], - instantiatedWith :: [(modulename,OriginalModule instpkgid modulename)], + instantiatedWith :: [(modulename,OriginalModule pkgkey modulename)], exposed :: Bool, trusted :: Bool } @@ -99,9 +100,9 @@ data InstalledPackageInfo instpkgid srcpkgid srcpkgname pkgkey modulename -- plus module name) representing where a module was *originally* defined -- (i.e., the 'exposedReexport' field of the original ExposedModule entry should -- be 'Nothing'). Invariant: an OriginalModule never points to a reexport. -data OriginalModule instpkgid modulename +data OriginalModule pkgkey modulename = OriginalModule { - originalPackageId :: instpkgid, + originalPackageId :: pkgkey, originalModuleName :: modulename } deriving (Eq, Show) @@ -128,11 +129,11 @@ data OriginalModule instpkgid modulename -- We use two 'Maybe' data types instead of an ADT with four branches or -- four fields because this representation allows us to treat -- reexports/signatures uniformly. -data ExposedModule instpkgid modulename +data ExposedModule pkgkey modulename = ExposedModule { exposedName :: modulename, - exposedReexport :: Maybe (OriginalModule instpkgid modulename), - exposedSignature :: Maybe (OriginalModule instpkgid modulename) + exposedReexport :: Maybe (OriginalModule pkgkey modulename), + exposedSignature :: Maybe (OriginalModule pkgkey modulename) } deriving (Eq, Show) @@ -150,6 +151,7 @@ emptyInstalledPackageInfo = packageName = fromStringRep BS.empty, packageVersion = Version [] [], packageKey = fromStringRep BS.empty, + abiHash = "", depends = [], importDirs = [], hsLibraries = [], @@ -301,7 +303,7 @@ instance (BinaryStringRep a, BinaryStringRep b, BinaryStringRep c, put (InstalledPackageInfo installedPackageId sourcePackageId packageName packageVersion packageKey - depends importDirs + abiHash depends importDirs hsLibraries extraLibraries extraGHCiLibraries libraryDirs frameworks frameworkDirs ldOptions ccOptions @@ -314,6 +316,7 @@ instance (BinaryStringRep a, BinaryStringRep b, BinaryStringRep c, put (toStringRep packageName) put packageVersion put (toStringRep packageKey) + put abiHash put (map toStringRep depends) put importDirs put hsLibraries @@ -340,6 +343,7 @@ instance (BinaryStringRep a, BinaryStringRep b, BinaryStringRep c, packageName <- get packageVersion <- get packageKey <- get + abiHash <- get depends <- get importDirs <- get hsLibraries <- get @@ -364,6 +368,7 @@ instance (BinaryStringRep a, BinaryStringRep b, BinaryStringRep c, (fromStringRep sourcePackageId) (fromStringRep packageName) packageVersion (fromStringRep packageKey) + abiHash (map fromStringRep depends) importDirs hsLibraries extraLibraries extraGHCiLibraries libraryDirs diff --git a/rts/package.conf.in b/rts/package.conf.in index 2670faeb57..0a096583c5 100644 --- a/rts/package.conf.in +++ b/rts/package.conf.in @@ -5,7 +5,7 @@ name: rts version: 1.0 -id: builtin_rts +id: rts key: rts license: BSD3 maintainer: glasgow-haskell-users@haskell.org diff --git a/testsuite/.gitignore b/testsuite/.gitignore index a1481ad1ce..a2b645429b 100644 --- a/testsuite/.gitignore +++ b/testsuite/.gitignore @@ -128,6 +128,7 @@ mk/ghcconfig*_bin_ghc*.exe.mk /tests/cabal/localT1750.package.conf/ /tests/cabal/localshadow1.package.conf/ /tests/cabal/localshadow2.package.conf/ +/tests/cabal/localshadow3.package.conf/ /tests/cabal/package.conf.*/ /tests/cabal/recache_reexport_db/package.cache /tests/cabal/shadow.hs diff --git a/testsuite/tests/cabal/Makefile b/testsuite/tests/cabal/Makefile index 47cd95d010..7644bd8467 100644 --- a/testsuite/tests/cabal/Makefile +++ b/testsuite/tests/cabal/Makefile @@ -127,43 +127,51 @@ T1750: PKGCONFSHADOW1=localshadow1.package.conf PKGCONFSHADOW2=localshadow2.package.conf +PKGCONFSHADOW3=localshadow3.package.conf LOCAL_GHC_PKGSHADOW1 = '$(GHC_PKG)' --no-user-package-db -f $(PKGCONFSHADOW1) LOCAL_GHC_PKGSHADOW2 = '$(GHC_PKG)' --no-user-package-db -f $(PKGCONFSHADOW2) -LOCAL_GHC_PKGSHADOW3 = '$(GHC_PKG)' --no-user-package-db -f $(PKGCONFSHADOW1) -f $(PKGCONFSHADOW2) +LOCAL_GHC_PKGSHADOW3 = '$(GHC_PKG)' --no-user-package-db -f $(PKGCONFSHADOW3) +LOCAL_GHC_PKGSHADOW12 = '$(GHC_PKG)' --no-user-package-db -f $(PKGCONFSHADOW1) -f $(PKGCONFSHADOW2) +LOCAL_GHC_PKGSHADOW13 = '$(GHC_PKG)' --no-user-package-db -f $(PKGCONFSHADOW1) -f $(PKGCONFSHADOW3) # Test package shadowing behaviour. # # localshadow1.package.conf: shadowdep-1-XXX <- shadow-1-XXX -# localshadow2.package.conf: shadow-1-YYY -# -# shadow-1-XXX will be shadowed by shadow-1-YYY, thus invalidating -# shadowdep-1-XXX. +# localshadow2.package.conf: shadow-1-XXX +# +# If the ABI hash of boths shadow-1s are the same, we'll just accept +# the later shadow version. However, if the ABIs are different, we +# should complain! shadow: - rm -rf $(PKGCONFSHADOW1) $(PKGCONFSHADOW2) shadow.hs shadow.o shadow.hi shadow.out shadow.hs shadow.hi + rm -rf $(PKGCONFSHADOW1) $(PKGCONFSHADOW2) $(PKGCONFSHADOW3) shadow.hs shadow.o shadow.hi shadow.out shadow.hs shadow.hi $(LOCAL_GHC_PKGSHADOW1) init $(PKGCONFSHADOW1) $(LOCAL_GHC_PKGSHADOW2) init $(PKGCONFSHADOW2) + $(LOCAL_GHC_PKGSHADOW3) init $(PKGCONFSHADOW3) $(LOCAL_GHC_PKGSHADOW1) register -v0 --force shadow1.pkg $(LOCAL_GHC_PKGSHADOW1) register -v0 --force shadow2.pkg $(LOCAL_GHC_PKGSHADOW2) register -v0 --force shadow3.pkg - $(LOCAL_GHC_PKGSHADOW3) list + $(LOCAL_GHC_PKGSHADOW3) register -v0 --force shadow1.pkg + @echo "databases 1 and 2:" + $(LOCAL_GHC_PKGSHADOW12) list + @echo "databases 1 and 3:" + $(LOCAL_GHC_PKGSHADOW13) list echo "main = return ()" >shadow.hs # -# In this test, shadow-1-XXX is shadowed by shadow-1-YYY, which causes -# shadowdep-1-XXX to be unavailable: +# In this test, shadow-1-XXX with ABI hash aaa conflicts with shadow-1-XXX with +# ABI hash bbb, so GHC errors # @echo "should FAIL:" - '$(TEST_HC)' $(TEST_HC_OPTS) -package-db $(PKGCONFSHADOW1) -package-db $(PKGCONFSHADOW2) -package shadowdep -c shadow.hs -fno-code || true -# -# Reversing the order of the package.conf files should fix the problem: + if '$(TEST_HC)' $(TEST_HC_OPTS) -package-db $(PKGCONFSHADOW1) -package-db $(PKGCONFSHADOW2) -package shadowdep -c shadow.hs -fno-code; then false; else true; fi # - @echo "should SUCCEED:" - '$(TEST_HC)' $(TEST_HC_OPTS) -package-db $(PKGCONFSHADOW2) -package-db $(PKGCONFSHADOW1) -package shadowdep -c shadow.hs -fno-code || true +# Reversing the orders of the configs does not fix the problem +# + @echo "should FAIL:" + if '$(TEST_HC)' $(TEST_HC_OPTS) -package-db $(PKGCONFSHADOW2) -package-db $(PKGCONFSHADOW1) -package shadowdep -c shadow.hs -fno-code; then false; else true; fi # -# We can also fix the problem by using an explicit -package-id flag to -# specify a package we really want to use: +# When the ABIs are the same, there is no problem # @echo "should SUCCEED:" - '$(TEST_HC)' $(TEST_HC_OPTS) -package-db $(PKGCONFSHADOW1) -package-db $(PKGCONFSHADOW2) -package-id shadowdep-1-XXX -c shadow.hs -fno-code + '$(TEST_HC)' $(TEST_HC_OPTS) -package-db $(PKGCONFSHADOW3) -package-db $(PKGCONFSHADOW1) -package shadowdep -c shadow.hs -fno-code # If we pass --global, we should ignore instances in the user database T5442a: @@ -210,7 +218,7 @@ T5442d: '$(GHC_PKG)' init package.conf.T5442d.user '$(GHC_PKG)' init package.conf.T5442d.extra '$(GHC_PKG)' -f package.conf.T5442d.global register --force-files shadow1.pkg 2>/dev/null - '$(GHC_PKG)' -f package.conf.T5442d.user register --force-files shadow3.pkg 2>/dev/null + '$(GHC_PKG)' -f package.conf.T5442d.user register --force-files shadow4.pkg 2>/dev/null '$(GHC_PKG)' --global-package-db=package.conf.T5442d.global -f package.conf.T5442d.extra register --force-files shadow2.pkg 2>/dev/null '$(GHC_PKG)' --global-package-db=package.conf.T5442d.global --user-package-db=package.conf.T5442d.user -f package.conf.T5442d.extra --global unregister shadow --force @echo "global (should be empty):" diff --git a/testsuite/tests/cabal/T1750A.pkg b/testsuite/tests/cabal/T1750A.pkg index 3f4a96e22b..9bda51eea0 100644 --- a/testsuite/tests/cabal/T1750A.pkg +++ b/testsuite/tests/cabal/T1750A.pkg @@ -1,5 +1,4 @@ name: T1750A version: 1 id: T1750A-1-XXX -key: T1750A-1 depends: T1750B-1-XXX diff --git a/testsuite/tests/cabal/T1750B.pkg b/testsuite/tests/cabal/T1750B.pkg index caaaefaa1a..479ce7092c 100644 --- a/testsuite/tests/cabal/T1750B.pkg +++ b/testsuite/tests/cabal/T1750B.pkg @@ -1,5 +1,4 @@ name: T1750B version: 1 id: T1750B-1-XXX -key: T1750B-1 depends: T1750A-1-XXX diff --git a/testsuite/tests/cabal/T5442d.stdout b/testsuite/tests/cabal/T5442d.stdout index 05c6619dde..f3214578d2 100644 --- a/testsuite/tests/cabal/T5442d.stdout +++ b/testsuite/tests/cabal/T5442d.stdout @@ -1,8 +1,8 @@ Reading package info from "shadow1.pkg" ... done. -Reading package info from "shadow3.pkg" ... done. +Reading package info from "shadow4.pkg" ... done. Reading package info from "shadow2.pkg" ... done. global (should be empty): user: -shadow-1 +shadow-2 extra: shadowdep-1 diff --git a/testsuite/tests/cabal/cabal03/Makefile b/testsuite/tests/cabal/cabal03/Makefile index b5520e3d08..97659344d9 100644 --- a/testsuite/tests/cabal/cabal03/Makefile +++ b/testsuite/tests/cabal/cabal03/Makefile @@ -20,14 +20,14 @@ cabal03: clean '$(GHC_PKG)' init tmp.d '$(TEST_HC)' -v0 --make Setup cd p && $(SETUP) clean - cd p && $(SETUP) configure $(CABAL_MINIMAL_BUILD) --with-ghc='$(TEST_HC)' --ghc-options='$(TEST_HC_OPTS)' --package-db=../tmp.d --disable-optimisation --ghc-pkg-option=--force + cd p && $(SETUP) configure $(CABAL_MINIMAL_BUILD) --with-ghc='$(TEST_HC)' --ghc-options='$(TEST_HC_OPTS)' --package-db=../tmp.d --disable-optimisation --ghc-pkg-option=--force --ipid p-noopt cd p && $(SETUP) build cd p && $(SETUP) register cd q && $(SETUP) configure $(CABAL_MINIMAL_BUILD) --with-ghc='$(TEST_HC)' --ghc-options='$(TEST_HC_OPTS)' --package-db=../tmp.d --ghc-pkg-option=--force cd q && $(SETUP) build cd q && $(SETUP) register cd p && $(SETUP) clean - cd p && $(SETUP) configure $(CABAL_MINIMAL_BUILD) --with-ghc='$(TEST_HC)' --ghc-options='$(TEST_HC_OPTS)' --package-db=../tmp.d --ghc-pkg-option=--force + cd p && $(SETUP) configure $(CABAL_MINIMAL_BUILD) --with-ghc='$(TEST_HC)' --ghc-options='$(TEST_HC_OPTS)' --package-db=../tmp.d --ghc-pkg-option=--force --ipid p-withopt cd p && $(SETUP) build cd p && $(SETUP) register cd r && ! ../Setup configure $(CABAL_MINIMAL_BUILD) --with-ghc='$(TEST_HC)' --ghc-options='$(TEST_HC_OPTS)' --package-db=../tmp.d --ghc-pkg-option=--force diff --git a/testsuite/tests/cabal/cabal06/Makefile b/testsuite/tests/cabal/cabal06/Makefile index 8b918a0e2c..9f47ea5756 100644 --- a/testsuite/tests/cabal/cabal06/Makefile +++ b/testsuite/tests/cabal/cabal06/Makefile @@ -4,7 +4,7 @@ include $(TOP)/mk/test.mk SETUP=../Setup -v0 -# This test is for packages whose package IDs overlap, but whose package keys +# This test is for packages whose package IDs overlap, but whose IPIDs # do not. # # 1. install p-1.0 @@ -15,7 +15,7 @@ SETUP=../Setup -v0 # 6. install r-1.0 asking for p-1.0 # # The notable steps are (4), which previously would have required a reinstall, -# and (6), where the dependency solver picks between two package keys with the +# and (6), where the dependency solver picks between two IPIDs with the # same package ID based on their depenencies. # # ./Setup configure is pretty dumb, so we spoonfeed it precisely the @@ -29,7 +29,7 @@ cabal06: clean cd p-1.0 && $(SETUP) configure $(CABAL_MINIMAL_BUILD) --with-ghc='$(TEST_HC)' --ghc-options='$(TEST_HC_OPTS)' --package-db=../tmp.d --prefix='$(PWD)/inst-a' --ghc-pkg-options='--enable-multi-instance' cd p-1.0 && $(SETUP) build cd p-1.0 && $(SETUP) copy - cd p-1.0 && $(SETUP) register + (cd p-1.0 && $(SETUP) register --print-ipid) > tmp_p_1_0 cd q && $(SETUP) clean cd q && $(SETUP) configure $(CABAL_MINIMAL_BUILD) --with-ghc='$(TEST_HC)' --ghc-options='$(TEST_HC_OPTS)' --package-db=../tmp.d --prefix='$(PWD)/inst-b' --ghc-pkg-options='--enable-multi-instance' cd q && $(SETUP) build @@ -39,16 +39,16 @@ cabal06: clean cd p-1.1 && $(SETUP) configure $(CABAL_MINIMAL_BUILD) --with-ghc='$(TEST_HC)' --ghc-options='$(TEST_HC_OPTS)' --package-db=../tmp.d --prefix='$(PWD)/inst-c' --ghc-pkg-options='--enable-multi-instance' cd p-1.1 && $(SETUP) build cd p-1.1 && $(SETUP) copy - cd p-1.1 && $(SETUP) register + (cd p-1.1 && $(SETUP) register --print-ipid) > tmp_p_1_1 cd q && $(SETUP) clean cd q && $(SETUP) configure $(CABAL_MINIMAL_BUILD) --with-ghc='$(TEST_HC)' --ghc-options='$(TEST_HC_OPTS)' --package-db=../tmp.d --constraint="p==1.1" --prefix='$(PWD)/inst-d' --ghc-pkg-options='--enable-multi-instance' cd q && $(SETUP) build cd q && $(SETUP) copy (cd q && $(SETUP) register --print-ipid) > tmp_second_q @echo "Does the first instance of q depend on p-1.0?" - '$(GHC_PKG)' field --ipid `cat tmp_first_q` depends -f tmp.d | grep p-1.0 | wc -l | sed 's/[[:space:]]//g' + '$(GHC_PKG)' field --ipid `cat tmp_first_q` depends -f tmp.d | grep `cat tmp_p_1_0` | wc -l | sed 's/[[:space:]]//g' @echo "Does the second instance of q depend on p-1.0?" - '$(GHC_PKG)' field --ipid `cat tmp_second_q` depends -f tmp.d | grep p-1.1 | wc -l | sed 's/[[:space:]]//g' + '$(GHC_PKG)' field --ipid `cat tmp_second_q` depends -f tmp.d | grep `cat tmp_p_1_1` | wc -l | sed 's/[[:space:]]//g' cd r && $(SETUP) clean cd r && ../Setup configure $(CABAL_MINIMAL_BUILD) --with-ghc='$(TEST_HC)' --ghc-options='$(TEST_HC_OPTS)' --package-db=../tmp.d --dependency="q=`cat ../tmp_first_q`" --constraint="p==1.0" --prefix='$(PWD)/inst-e' --ghc-pkg-options='--enable-multi-instance' cd r && $(SETUP) build diff --git a/testsuite/tests/cabal/cabal07/all.T b/testsuite/tests/cabal/cabal07/all.T index 2286f30783..2052c891f2 100644 --- a/testsuite/tests/cabal/cabal07/all.T +++ b/testsuite/tests/cabal/cabal07/all.T @@ -3,10 +3,7 @@ if default_testopts.cleanup != '': else: cleanup = '' -def normaliseContainersPackage(str): - return re.sub('containers-[^@]+@[A-Za-z0-9]+', 'containers-<VERSION>@<HASH>', str) - test('cabal07', - normalise_errmsg_fun(normaliseContainersPackage), + normalise_version('containers'), run_command, ['$MAKE -s --no-print-directory cabal07 ' + cleanup]) diff --git a/testsuite/tests/cabal/cabal07/cabal07.stderr b/testsuite/tests/cabal/cabal07/cabal07.stderr index 23249b68ff..b1b90c1528 100644 --- a/testsuite/tests/cabal/cabal07/cabal07.stderr +++ b/testsuite/tests/cabal/cabal07/cabal07.stderr @@ -1,6 +1,6 @@ Q.hs:3:8: error: Could not find module ‘Data.Set’ - It is a member of the hidden package ‘containers-0.5.6.2@0tT640fErehCGZtZRn6YbE’. + It is a member of the hidden package ‘containers-0.5.6.2@containers-0.5.6.2’. Perhaps you need to add ‘containers’ to the build-depends in your .cabal file. Use -v to see a list of the files searched for. diff --git a/testsuite/tests/cabal/ghcpkg01.stdout b/testsuite/tests/cabal/ghcpkg01.stdout index c8faf7fdbb..c056cf9824 100644 --- a/testsuite/tests/cabal/ghcpkg01.stdout +++ b/testsuite/tests/cabal/ghcpkg01.stdout @@ -4,7 +4,7 @@ Reading package info from "test.pkg" ... done. name: testpkg version: 1.2.3.4 id: testpkg-1.2.3.4-XXX -key: testpkg-1.2.3.4 +key: testpkg-1.2.3.4-XXX license: BSD3 copyright: (c) The Univsersity of Glasgow 2004 maintainer: glasgow-haskell-users@haskell.org @@ -19,17 +19,18 @@ exposed: True exposed-modules: A hidden-modules: B C.D +abi: trusted: False import-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" library-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" -hs-libraries: testpkg-1.2.3.4 +hs-libraries: testpkg-1.2.3.4-XXX include-dirs: /usr/local/include/testpkg "c:/Program Files/testpkg" pkgroot: name: testpkg version: 1.2.3.4 id: testpkg-1.2.3.4-XXX -key: testpkg-1.2.3.4 +key: testpkg-1.2.3.4-XXX license: BSD3 copyright: (c) The Univsersity of Glasgow 2004 maintainer: glasgow-haskell-users@haskell.org @@ -44,10 +45,11 @@ exposed: True exposed-modules: A hidden-modules: B C.D +abi: trusted: False import-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" library-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" -hs-libraries: testpkg-1.2.3.4 +hs-libraries: testpkg-1.2.3.4-XXX include-dirs: /usr/local/include/testpkg "c:/Program Files/testpkg" pkgroot: @@ -60,7 +62,7 @@ local01.package.conf: name: testpkg version: 2.0 id: testpkg-2.0-XXX -key: testpkg-2.0 +key: testpkg-2.0-XXX license: BSD3 copyright: (c) The Univsersity of Glasgow 2004 maintainer: glasgow-haskell-users@haskell.org @@ -75,17 +77,18 @@ exposed: False exposed-modules: A hidden-modules: B C.D C.E +abi: trusted: False import-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" library-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" -hs-libraries: testpkg-2.0 +hs-libraries: testpkg-2.0-XXX include-dirs: /usr/local/include/testpkg "c:/Program Files/testpkg" pkgroot: name: testpkg version: 2.0 id: testpkg-2.0-XXX -key: testpkg-2.0 +key: testpkg-2.0-XXX license: BSD3 copyright: (c) The Univsersity of Glasgow 2004 maintainer: glasgow-haskell-users@haskell.org @@ -100,17 +103,18 @@ exposed: False exposed-modules: A hidden-modules: B C.D C.E +abi: trusted: False import-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" library-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" -hs-libraries: testpkg-2.0 +hs-libraries: testpkg-2.0-XXX include-dirs: /usr/local/include/testpkg "c:/Program Files/testpkg" pkgroot: --- name: testpkg version: 1.2.3.4 id: testpkg-1.2.3.4-XXX -key: testpkg-1.2.3.4 +key: testpkg-1.2.3.4-XXX license: BSD3 copyright: (c) The Univsersity of Glasgow 2004 maintainer: glasgow-haskell-users@haskell.org @@ -125,10 +129,11 @@ exposed: True exposed-modules: A hidden-modules: B C.D +abi: trusted: False import-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" library-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" -hs-libraries: testpkg-1.2.3.4 +hs-libraries: testpkg-1.2.3.4-XXX include-dirs: /usr/local/include/testpkg "c:/Program Files/testpkg" pkgroot: @@ -142,7 +147,7 @@ Reading package info from "test3.pkg" ... done. name: testpkg version: 1.2.3.4 id: testpkg-1.2.3.4-XXX -key: testpkg-1.2.3.4 +key: testpkg-1.2.3.4-XXX license: BSD3 copyright: (c) The Univsersity of Glasgow 2004 maintainer: glasgow-haskell-users@haskell.org @@ -157,10 +162,11 @@ exposed: False exposed-modules: A hidden-modules: B C.D +abi: trusted: False import-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" library-dirs: /usr/local/lib/testpkg "c:/Program Files/testpkg" -hs-libraries: testpkg-1.2.3.4 +hs-libraries: testpkg-1.2.3.4-XXX include-dirs: /usr/local/include/testpkg "c:/Program Files/testpkg" pkgroot: diff --git a/testsuite/tests/cabal/ghcpkg03.stderr b/testsuite/tests/cabal/ghcpkg03.stderr index 05d288dce2..31eb7ecee5 100644 --- a/testsuite/tests/cabal/ghcpkg03.stderr +++ b/testsuite/tests/cabal/ghcpkg03.stderr @@ -7,7 +7,7 @@ testpkg-1.2.3.4: include-dirs: c:/Program Files/testpkg is a relative path which testpkg-1.2.3.4: cannot find any of ["A.hi","A.p_hi","A.dyn_hi"] (ignoring) testpkg-1.2.3.4: cannot find any of ["B.hi","B.p_hi","B.dyn_hi"] (ignoring) testpkg-1.2.3.4: cannot find any of ["C/D.hi","C/D.p_hi","C/D.dyn_hi"] (ignoring) -testpkg-1.2.3.4: cannot find any of ["libtestpkg-1.2.3.4.a","libtestpkg-1.2.3.4.p_a","libtestpkg-1.2.3.4-ghc<VERSION>.so","libtestpkg-1.2.3.4-ghc<VERSION>.dylib","testpkg-1.2.3.4-ghc<VERSION>.dll"] on library path (ignoring) +testpkg-1.2.3.4: cannot find any of ["libtestpkg-1.2.3.4-XXX.a","libtestpkg-1.2.3.4-XXX.p_a","libtestpkg-1.2.3.4-XXX-ghc7.11.20150825.so","libtestpkg-1.2.3.4-XXX-ghc7.11.20150825.dylib","testpkg-1.2.3.4-XXX-ghc7.11.20150825.dll"] on library path (ignoring) testpkg-2.0: Warning: library-dirs: /usr/local/lib/testpkg doesn't exist or isn't a directory testpkg-2.0: Warning: include-dirs: /usr/local/include/testpkg doesn't exist or isn't a directory testpkg-2.0: import-dirs: /usr/local/lib/testpkg doesn't exist or isn't a directory (ignoring) @@ -18,7 +18,7 @@ testpkg-2.0: cannot find any of ["A.hi","A.p_hi","A.dyn_hi"] (ignoring) testpkg-2.0: cannot find any of ["B.hi","B.p_hi","B.dyn_hi"] (ignoring) testpkg-2.0: cannot find any of ["C/D.hi","C/D.p_hi","C/D.dyn_hi"] (ignoring) testpkg-2.0: cannot find any of ["C/E.hi","C/E.p_hi","C/E.dyn_hi"] (ignoring) -testpkg-2.0: cannot find any of ["libtestpkg-2.0.a","libtestpkg-2.0.p_a","libtestpkg-2.0-ghc<VERSION>.so","libtestpkg-2.0-ghc<VERSION>.dylib","testpkg-2.0-ghc<VERSION>.dll"] on library path (ignoring) +testpkg-2.0: cannot find any of ["libtestpkg-2.0-XXX.a","libtestpkg-2.0-XXX.p_a","libtestpkg-2.0-XXX-ghc7.11.20150825.so","libtestpkg-2.0-XXX-ghc7.11.20150825.dylib","testpkg-2.0-XXX-ghc7.11.20150825.dll"] on library path (ignoring) testpkg-1.2.3.4: Warning: library-dirs: /usr/local/lib/testpkg doesn't exist or isn't a directory testpkg-1.2.3.4: Warning: include-dirs: /usr/local/include/testpkg doesn't exist or isn't a directory testpkg-1.2.3.4: import-dirs: /usr/local/lib/testpkg doesn't exist or isn't a directory (ignoring) @@ -28,4 +28,4 @@ testpkg-1.2.3.4: include-dirs: c:/Program Files/testpkg is a relative path which testpkg-1.2.3.4: cannot find any of ["A.hi","A.p_hi","A.dyn_hi"] (ignoring) testpkg-1.2.3.4: cannot find any of ["B.hi","B.p_hi","B.dyn_hi"] (ignoring) testpkg-1.2.3.4: cannot find any of ["C/D.hi","C/D.p_hi","C/D.dyn_hi"] (ignoring) -testpkg-1.2.3.4: cannot find any of ["libtestpkg-1.2.3.4.a","libtestpkg-1.2.3.4.p_a","libtestpkg-1.2.3.4-ghc<VERSION>.so","libtestpkg-1.2.3.4-ghc<VERSION>.dylib","testpkg-1.2.3.4-ghc<VERSION>.dll"] on library path (ignoring) +testpkg-1.2.3.4: cannot find any of ["libtestpkg-1.2.3.4-XXX.a","libtestpkg-1.2.3.4-XXX.p_a","libtestpkg-1.2.3.4-XXX-ghc7.11.20150825.so","libtestpkg-1.2.3.4-XXX-ghc7.11.20150825.dylib","testpkg-1.2.3.4-XXX-ghc7.11.20150825.dll"] on library path (ignoring) diff --git a/testsuite/tests/cabal/ghcpkg05.stderr b/testsuite/tests/cabal/ghcpkg05.stderr index df8d11a6b9..7440a6fb6c 100644 --- a/testsuite/tests/cabal/ghcpkg05.stderr +++ b/testsuite/tests/cabal/ghcpkg05.stderr @@ -9,7 +9,30 @@ There are problems in package testpkg-2.0: cannot find any of ["B.hi","B.p_hi","B.dyn_hi"] cannot find any of ["C/D.hi","C/D.p_hi","C/D.dyn_hi"] cannot find any of ["C/E.hi","C/E.p_hi","C/E.dyn_hi"] - cannot find any of ["libtestpkg-2.0.a","libtestpkg-2.0.p_a","libtestpkg-2.0-ghc<VERSION>.so","libtestpkg-2.0-ghc<VERSION>.dylib","testpkg-2.0-ghc<VERSION>.dll"] on library path + cannot find any of ["libtestpkg-2.0-XXX.a","libtestpkg-2.0-XXX.p_a","libtestpkg-2.0-XXX-ghc7.11.20150825.so","libtestpkg-2.0-XXX-ghc7.11.20150825.dylib","testpkg-2.0-XXX-ghc7.11.20150825.dll"] on library path +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/compiler/stage2/doc/html/ghc/ghc.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/haskeline/dist-install/doc/html/haskeline/haskeline.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/terminfo/dist-install/doc/html/terminfo/terminfo.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/transformers/dist-install/doc/html/transformers/transformers.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/hoopl/dist-install/doc/html/hoopl/hoopl.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/bin-package-db/dist-install/doc/html/bin-package-db/bin-package-db.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/Cabal/Cabal/dist-install/doc/html/Cabal/Cabal.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/binary/dist-install/doc/html/binary/binary.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/template-haskell/dist-install/doc/html/template-haskell/template-haskell.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/pretty/dist-install/doc/html/pretty/pretty.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/hpc/dist-install/doc/html/hpc/hpc.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/process/dist-install/doc/html/process/process.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/directory/dist-install/doc/html/directory/directory.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/unix/dist-install/doc/html/unix/unix.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/time/dist-install/doc/html/time/time.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/containers/dist-install/doc/html/containers/containers.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/bytestring/dist-install/doc/html/bytestring/bytestring.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/deepseq/dist-install/doc/html/deepseq/deepseq.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/array/dist-install/doc/html/array/array.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/filepath/dist-install/doc/html/filepath/filepath.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/base/dist-install/doc/html/base/base.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/integer-gmp/dist-install/doc/html/integer-gmp/integer-gmp.haddock doesn't exist or isn't a file +Warning: haddock-interfaces: /home/hs01/ezyang/ghc-quick2/libraries/ghc-prim/dist-install/doc/html/ghc-prim/ghc-prim.haddock doesn't exist or isn't a file The following packages are broken, either because they have a problem listed above, or because they depend on a broken package. diff --git a/testsuite/tests/cabal/shadow.stderr b/testsuite/tests/cabal/shadow.stderr index a0a38cde22..3825896e85 100644 --- a/testsuite/tests/cabal/shadow.stderr +++ b/testsuite/tests/cabal/shadow.stderr @@ -1,4 +1,4 @@ -<command line>: cannot satisfy -package shadowdep: - shadowdep-1-XXX is unusable due to missing or recursive dependencies: - shadow-1-XXX - (use -v for more information) +<command line>: package db: duplicate packages with incompatible ABIs: + shadow-1-XXX has ABIs: aaa, bbb +<command line>: package db: duplicate packages with incompatible ABIs: + shadow-1-XXX has ABIs: aaa, bbb diff --git a/testsuite/tests/cabal/shadow.stdout b/testsuite/tests/cabal/shadow.stdout index 0d14e9cb8a..f4b783aa7d 100644 --- a/testsuite/tests/cabal/shadow.stdout +++ b/testsuite/tests/cabal/shadow.stdout @@ -1,3 +1,4 @@ +databases 1 and 2: localshadow1.package.conf: (shadow-1) (shadowdep-1) @@ -5,6 +6,14 @@ localshadow1.package.conf: localshadow2.package.conf: (shadow-1) +databases 1 and 3: +localshadow1.package.conf: + (shadow-1) + (shadowdep-1) + +localshadow3.package.conf: + (shadow-1) + +should FAIL: should FAIL: -should SUCCEED: should SUCCEED: diff --git a/testsuite/tests/cabal/shadow1.pkg b/testsuite/tests/cabal/shadow1.pkg index 553ebeb776..1e3960202c 100644 --- a/testsuite/tests/cabal/shadow1.pkg +++ b/testsuite/tests/cabal/shadow1.pkg @@ -1,5 +1,6 @@ name: shadow version: 1 id: shadow-1-XXX -key: shadow-1 +key: shadow-1-XXX +abi: aaa depends: diff --git a/testsuite/tests/cabal/shadow2.pkg b/testsuite/tests/cabal/shadow2.pkg index ae89641176..5cd54cca02 100644 --- a/testsuite/tests/cabal/shadow2.pkg +++ b/testsuite/tests/cabal/shadow2.pkg @@ -1,5 +1,5 @@ name: shadowdep version: 1 id: shadowdep-1-XXX -key: shadowdep-1 +key: shadowdep-1-XXX depends: shadow-1-XXX diff --git a/testsuite/tests/cabal/shadow3.pkg b/testsuite/tests/cabal/shadow3.pkg index 62c93f95e1..6640e9da10 100644 --- a/testsuite/tests/cabal/shadow3.pkg +++ b/testsuite/tests/cabal/shadow3.pkg @@ -1,5 +1,6 @@ name: shadow version: 1 -id: shadow-1-YYY -key: shadow-1 +id: shadow-1-XXX +key: shadow-1-XXX +abi: bbb depends: diff --git a/testsuite/tests/cabal/shadow4.pkg b/testsuite/tests/cabal/shadow4.pkg new file mode 100644 index 0000000000..fb4e08e4a4 --- /dev/null +++ b/testsuite/tests/cabal/shadow4.pkg @@ -0,0 +1,6 @@ +name: shadow +version: 2 +id: shadow-2-ZZZ +key: shadow-2-ZZZ +abi: zzz +depends: diff --git a/testsuite/tests/cabal/test.pkg b/testsuite/tests/cabal/test.pkg index 42c557a0f9..4a1adc93eb 100644 --- a/testsuite/tests/cabal/test.pkg +++ b/testsuite/tests/cabal/test.pkg @@ -1,7 +1,7 @@ name: testpkg version: 1.2.3.4 id: testpkg-1.2.3.4-XXX -key: testpkg-1.2.3.4 +key: testpkg-1.2.3.4-XXX license: BSD3 copyright: (c) The Univsersity of Glasgow 2004 maintainer: glasgow-haskell-users@haskell.org @@ -17,4 +17,4 @@ hidden-modules: B, "C.D" import-dirs: /usr/local/lib/testpkg, "c:/Program Files/testpkg" library-dirs: /usr/local/lib/testpkg, "c:/Program Files/testpkg" include-dirs: /usr/local/include/testpkg, "c:/Program Files/testpkg" -hs-libraries: testpkg-1.2.3.4 +hs-libraries: testpkg-1.2.3.4-XXX diff --git a/testsuite/tests/cabal/test2.pkg b/testsuite/tests/cabal/test2.pkg index c027ed3a15..0c627d2e13 100644 --- a/testsuite/tests/cabal/test2.pkg +++ b/testsuite/tests/cabal/test2.pkg @@ -1,7 +1,7 @@ name: "testpkg" version: 2.0 id: testpkg-2.0-XXX -key: testpkg-2.0 +key: testpkg-2.0-XXX license: BSD3 copyright: (c) The Univsersity of Glasgow 2004 maintainer: glasgow-haskell-users@haskell.org @@ -17,4 +17,4 @@ hidden-modules: B, "C.D", "C.E" import-dirs: /usr/local/lib/testpkg, "c:/Program Files/testpkg" library-dirs: /usr/local/lib/testpkg, "c:/Program Files/testpkg" include-dirs: /usr/local/include/testpkg, "c:/Program Files/testpkg" -hs-libraries: testpkg-2.0 +hs-libraries: testpkg-2.0-XXX diff --git a/testsuite/tests/cabal/test3.pkg b/testsuite/tests/cabal/test3.pkg index 8f1ca04366..2c017422c0 100644 --- a/testsuite/tests/cabal/test3.pkg +++ b/testsuite/tests/cabal/test3.pkg @@ -1,7 +1,7 @@ name: "testpkg" version: 3.0 id: testpkg-3.0-XXX -key: testpkg-3.0 +key: testpkg-3.0-XXX license: BSD3 copyright: (c) The Univsersity of Glasgow 2004 maintainer: glasgow-haskell-users@haskell.org diff --git a/testsuite/tests/cabal/test4.pkg b/testsuite/tests/cabal/test4.pkg index c4b1883512..eba9509572 100644 --- a/testsuite/tests/cabal/test4.pkg +++ b/testsuite/tests/cabal/test4.pkg @@ -1,7 +1,7 @@ name: "testpkg" version: 4.0 id: testpkg-4.0-XXX -key: testpkg-4.0 +key: testpkg-4.0-XXX license: BSD3 copyright: (c) The Univsersity of Glasgow 2004 maintainer: glasgow-haskell-users@haskell.org diff --git a/testsuite/tests/cabal/test5.pkg b/testsuite/tests/cabal/test5.pkg index 48e198cd30..c66d19bc0c 100644 --- a/testsuite/tests/cabal/test5.pkg +++ b/testsuite/tests/cabal/test5.pkg @@ -1,7 +1,7 @@ name: "newtestpkg" version: 2.0 id: newtestpkg-2.0-XXX -key: newtestpkg-2.0 +key: newtestpkg-2.0-XXX license: BSD3 copyright: (c) The Univsersity of Glasgow 2004 maintainer: glasgow-haskell-users@haskell.org @@ -16,4 +16,4 @@ exposed-modules: A hidden-modules: B, "C.D", "C.E" import-dirs: /usr/local/lib/testpkg, "c:/Program Files/testpkg" library-dirs: /usr/local/lib/testpkg, "c:/Program Files/testpkg" -hs-libraries: testpkg-2.0 +hs-libraries: testpkg-2.0-XXX diff --git a/testsuite/tests/cabal/test7a.pkg b/testsuite/tests/cabal/test7a.pkg index 7eaeea2a8a..ae78add404 100644 --- a/testsuite/tests/cabal/test7a.pkg +++ b/testsuite/tests/cabal/test7a.pkg @@ -1,7 +1,7 @@ name: testpkg7a version: 1.0 id: testpkg7a-1.0-XXX -key: testpkg7a-1.0 +key: testpkg7a-1.0-XXX license: BSD3 copyright: (c) The Univsersity of Glasgow 2004 maintainer: glasgow-haskell-users@haskell.org @@ -13,5 +13,5 @@ category: none author: simonmar@microsoft.com exposed: True exposed-modules: E, A from testpkg-1.2.3.4-XXX:A, A1 from testpkg-1.2.3.4-XXX:A, E2 from testpkg7a-1.0-XXX:E -hs-libraries: testpkg7a-1.0 +hs-libraries: testpkg7a-1.0-XXX depends: testpkg-1.2.3.4-XXX diff --git a/testsuite/tests/cabal/test7b.pkg b/testsuite/tests/cabal/test7b.pkg index f0bc6871f0..74b4b86014 100644 --- a/testsuite/tests/cabal/test7b.pkg +++ b/testsuite/tests/cabal/test7b.pkg @@ -1,7 +1,7 @@ name: testpkg7b version: 1.0 id: testpkg7b-1.0-XXX -key: testpkg7b-1.0 +key: testpkg7b-1.0-XXX license: BSD3 copyright: (c) The Univsersity of Glasgow 2004 maintainer: glasgow-haskell-users@haskell.org @@ -13,5 +13,5 @@ category: none author: simonmar@microsoft.com exposed: True exposed-modules: F1 from testpkg-1.2.3.4-XXX:A, F2 from testpkg7a-1.0-XXX:A, F3 from testpkg7a-1.0-XXX:A1, F4 from testpkg7a-1.0-XXX:E, E from testpkg7a-1.0-XXX:E, E3 from testpkg7a-1.0-XXX:E2 -hs-libraries: testpkg7b-1.0 +hs-libraries: testpkg7b-1.0-XXX depends: testpkg-1.2.3.4-XXX, testpkg7a-1.0-XXX diff --git a/testsuite/tests/cabal/testdup.pkg b/testsuite/tests/cabal/testdup.pkg index 0e368e5ae8..bf1db32da4 100644 --- a/testsuite/tests/cabal/testdup.pkg +++ b/testsuite/tests/cabal/testdup.pkg @@ -1,6 +1,6 @@ name: testdup version: 1.0 id: testdup-1.0-XXX -key: testdup-1.0 +key: testdup-1.0-XXX license: BSD3 depends: testpkg-1.2.3.4-XXX testpkg-1.2.3.4-XXX diff --git a/testsuite/tests/ghci/scripts/T5979.stderr b/testsuite/tests/ghci/scripts/T5979.stderr index b4abfbd99c..cafb6a4992 100644 --- a/testsuite/tests/ghci/scripts/T5979.stderr +++ b/testsuite/tests/ghci/scripts/T5979.stderr @@ -1,7 +1,7 @@ -<no location info>: +<no location info>: error: Could not find module ‘Control.Monad.Trans.State’ Perhaps you meant - Control.Monad.Trans.State (from transformers-<VERSION>@<HASH>) - Control.Monad.Trans.Class (from transformers-<VERSION>@<HASH>) - Control.Monad.Trans.Cont (from transformers-<VERSION>@<HASH>) + Control.Monad.Trans.State (from transformers-0.4.3.0@transformers-0.4.3.0) + Control.Monad.Trans.Class (from transformers-0.4.3.0@transformers-0.4.3.0) + Control.Monad.Trans.Cont (from transformers-0.4.3.0@transformers-0.4.3.0) diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index faf3f1d02a..d58b2dc0aa 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -1,8 +1,5 @@ # coding=utf8 -def normaliseTransformersPackageKey(str): - return re.sub('transformers-[^@]+@[A-Za-z0-9]+', 'transformers-<VERSION>@<HASH>', str) - setTestOpts(when(compiler_profiled(), skip)) test('ghci001', combined_output, ghci_script, ['ghci001.script']) @@ -126,7 +123,7 @@ test('T5836', normal, ghci_script, ['T5836.script']) test('T5979', [reqlib('transformers'), normalise_slashes, - normalise_errmsg_fun(normaliseTransformersPackageKey)], + normalise_version("transformers")], ghci_script, ['T5979.script']) test('T5975a', [pre_cmd('touch föøbàr1.hs'), diff --git a/testsuite/tests/rename/prog006/Makefile b/testsuite/tests/rename/prog006/Makefile index 41c33c8765..0012e50bad 100644 --- a/testsuite/tests/rename/prog006/Makefile +++ b/testsuite/tests/rename/prog006/Makefile @@ -28,12 +28,12 @@ rn.prog006: rm -f pkg.conf rm -f pwd pwd.exe pwd.exe.manifest pwd.hi pwd.o '$(TEST_HC)' $(TEST_HC_OPTS) --make pwd -v0 - '$(TEST_HC)' $(TEST_HC_OPTS) --make -this-package-key test-1.0 B.C -fforce-recomp -v0 $(RM_PROG006_EXTRA_FLAGS) + '$(TEST_HC)' $(TEST_HC_OPTS) --make -this-package-key test-1.0-XXX B.C -fforce-recomp -v0 $(RM_PROG006_EXTRA_FLAGS) rm -f pkg.conf echo "name: test" >>pkg.conf echo "version: 1.0" >>pkg.conf - echo "id: test-XXX" >>pkg.conf - echo "key: test-1.0" >>pkg.conf + echo "id: test-1.0-XXX" >>pkg.conf + echo "key: test-1.0-XXX" >>pkg.conf echo "import-dirs: `./pwd`" >>pkg.conf echo "exposed-modules: B.C" >>pkg.conf rm -rf $(LOCAL_PKGCONF) diff --git a/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr b/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr index a89ff72d04..5616259ee3 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr +++ b/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly07.stderr @@ -1,6 +1,6 @@ <no location info>: error: - The package (bytestring-0.10.6.0) is required to be trusted but it isn't! + The package (base-4.8.2.0) is required to be trusted but it isn't! <no location info>: error: - The package (base-4.8.2.0) is required to be trusted but it isn't! + The package (bytestring-0.10.6.0) is required to be trusted but it isn't! diff --git a/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly08.stderr b/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly08.stderr index f4013c0a90..5616259ee3 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly08.stderr +++ b/testsuite/tests/safeHaskell/check/pkg01/ImpSafeOnly08.stderr @@ -1,6 +1,6 @@ -<no location info>: - The package (bytestring-0.10.5.0) is required to be trusted but it isn't! - -<no location info>: +<no location info>: error: The package (base-4.8.2.0) is required to be trusted but it isn't! + +<no location info>: error: + The package (bytestring-0.10.6.0) is required to be trusted but it isn't! diff --git a/testsuite/tests/safeHaskell/check/pkg01/all.T b/testsuite/tests/safeHaskell/check/pkg01/all.T index 5f337370af..aea4406986 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/all.T +++ b/testsuite/tests/safeHaskell/check/pkg01/all.T @@ -29,7 +29,8 @@ make_args = 'VANILLA=' + vanilla + ' PROF=' + prof + ' DYN=' + dyn test('safePkg01', [clean_cmd('$MAKE -s --no-print-directory cleanPackageDatabase.safePkg01'), normalise_errmsg_fun(ignoreLdOutput), - normalise_version("array", "integer-gmp", "integer-simple", "bytestring"), + normalise_version("array", "integer-gmp", "integer-simple", "bytestring", + "base", "deepseq", "ghc-prim"), ], run_command, ['$MAKE -s --no-print-directory safePkg01 ' + make_args]) @@ -91,13 +92,13 @@ test('ImpSafeOnly06', test('ImpSafeOnly07', [pre_cmd('$MAKE -s --no-print-directory mkPackageDatabase.ImpSafeOnly07 ' + make_args), clean_cmd('$MAKE -s --no-print-directory cleanPackageDatabase.ImpSafeOnly07'), - normalise_version("bytestring")], + normalise_version("bytestring", "base")], compile_fail, ['-fpackage-trust -package-db pdb.ImpSafeOnly07/local.db -trust safePkg01 -distrust bytestring']) test('ImpSafeOnly08', [pre_cmd('$MAKE -s --no-print-directory mkPackageDatabase.ImpSafeOnly08 ' + make_args), clean_cmd('$MAKE -s --no-print-directory cleanPackageDatabase.ImpSafeOnly08'), - normalise_version("bytestring")], + normalise_version("bytestring", "base")], compile_fail, ['-fpackage-trust -package-db pdb.ImpSafeOnly08/local.db -trust safePkg01']) test('ImpSafeOnly09', diff --git a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout index a3810ffb8b..62f18d1392 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout +++ b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout @@ -29,17 +29,17 @@ trusted: safe require own pkg trusted: True M_SafePkg6 -package dependencies: bytestring-0.10.6.0* deepseq-1.4.1.1 array-0.5.1.0 base-4.8.2.0* ghc-prim-0.4.0.0 integer-gmp-1.0.0.0 +package dependencies: array-0.5.1.0 base-4.8.2.0* bytestring-0.10.6.0* deepseq-1.4.1.1 ghc-prim-0.4.0.0 integer-gmp-1.0.0.0 trusted: trustworthy require own pkg trusted: False M_SafePkg7 -package dependencies: bytestring-0.10.6.0* deepseq-1.4.1.1 array-0.5.1.0 base-4.8.2.0* ghc-prim-0.4.0.0 integer-gmp-1.0.0.0 +package dependencies: array-0.5.1.0 base-4.8.2.0* bytestring-0.10.6.0* deepseq-1.4.1.1 ghc-prim-0.4.0.0 integer-gmp-1.0.0.0 trusted: safe require own pkg trusted: False M_SafePkg8 -package dependencies: bytestring-0.10.6.0* deepseq-1.4.1.1 array-0.5.1.0 base-4.8.2.0 ghc-prim-0.4.0.0 integer-gmp-1.0.0.0 +package dependencies: array-0.5.1.0 base-4.8.2.0 bytestring-0.10.6.0* deepseq-1.4.1.1 ghc-prim-0.4.0.0 integer-gmp-1.0.0.0 trusted: trustworthy require own pkg trusted: False diff --git a/testsuite/tests/th/TH_Roles2.stderr b/testsuite/tests/th/TH_Roles2.stderr index 891a792300..8f078ba901 100644 --- a/testsuite/tests/th/TH_Roles2.stderr +++ b/testsuite/tests/th/TH_Roles2.stderr @@ -4,9 +4,9 @@ TYPE CONSTRUCTORS data T (a :: k) COERCION AXIOMS Dependent modules: [] -Dependent packages: [ghc-boot-0.0.0.0, pretty-<VERSION>, - deepseq-<VERSION>, array-<VERSION>, base-<VERSION>, ghc-prim-<VERSION>, - integer-<IMPL>-<VERSION>, template-haskell-<VERSION>] +Dependent packages: [array-0.5.1.0, base-4.8.2.0, deepseq-1.4.1.1, + ghc-boot-0.0.0.0, ghc-prim-0.4.0.0, integer-gmp-1.0.0.0, + pretty-1.1.2.0, template-haskell-2.11.0.0] ==================== Typechecker ==================== diff --git a/utils/ghc-cabal/Main.hs b/utils/ghc-cabal/Main.hs index 206b676031..71ba847c48 100644 --- a/utils/ghc-cabal/Main.hs +++ b/utils/ghc-cabal/Main.hs @@ -229,12 +229,7 @@ doRegister directory distDir ghc ghcpkg topdir let installedPkgs' = PackageIndex.fromList instInfos let updateComponentConfig (cn, clbi, deps) = (cn, updateComponentLocalBuildInfo clbi, deps) - updateComponentLocalBuildInfo clbi - = clbi { - componentPackageDeps = - [ (fixupPackageId instInfos ipid, pid) - | (ipid,pid) <- componentPackageDeps clbi ] - } + updateComponentLocalBuildInfo clbi = clbi -- TODO: remove ccs' = map updateComponentConfig (componentsConfigs lbi) lbi' = lbi { componentsConfigs = ccs', @@ -265,30 +260,6 @@ updateInstallDirTemplates relocatableBuild myPrefix myLibdir myDocdir idts htmldir = toPathTemplate "$docdir" } --- The packages are built with the package ID ending in "-inplace", but --- when they're installed they get the package hash appended. We need to --- fix up the package deps so that they use the hash package IDs, not --- the inplace package IDs. -fixupPackageId :: [Installed.InstalledPackageInfo] - -> InstalledPackageId - -> InstalledPackageId -fixupPackageId _ x@(InstalledPackageId ipi) - | "builtin_" `isPrefixOf` ipi = x -fixupPackageId ipinfos (InstalledPackageId ipi) - = case stripPrefix (reverse "-inplace") $ reverse ipi of - Nothing -> - error ("Installed package ID doesn't end in -inplace: " ++ show ipi) - Just x -> - let ipi' = reverse ('-' : x) - f (ipinfo : ipinfos') = case Installed.installedPackageId ipinfo of - y@(InstalledPackageId ipinfoid) - | ipi' `isPrefixOf` ipinfoid -> - y - _ -> - f ipinfos' - f [] = error ("Installed package ID not registered: " ++ show ipi) - in f ipinfos - -- On Windows we need to split the ghc package into 2 pieces, or the -- DLL that it makes contains too many symbols (#5987). There are -- therefore 2 libraries, not just the 1 that Cabal assumes. @@ -316,7 +287,7 @@ generate directory distdir dll0Modules config_args -- XXX We shouldn't just configure with the default flags -- XXX And this, and thus the "getPersistBuildConfig distdir" below, -- aren't going to work when the deps aren't built yet - withArgs (["configure", "--distdir", distdir] ++ config_args) + withArgs (["configure", "--distdir", distdir, "--ipid", "$pkg-$version"] ++ config_args) runDefaultMain lbi <- getPersistBuildConfig distdir @@ -342,11 +313,12 @@ generate directory distdir dll0Modules config_args -- generate inplace-pkg-config withLibLBI pd lbi $ \lib clbi -> do cwd <- getCurrentDirectory - let ipid = InstalledPackageId (display (packageId pd) ++ "-inplace") + let ipid = ComponentId (display (packageId pd)) let installedPkgInfo = inplaceInstalledPackageInfo cwd distdir - pd ipid lib lbi clbi + pd (Installed.AbiHash "") lib lbi clbi final_ipi = mangleIPI directory distdir lbi $ installedPkgInfo { - Installed.installedPackageId = ipid, + Installed.installedComponentId = ipid, + Installed.compatPackageKey = ipid, Installed.haddockHTMLs = [] } content = Installed.showInstalledPackageInfo final_ipi ++ "\n" @@ -397,24 +369,24 @@ generate directory distdir dll0Modules config_args dep_ids = map snd (externalPackageDeps lbi) deps = map display dep_ids dep_direct = map (fromMaybe (error "ghc-cabal: dep_keys failed") - . PackageIndex.lookupInstalledPackageId + . PackageIndex.lookupComponentId (installedPkgs lbi) . fst) . externalPackageDeps $ lbi - dep_ipids = map (display . Installed.installedPackageId) dep_direct + dep_ipids = map (display . Installed.installedComponentId) dep_direct depLibNames - | packageKeySupported comp - = map (display . Installed.libraryName) dep_direct + | packageKeySupported comp = dep_ipids | otherwise = deps depNames = map (display . packageName) dep_ids transitive_dep_ids = map Installed.sourcePackageId dep_pkgs transitiveDeps = map display transitive_dep_ids transitiveDepLibNames - | packageKeySupported comp - = map (display . Installed.libraryName) dep_pkgs + | packageKeySupported comp = map fixupRtsLibName transitiveDeps | otherwise = transitiveDeps + fixupRtsLibName "rts-1.0" = "rts" + fixupRtsLibName x = x transitiveDepNames = map (display . packageName) transitive_dep_ids libraryDirs = forDeps Installed.libraryDirs @@ -434,9 +406,9 @@ generate directory distdir dll0Modules config_args allMods = mods ++ otherMods let xs = [variablePrefix ++ "_VERSION = " ++ display (pkgVersion (package pd)), -- TODO: move inside withLibLBI - variablePrefix ++ "_PACKAGE_KEY = " ++ display (localPackageKey lbi), + variablePrefix ++ "_PACKAGE_KEY = " ++ display (localCompatPackageKey lbi), -- copied from mkComponentsLocalBuildInfo - variablePrefix ++ "_LIB_NAME = " ++ display (localLibraryName lbi), + variablePrefix ++ "_LIB_NAME = " ++ display (localComponentId lbi), variablePrefix ++ "_MODULES = " ++ unwords mods, variablePrefix ++ "_HIDDEN_MODULES = " ++ unwords otherMods, variablePrefix ++ "_SYNOPSIS =" ++ synopsis pd, diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs index 4ee0d012f2..8095cc434a 100644 --- a/utils/ghc-pkg/Main.hs +++ b/utils/ghc-pkg/Main.hs @@ -19,7 +19,7 @@ import Distribution.ModuleName (ModuleName) import Distribution.InstalledPackageInfo as Cabal import Distribution.Compat.ReadP hiding (get) import Distribution.ParseUtils -import Distribution.Package hiding (installedPackageId) +import Distribution.Package hiding (installedComponentId) import Distribution.Text import Distribution.Version import Distribution.Simple.Utils (fromUTF8, toUTF8, writeUTF8File, readUTF8File) @@ -136,8 +136,7 @@ data Flag | FlagIgnoreCase | FlagNoUserDb | FlagVerbosity (Maybe String) - | FlagIPId - | FlagPackageKey + | FlagComponentId deriving Eq flags :: [OptDescr Flag] @@ -180,10 +179,8 @@ flags = [ "only print package names, not versions; can only be used with list --simple-output", Option [] ["ignore-case"] (NoArg FlagIgnoreCase) "ignore case for substring matching", - Option [] ["ipid"] (NoArg FlagIPId) + Option [] ["ipid", "package-key"] (NoArg FlagComponentId) "interpret package arguments as installed package IDs", - Option [] ["package-key"] (NoArg FlagPackageKey) - "interpret package arguments as installed package keys", Option ['v'] ["verbose"] (OptArg FlagVerbosity "Verbosity") "verbosity level (0-2, default 1)" ] @@ -322,8 +319,7 @@ data Force = NoForce | ForceFiles | ForceAll | CannotForce -- | Enum flag representing argument type data AsPackageArg - = AsIpid - | AsPackageKey + = AsComponentId | AsDefault -- | Represents how a package may be specified by a user on the command line. @@ -332,10 +328,7 @@ data PackageArg = Id PackageIdentifier -- | An installed package ID foo-0.1-HASH. This is guaranteed to uniquely -- match a single entry in the package database. - | IPId InstalledPackageId - -- | A package key foo_HASH. This is also guaranteed to uniquely match - -- a single entry in the package database - | PkgKey PackageKey + | ICId ComponentId -- | A glob against the package name. The first string is the literal -- glob, the second is a function which returns @True@ if the argument -- matches. @@ -350,8 +343,7 @@ runit verbosity cli nonopts = do | FlagForce `elem` cli = ForceAll | FlagForceFiles `elem` cli = ForceFiles | otherwise = NoForce - as_arg | FlagIPId `elem` cli = AsIpid - | FlagPackageKey `elem` cli = AsPackageKey + as_arg | FlagComponentId `elem` cli = AsComponentId | otherwise = AsDefault multi_instance = FlagMultiInstance `elem` cli expand_env_vars= FlagExpandEnvVars `elem` cli @@ -504,10 +496,8 @@ parseGlobPackageId = return (PackageIdentifier{ pkgName = n, pkgVersion = globVersion })) readPackageArg :: AsPackageArg -> String -> IO PackageArg -readPackageArg AsIpid str = - parseCheck (IPId `fmap` parse) str "installed package id" -readPackageArg AsPackageKey str = - parseCheck (PkgKey `fmap` parse) str "package key" +readPackageArg AsComponentId str = + parseCheck (ICId `fmap` parse) str "installed package id" readPackageArg AsDefault str = Id `fmap` readGlobPkgId str -- globVersion means "all versions" @@ -1013,12 +1003,7 @@ parsePackageInfo str = (Just l, s) -> die (show l ++ ": " ++ s) mungePackageInfo :: InstalledPackageInfo -> InstalledPackageInfo -mungePackageInfo ipi = ipi { packageKey = packageKey' } - where - packageKey' - | OldPackageKey (PackageIdentifier (PackageName "") _) <- packageKey ipi - = OldPackageKey (sourcePackageId ipi) - | otherwise = packageKey ipi +mungePackageInfo ipi = ipi -- ----------------------------------------------------------------------------- -- Making changes to a package database @@ -1038,7 +1023,7 @@ updateInternalDB :: PackageDB -> [DBOp] -> PackageDB updateInternalDB db cmds = db{ packages = foldl do_cmd (packages db) cmds } where do_cmd pkgs (RemovePackage p) = - filter ((/= installedPackageId p) . installedPackageId) pkgs + filter ((/= installedComponentId p) . installedComponentId) pkgs do_cmd pkgs (AddPackage p) = p : pkgs do_cmd pkgs (ModifyPackage p) = do_cmd (do_cmd pkgs (RemovePackage p)) (AddPackage p) @@ -1050,11 +1035,11 @@ changeDBDir verbosity cmds db = do updateDBCache verbosity db where do_cmd (RemovePackage p) = do - let file = location db </> display (installedPackageId p) <.> "conf" + let file = location db </> display (installedComponentId p) <.> "conf" when (verbosity > Normal) $ infoLn ("removing " ++ file) removeFileSafe file do_cmd (AddPackage p) = do - let file = location db </> display (installedPackageId p) <.> "conf" + let file = location db </> display (installedComponentId p) <.> "conf" when (verbosity > Normal) $ infoLn ("writing " ++ file) writeUTF8File file (showInstalledPackageInfo p) do_cmd (ModifyPackage p) = @@ -1097,12 +1082,14 @@ type PackageCacheFormat = GhcPkg.InstalledPackageInfo convertPackageInfoToCacheFormat :: InstalledPackageInfo -> PackageCacheFormat convertPackageInfoToCacheFormat pkg = GhcPkg.InstalledPackageInfo { - GhcPkg.installedPackageId = display (installedPackageId pkg), + GhcPkg.installedPackageId = display (installedComponentId pkg), GhcPkg.sourcePackageId = display (sourcePackageId pkg), GhcPkg.packageName = display (packageName pkg), GhcPkg.packageVersion = packageVersion pkg, - GhcPkg.packageKey = display (packageKey pkg), + GhcPkg.packageKey = display (installedComponentId pkg), GhcPkg.depends = map display (depends pkg), + GhcPkg.abiHash = let AbiHash abi = abiHash pkg + in abi, GhcPkg.importDirs = importDirs pkg, GhcPkg.hsLibraries = hsLibraries pkg, GhcPkg.extraLibraries = extraLibraries pkg, @@ -1174,9 +1161,9 @@ modifyPackage fn pkgarg verbosity my_flags force = do db_name = location db pkgs = packages db - pks = map packageKey ps + pks = map installedComponentId ps - cmds = [ fn pkg | pkg <- pkgs, packageKey pkg `elem` pks ] + cmds = [ fn pkg | pkg <- pkgs, installedComponentId pkg `elem` pks ] new_db = updateInternalDB db cmds -- ...but do consistency checks with regards to the full stack @@ -1184,14 +1171,14 @@ modifyPackage fn pkgarg verbosity my_flags force = do rest_of_stack = filter ((/= db_name) . location) db_stack new_stack = new_db : rest_of_stack new_broken = brokenPackages (allPackagesInStack new_stack) - newly_broken = filter ((`notElem` map packageKey old_broken) - . packageKey) new_broken + newly_broken = filter ((`notElem` map installedComponentId old_broken) + . installedComponentId) new_broken -- let displayQualPkgId pkg | [_] <- filter ((== pkgid) . sourcePackageId) (allPackagesInStack db_stack) = display pkgid - | otherwise = display pkgid ++ "@" ++ display (packageKey pkg) + | otherwise = display pkgid ++ "@" ++ display (installedComponentId pkg) where pkgid = sourcePackageId pkg when (not (null newly_broken)) $ dieOrForceAll force ("unregistering would break the following packages: " @@ -1242,7 +1229,7 @@ listPackages verbosity my_flags mPackageName mModuleName = do EQ -> case pkgVersion p1 `compare` pkgVersion p2 of LT -> LT GT -> GT - EQ -> packageKey pkg1 `compare` packageKey pkg2 + EQ -> installedComponentId pkg1 `compare` installedComponentId pkg2 where (p1,p2) = (sourcePackageId pkg1, sourcePackageId pkg2) stack = reverse db_stack_sorted @@ -1250,7 +1237,7 @@ listPackages verbosity my_flags mPackageName mModuleName = do match `exposedInPkg` pkg = any match (map display $ exposedModules pkg) pkg_map = allPackagesInStack db_stack - broken = map packageKey (brokenPackages pkg_map) + broken = map installedComponentId (brokenPackages pkg_map) show_normal PackageDB{ location = db_name, packages = pkg_confs } = do hPutStrLn stdout (db_name ++ ":") @@ -1259,15 +1246,15 @@ listPackages verbosity my_flags mPackageName mModuleName = do else hPutStrLn stdout $ unlines (map (" " ++) pp_pkgs) where -- Sort using instance Ord PackageId - pp_pkgs = map pp_pkg . sortBy (comparing installedPackageId) $ pkg_confs + pp_pkgs = map pp_pkg . sortBy (comparing installedComponentId) $ pkg_confs pp_pkg p - | packageKey p `elem` broken = printf "{%s}" doc + | installedComponentId p `elem` broken = printf "{%s}" doc | exposed p = doc | otherwise = printf "(%s)" doc - where doc | verbosity >= Verbose = printf "%s (%s)" pkg ipid + where doc | verbosity >= Verbose = printf "%s (%s)" pkg pk | otherwise = pkg where - InstalledPackageId ipid = installedPackageId p + ComponentId pk = installedComponentId p pkg = display (sourcePackageId p) show_simple = simplePackageList my_flags . allPackagesInStack @@ -1288,15 +1275,15 @@ listPackages verbosity my_flags mPackageName mModuleName = do map (termText " " <#>) (map pp_pkg (packages db))) where pp_pkg p - | packageKey p `elem` broken = withF Red doc + | installedComponentId p `elem` broken = withF Red doc | exposed p = doc | otherwise = withF Blue doc where doc | verbosity >= Verbose - = termText (printf "%s (%s)" pkg ipid) + = termText (printf "%s (%s)" pkg pk) | otherwise = termText pkg where - InstalledPackageId ipid = installedPackageId p + ComponentId pk = installedComponentId p pkg = display (sourcePackageId p) is_tty <- hIsTerminalDevice stdout @@ -1332,8 +1319,8 @@ showPackageDot verbosity myflags = do mapM_ putStrLn [ quote from ++ " -> " ++ quote to | p <- all_pkgs, let from = display (sourcePackageId p), - depid <- depends p, - Just dep <- [PackageIndex.lookupInstalledPackageId ipix depid], + key <- depends p, + Just dep <- [PackageIndex.lookupComponentId ipix key], let to = display (sourcePackageId dep) ] putStrLn "}" @@ -1405,8 +1392,7 @@ findPackagesByDB db_stack pkgarg ps -> return ps where pkg_msg (Id pkgid) = display pkgid - pkg_msg (PkgKey pk) = display pk - pkg_msg (IPId ipid) = display ipid + pkg_msg (ICId ipid) = display ipid pkg_msg (Substring pkgpat _) = "matching " ++ pkgpat matches :: PackageIdentifier -> PackageIdentifier -> Bool @@ -1420,8 +1406,7 @@ realVersion pkgid = versionBranch (pkgVersion pkgid) /= [] matchesPkg :: PackageArg -> InstalledPackageInfo -> Bool (Id pid) `matchesPkg` pkg = pid `matches` sourcePackageId pkg -(PkgKey pk) `matchesPkg` pkg = pk == packageKey pkg -(IPId ipid) `matchesPkg` pkg = ipid == installedPackageId pkg +(ICId ipid) `matchesPkg` pkg = ipid == installedComponentId pkg (Substring _ m) `matchesPkg` pkg = m (display (sourcePackageId pkg)) -- ----------------------------------------------------------------------------- @@ -1509,7 +1494,7 @@ closure pkgs db_stack = go pkgs db_stack -> Bool depsAvailable pkgs_ok pkg = null dangling where dangling = filter (`notElem` pids) (depends pkg) - pids = map installedPackageId pkgs_ok + pids = map installedComponentId pkgs_ok -- we want mutually recursive groups of package to show up -- as broken. (#1750) @@ -1597,9 +1582,8 @@ checkPackageConfig :: InstalledPackageInfo -> Validate () checkPackageConfig pkg verbosity db_stack multi_instance update = do - checkInstalledPackageId pkg db_stack update checkPackageId pkg - checkPackageKey pkg + checkComponentId pkg db_stack update checkDuplicates db_stack pkg multi_instance update mapM_ (checkDep db_stack) (depends pkg) checkDuplicateDepends (depends pkg) @@ -1617,18 +1601,6 @@ checkPackageConfig pkg verbosity db_stack -- extra_libraries :: [String], -- c_includes :: [String], -checkInstalledPackageId :: InstalledPackageInfo -> PackageDBStack -> Bool - -> Validate () -checkInstalledPackageId ipi db_stack update = do - let ipid@(InstalledPackageId str) = installedPackageId ipi - when (null str) $ verror CannotForce "missing id field" - let dups = [ p | p <- allPackagesInStack db_stack, - installedPackageId p == ipid ] - when (not update && not (null dups)) $ - verror CannotForce $ - "package(s) with this id already exist: " ++ - unwords (map (display.packageId) dups) - -- When the package name and version are put together, sometimes we can -- end up with a package id that cannot be parsed. This will lead to -- difficulties when the user wants to refer to the package later, so @@ -1641,13 +1613,17 @@ checkPackageId ipi = [] -> verror CannotForce ("invalid package identifier: " ++ str) _ -> verror CannotForce ("ambiguous package identifier: " ++ str) -checkPackageKey :: InstalledPackageInfo -> Validate () -checkPackageKey ipi = - let str = display (packageKey ipi) in - case [ x :: PackageKey | (x,ys) <- readP_to_S parse str, all isSpace ys ] of - [_] -> return () - [] -> verror CannotForce ("invalid package key: " ++ str) - _ -> verror CannotForce ("ambiguous package key: " ++ str) +checkComponentId :: InstalledPackageInfo -> PackageDBStack -> Bool + -> Validate () +checkComponentId ipi db_stack update = do + let pk@(ComponentId str) = installedComponentId ipi + when (null str) $ verror CannotForce "missing id field" + let dups = [ p | p <- allPackagesInStack db_stack, + installedComponentId p == pk ] + when (not update && not (null dups)) $ + verror CannotForce $ + "package(s) with this id already exist: " ++ + unwords (map (display.installedComponentId) dups) checkDuplicates :: PackageDBStack -> InstalledPackageInfo -> Bool -> Bool-> Validate () @@ -1706,16 +1682,16 @@ checkPath url_ok is_dir warn_only thisfield d then vwarn msg else verror ForceFiles msg -checkDep :: PackageDBStack -> InstalledPackageId -> Validate () +checkDep :: PackageDBStack -> ComponentId -> Validate () checkDep db_stack pkgid | pkgid `elem` pkgids = return () | otherwise = verror ForceAll ("dependency \"" ++ display pkgid ++ "\" doesn't exist") where all_pkgs = allPackagesInStack db_stack - pkgids = map installedPackageId all_pkgs + pkgids = map installedComponentId all_pkgs -checkDuplicateDepends :: [InstalledPackageId] -> Validate () +checkDuplicateDepends :: [ComponentId] -> Validate () checkDuplicateDepends deps | null dups = return () | otherwise = verror ForceAll ("package has duplicate dependencies: " ++ @@ -1799,9 +1775,9 @@ checkOriginalModule :: String -> Validate () checkOriginalModule field_name db_stack pkg (OriginalModule definingPkgId definingModule) = - let mpkg = if definingPkgId == installedPackageId pkg + let mpkg = if definingPkgId == installedComponentId pkg then Just pkg - else PackageIndex.lookupInstalledPackageId ipix definingPkgId + else PackageIndex.lookupComponentId ipix definingPkgId in case mpkg of Nothing -> verror ForceAll (field_name ++ " refers to a non-existent " ++ @@ -1810,7 +1786,7 @@ checkOriginalModule field_name db_stack pkg Just definingPkg | not (isIndirectDependency definingPkgId) - -> verror ForceAll (field_name ++ " refers to a defining " ++ + -> verror ForceAll (field_name ++ " refers to a defining " ++ "package that is not a direct (or indirect) " ++ "dependency of this package: " ++ display definingPkgId) @@ -1835,7 +1811,7 @@ checkOriginalModule field_name db_stack pkg ipix = PackageIndex.fromList all_pkgs isIndirectDependency pkgid = fromMaybe False $ do - thispkg <- graphVertex (installedPackageId pkg) + thispkg <- graphVertex (installedComponentId pkg) otherpkg <- graphVertex pkgid return (Graph.path depgraph thispkg otherpkg) (depgraph, _, graphVertex) = |