diff --git a/Cabal-syntax/Cabal-syntax.cabal b/Cabal-syntax/Cabal-syntax.cabal index 1bc8bcabeb2..3ece9dc516f 100644 --- a/Cabal-syntax/Cabal-syntax.cabal +++ b/Cabal-syntax/Cabal-syntax.cabal @@ -135,6 +135,7 @@ library Distribution.Types.ConfVar Distribution.Types.Dependency Distribution.Types.DependencyMap + Distribution.Types.DependencySatisfaction Distribution.Types.ExeDependency Distribution.Types.Executable Distribution.Types.Executable.Lens @@ -158,6 +159,8 @@ library Distribution.Types.Library.Lens Distribution.Types.LibraryName Distribution.Types.LibraryVisibility + Distribution.Types.MissingDependency + Distribution.Types.MissingDependencyReason Distribution.Types.Mixin Distribution.Types.Module Distribution.Types.ModuleReexport diff --git a/Cabal-syntax/src/Distribution/Compat/NonEmptySet.hs b/Cabal-syntax/src/Distribution/Compat/NonEmptySet.hs index 17e3811e9a4..9e227459e84 100644 --- a/Cabal-syntax/src/Distribution/Compat/NonEmptySet.hs +++ b/Cabal-syntax/src/Distribution/Compat/NonEmptySet.hs @@ -12,6 +12,7 @@ module Distribution.Compat.NonEmptySet -- * Deletion , delete + , filter -- * Conversions , toNonEmpty @@ -116,6 +117,9 @@ delete x (NES xs) where res = Set.delete x xs +filter :: (a -> Bool) -> NonEmptySet a -> Set.Set a +filter predicate (NES set) = Set.filter predicate set + ------------------------------------------------------------------------------- -- Conversions ------------------------------------------------------------------------------- diff --git a/Cabal-syntax/src/Distribution/PackageDescription/Configuration.hs b/Cabal-syntax/src/Distribution/PackageDescription/Configuration.hs index e811c361221..eebf760094d 100644 --- a/Cabal-syntax/src/Distribution/PackageDescription/Configuration.hs +++ b/Cabal-syntax/src/Distribution/PackageDescription/Configuration.hs @@ -56,12 +56,13 @@ import Distribution.System import Distribution.Types.Component import Distribution.Types.ComponentRequestedSpec import Distribution.Types.DependencyMap +import Distribution.Types.DependencySatisfaction (DependencySatisfaction (..)) +import Distribution.Types.MissingDependency (MissingDependency (..)) import Distribution.Types.PackageVersionConstraint import Distribution.Utils.Generic import Distribution.Utils.Path (sameDirectory) import Distribution.Version -import qualified Data.Map.Lazy as Map import Data.Tree (Tree (Node)) ------------------------------------------------------------------------------ @@ -144,15 +145,17 @@ parseCondition = condOr ------------------------------------------------------------------------------ --- | Result of dependency test. Isomorphic to @Maybe d@ but renamed for +-- | Result of dependency test. Isomorphic to @Maybe@ but renamed for -- clarity. -data DepTestRslt d = DepOk | MissingDeps d +data DepTestRslt + = DepOk + | MissingDeps [MissingDependency] -instance Semigroup d => Monoid (DepTestRslt d) where +instance Monoid DepTestRslt where mempty = DepOk mappend = (<>) -instance Semigroup d => Semigroup (DepTestRslt d) where +instance Semigroup DepTestRslt where DepOk <> x = x x <> DepOk = x (MissingDeps d) <> (MissingDeps d') = MissingDeps (d <> d') @@ -190,13 +193,13 @@ resolveWithFlags -> [PackageVersionConstraint] -- ^ Additional constraints -> [CondTree ConfVar [Dependency] PDTagged] - -> ([Dependency] -> DepTestRslt [Dependency]) + -> ([Dependency] -> DepTestRslt) -- ^ Dependency test function. - -> Either [Dependency] (TargetSet PDTagged, FlagAssignment) + -> Either [MissingDependency] (TargetSet PDTagged, FlagAssignment) -- ^ Either the missing dependencies (error case), or a pair of -- (set of build targets with dependencies, chosen flag assignments) resolveWithFlags dom enabled os arch impl constrs trees checkDeps = - either (Left . fromDepMapUnion) Right $ explore (build mempty dom) + explore (build mempty dom) where -- simplify trees by (partially) evaluating all conditions and converting -- dependencies to dependency maps. @@ -216,7 +219,7 @@ resolveWithFlags dom enabled os arch impl constrs trees checkDeps = -- computation overhead in the successful case. explore :: Tree FlagAssignment - -> Either DepMapUnion (TargetSet PDTagged, FlagAssignment) + -> Either [MissingDependency] (TargetSet PDTagged, FlagAssignment) explore (Node flags ts) = let targetSet = TargetSet $ @@ -229,7 +232,7 @@ resolveWithFlags dom enabled os arch impl constrs trees checkDeps = DepOk | null ts -> Right (targetSet, flags) | otherwise -> tryAll $ map explore ts - MissingDeps mds -> Left (toDepMapUnion mds) + MissingDeps mds -> Left mds -- Builds a tree of all possible flag assignments. Internal nodes -- have only partial assignments. @@ -238,18 +241,18 @@ resolveWithFlags dom enabled os arch impl constrs trees checkDeps = build assigned ((fn, vals) : unassigned) = Node assigned $ map (\v -> build (insertFlagAssignment fn v assigned) unassigned) vals - tryAll :: [Either DepMapUnion a] -> Either DepMapUnion a + tryAll :: Monoid a => [Either a b] -> Either a b tryAll = foldr mp mz -- special version of `mplus' for our local purposes - mp :: Either DepMapUnion a -> Either DepMapUnion a -> Either DepMapUnion a + mp :: Monoid a => Either a b -> Either a b -> Either a b mp m@(Right _) _ = m mp _ m@(Right _) = m mp (Left xs) (Left ys) = Left (xs <> ys) -- `mzero' - mz :: Either DepMapUnion a - mz = Left (DepMapUnion Map.empty) + mz :: Monoid a => Either a b + mz = Left mempty env :: FlagAssignment -> FlagName -> Either FlagName Bool env flags flag = (maybe (Left flag) Right . lookupFlagAssignment flag) flags @@ -323,27 +326,6 @@ extractConditions f gpkg = , extractCondition (f . benchmarkBuildInfo) . snd <$> condBenchmarks gpkg ] --- | A map of package constraints that combines version ranges using 'unionVersionRanges'. -newtype DepMapUnion = DepMapUnion {unDepMapUnion :: Map PackageName (VersionRange, NonEmptySet LibraryName)} - -instance Semigroup DepMapUnion where - DepMapUnion x <> DepMapUnion y = - DepMapUnion $ - Map.unionWith unionVersionRanges' x y - -unionVersionRanges' - :: (VersionRange, NonEmptySet LibraryName) - -> (VersionRange, NonEmptySet LibraryName) - -> (VersionRange, NonEmptySet LibraryName) -unionVersionRanges' (vr, cs) (vr', cs') = (unionVersionRanges vr vr', cs <> cs') - -toDepMapUnion :: [Dependency] -> DepMapUnion -toDepMapUnion ds = - DepMapUnion $ Map.fromListWith unionVersionRanges' [(p, (vr, cs)) | Dependency p vr cs <- ds] - -fromDepMapUnion :: DepMapUnion -> [Dependency] -fromDepMapUnion m = [Dependency p vr cs | (p, (vr, cs)) <- Map.toList (unDepMapUnion m)] - freeVars :: CondTree ConfVar c a -> [FlagName] freeVars t = [f | PackageFlag f <- freeVars' t] where @@ -453,7 +435,7 @@ finalizePD :: FlagAssignment -- ^ Explicitly specified flag assignments -> ComponentRequestedSpec - -> (Dependency -> Bool) + -> (Dependency -> DependencySatisfaction) -- ^ Is a given dependency satisfiable from the set of -- available packages? If this is unknown then use -- True. @@ -465,7 +447,7 @@ finalizePD -- ^ Additional constraints -> GenericPackageDescription -> Either - [Dependency] + [MissingDependency] (PackageDescription, FlagAssignment) -- ^ Either missing dependencies or the resolved package -- description along with the flag assignments chosen. @@ -526,7 +508,11 @@ finalizePD | otherwise -> [b, not b] -- flagDefaults = map (\(n,x:_) -> (n,x)) flagChoices check ds = - let missingDeps = filter (not . satisfyDep) ds + let missingDeps = + [ MissingDependency dependency reason + | (dependency, Unsatisfied reason) <- + map (\dependency -> (dependency, satisfyDep dependency)) ds + ] in if null missingDeps then DepOk else MissingDeps missingDeps diff --git a/Cabal-syntax/src/Distribution/Pretty.hs b/Cabal-syntax/src/Distribution/Pretty.hs index 3ddb806d81b..fcb0a7f0d0b 100644 --- a/Cabal-syntax/src/Distribution/Pretty.hs +++ b/Cabal-syntax/src/Distribution/Pretty.hs @@ -10,6 +10,8 @@ module Distribution.Pretty , showTokenStr , showFreeText , showFreeTextV3 + , commaSpaceSep + , commaSep -- * Deprecated , Separator @@ -118,3 +120,11 @@ lines_ s = in l : case s' of [] -> [] (_ : s'') -> lines_ s'' + +-- | Separate a list of documents by commas and spaces. +commaSpaceSep :: Pretty a => [a] -> PP.Doc +commaSpaceSep = PP.hsep . PP.punctuate PP.comma . map pretty + +-- | Separate a list of documents by commas. +commaSep :: Pretty a => [a] -> PP.Doc +commaSep = PP.hcat . PP.punctuate PP.comma . map pretty diff --git a/Cabal-syntax/src/Distribution/Types/Dependency.hs b/Cabal-syntax/src/Distribution/Types/Dependency.hs index 222a699a3f9..a152c9e3a68 100644 --- a/Cabal-syntax/src/Distribution/Types/Dependency.hs +++ b/Cabal-syntax/src/Distribution/Types/Dependency.hs @@ -78,31 +78,21 @@ instance NFData Dependency where rnf = genericRnf -- "pkg" -- -- >>> prettyShow $ Dependency (mkPackageName "pkg") anyVersion $ NES.insert (LSubLibName $ mkUnqualComponentName "sublib") mainLibSet --- "pkg:{pkg, sublib}" +-- "pkg:{pkg,sublib}" -- -- >>> prettyShow $ Dependency (mkPackageName "pkg") anyVersion $ NES.singleton (LSubLibName $ mkUnqualComponentName "sublib") -- "pkg:sublib" -- -- >>> prettyShow $ Dependency (mkPackageName "pkg") anyVersion $ NES.insert (LSubLibName $ mkUnqualComponentName "sublib-b") $ NES.singleton (LSubLibName $ mkUnqualComponentName "sublib-a") --- "pkg:{sublib-a, sublib-b}" +-- "pkg:{sublib-a,sublib-b}" instance Pretty Dependency where - pretty (Dependency name ver sublibs) = withSubLibs (pretty name) <+> pver + pretty (Dependency name ver sublibs) = prettyLibraryNames name (NES.toNonEmpty sublibs) <+> pver where -- TODO: change to isAnyVersion after #6736 pver | isAnyVersionLight ver = PP.empty | otherwise = pretty ver - withSubLibs doc = case NES.toList sublibs of - [LMainLibName] -> doc - [LSubLibName uq] -> doc <<>> PP.colon <<>> pretty uq - _ -> doc <<>> PP.colon <<>> PP.braces prettySublibs - - prettySublibs = PP.hsep $ PP.punctuate PP.comma $ prettySublib <$> NES.toList sublibs - - prettySublib LMainLibName = PP.text $ unPackageName name - prettySublib (LSubLibName un) = PP.text $ unUnqualComponentName un - -- | -- -- >>> simpleParsec "mylib:sub" :: Maybe Dependency diff --git a/Cabal-syntax/src/Distribution/Types/DependencySatisfaction.hs b/Cabal-syntax/src/Distribution/Types/DependencySatisfaction.hs new file mode 100644 index 00000000000..56ce74c1c45 --- /dev/null +++ b/Cabal-syntax/src/Distribution/Types/DependencySatisfaction.hs @@ -0,0 +1,14 @@ +module Distribution.Types.DependencySatisfaction + ( DependencySatisfaction (..) + ) where + +import Distribution.Types.MissingDependencyReason (MissingDependencyReason) + +-- | Whether or not a dependency constraint is satisfied. +data DependencySatisfaction + = -- | The dependency constraint is satisfied. + Satisfied + | -- | The dependency constraint is not satisfied. + -- + -- Includes a reason for explanation. + Unsatisfied MissingDependencyReason diff --git a/Cabal-syntax/src/Distribution/Types/LibraryName.hs b/Cabal-syntax/src/Distribution/Types/LibraryName.hs index 2b8f53f4f89..9073aae9a1f 100644 --- a/Cabal-syntax/src/Distribution/Types/LibraryName.hs +++ b/Cabal-syntax/src/Distribution/Types/LibraryName.hs @@ -10,6 +10,7 @@ module Distribution.Types.LibraryName , libraryNameString -- * Pretty & Parse + , prettyLibraryNames , prettyLibraryNameComponent , parsecLibraryNameComponent ) where @@ -17,6 +18,7 @@ module Distribution.Types.LibraryName import Distribution.Compat.Prelude import Prelude () +import qualified Data.List.NonEmpty as NEL import Distribution.Parsec import Distribution.Pretty import Distribution.Types.UnqualComponentName @@ -42,6 +44,22 @@ prettyLibraryNameComponent :: LibraryName -> Disp.Doc prettyLibraryNameComponent LMainLibName = Disp.text "lib" prettyLibraryNameComponent (LSubLibName str) = Disp.text "lib:" <<>> pretty str +-- | Pretty print a 'LibraryName' after a package name. +-- +-- Produces output like @foo@, @foo:bar@, or @foo:{bar,baz}@ +prettyLibraryNames :: Pretty a => a -> NonEmpty LibraryName -> Disp.Doc +prettyLibraryNames package libraries = + let doc = pretty package + + prettyComponent LMainLibName = pretty package + prettyComponent (LSubLibName component) = Disp.text $ unUnqualComponentName component + + prettyComponents = commaSep $ prettyComponent <$> NEL.toList libraries + in case libraries of + LMainLibName :| [] -> doc + LSubLibName component :| [] -> doc <<>> Disp.colon <<>> pretty component + _ -> doc <<>> Disp.colon <<>> Disp.braces prettyComponents + parsecLibraryNameComponent :: CabalParsing m => m LibraryName parsecLibraryNameComponent = do _ <- P.string "lib" diff --git a/Cabal-syntax/src/Distribution/Types/MissingDependency.hs b/Cabal-syntax/src/Distribution/Types/MissingDependency.hs new file mode 100644 index 00000000000..57d90276d8c --- /dev/null +++ b/Cabal-syntax/src/Distribution/Types/MissingDependency.hs @@ -0,0 +1,34 @@ +module Distribution.Types.MissingDependency + ( MissingDependency (..) + ) where + +import Distribution.Compat.Prelude +import Distribution.Pretty +import Distribution.Types.Dependency + ( Dependency + , simplifyDependency + ) +import Distribution.Types.LibraryName + ( prettyLibraryNames + ) +import Distribution.Types.MissingDependencyReason + ( MissingDependencyReason (..) + ) + +import qualified Text.PrettyPrint as PP + +-- | A missing dependency and information on why it's missing. +data MissingDependency = MissingDependency Dependency MissingDependencyReason + deriving (Show) + +instance Pretty MissingDependency where + pretty (MissingDependency dependency reason) = + let prettyReason = + case reason of + MissingLibrary libraries -> + PP.text "missing" <+> prettyLibraryNames PP.empty libraries + MissingPackage -> PP.text "missing" + MissingComponent name -> PP.text "missing component" <+> pretty name + WrongVersion versions -> + PP.text "installed:" <+> commaSpaceSep versions + in pretty (simplifyDependency dependency) <+> PP.parens prettyReason diff --git a/Cabal-syntax/src/Distribution/Types/MissingDependencyReason.hs b/Cabal-syntax/src/Distribution/Types/MissingDependencyReason.hs new file mode 100644 index 00000000000..c1c37800f21 --- /dev/null +++ b/Cabal-syntax/src/Distribution/Types/MissingDependencyReason.hs @@ -0,0 +1,25 @@ +module Distribution.Types.MissingDependencyReason + ( MissingDependencyReason (..) + ) where + +import Data.List.NonEmpty (NonEmpty) +import Distribution.Types.LibraryName (LibraryName) +import Distribution.Types.PackageName (PackageName) +import Distribution.Types.Version (Version) + +-- | A reason for a depency failing to solve. +-- +-- This helps pinpoint dependencies that are installed with an incorrect +-- version vs. dependencies that are not installed at all. +data MissingDependencyReason + = -- | One or more libraries is missing. + MissingLibrary (NonEmpty LibraryName) + | -- | A package is not installed. + MissingPackage + | -- | A package is installed, but the versions don't match. + -- + -- Contains the available versions. + WrongVersion [Version] + | -- | A component is not installed. + MissingComponent PackageName + deriving (Show) diff --git a/Cabal-tests/tests/ParserTests/regressions/issue-5846.format b/Cabal-tests/tests/ParserTests/regressions/issue-5846.format index 749a9c20524..93e53fc48bd 100644 --- a/Cabal-tests/tests/ParserTests/regressions/issue-5846.format +++ b/Cabal-tests/tests/ParserTests/regressions/issue-5846.format @@ -5,7 +5,7 @@ version: 5846 library default-language: Haskell2010 build-depends: - lib1:{a, b}, + lib1:{a,b}, lib2:c, lib3:d >=1, - lib4:{a, b} >=1 + lib4:{a,b} >=1 diff --git a/Cabal/Cabal.cabal b/Cabal/Cabal.cabal index 14e7050c5db..1e98be1a99c 100644 --- a/Cabal/Cabal.cabal +++ b/Cabal/Cabal.cabal @@ -248,6 +248,7 @@ library Distribution.Types.ConfVar, Distribution.Types.Dependency, Distribution.Types.DependencyMap, + Distribution.Types.DependencySatisfaction, Distribution.Types.ExeDependency, Distribution.Types.Executable, Distribution.Types.Executable.Lens, @@ -271,6 +272,8 @@ library Distribution.Types.Library.Lens, Distribution.Types.LibraryName, Distribution.Types.LibraryVisibility, + Distribution.Types.MissingDependency, + Distribution.Types.MissingDependencyReason, Distribution.Types.Mixin, Distribution.Types.Module, Distribution.Types.ModuleReexport, diff --git a/Cabal/src/Distribution/Simple/Configure.hs b/Cabal/src/Distribution/Simple/Configure.hs index 04929bad030..b3d0b28d462 100644 --- a/Cabal/src/Distribution/Simple/Configure.hs +++ b/Cabal/src/Distribution/Simple/Configure.hs @@ -106,9 +106,11 @@ import qualified Distribution.Simple.SetupHooks.Internal as SetupHooks import Distribution.Simple.Utils import Distribution.System import Distribution.Types.ComponentRequestedSpec +import Distribution.Types.DependencySatisfaction (DependencySatisfaction (..)) import Distribution.Types.GivenComponent import qualified Distribution.Types.LocalBuildConfig as LBC import Distribution.Types.LocalBuildInfo +import Distribution.Types.MissingDependencyReason (MissingDependencyReason (..)) import Distribution.Types.PackageVersionConstraint import Distribution.Utils.LogProgress import Distribution.Utils.NubList @@ -1480,7 +1482,7 @@ dependencySatisfiable -> Map (PackageName, ComponentName) ComponentId -> Map (PackageName, ComponentName) InstalledPackageInfo -- ^ required dependencies - -> (Dependency -> Bool) + -> (Dependency -> DependencySatisfaction) dependencySatisfiable use_external_internal_deps exact_config @@ -1506,16 +1508,18 @@ dependencySatisfiable internalDepSatisfiable else -- Backward compatibility for the old sublibrary syntax - ( sublibs == mainLibSet - && Map.member - ( pn - , CLibName $ - LSubLibName $ - packageNameToUnqualComponentName depName - ) - requiredDepsMap - ) - || all visible sublibs + if sublibs == mainLibSet + then + let depComponentName = + CLibName $ LSubLibName $ packageNameToUnqualComponentName depName + in if Map.member (pn, depComponentName) requiredDepsMap + then Satisfied + else Unsatisfied $ MissingComponent depName + else + let invisibleLibraries = NES.filter (not . visible) sublibs + in case nonEmpty $ Set.toList invisibleLibraries of + Nothing -> Satisfied + Just invisibleLibraries' -> Unsatisfied $ MissingLibrary invisibleLibraries' | isInternalDep = if use_external_internal_deps then -- When we are doing per-component configure, we now need to @@ -1532,12 +1536,31 @@ dependencySatisfiable isInternalDep = pn == depName depSatisfiable = - not . null $ PackageIndex.lookupDependency installedPackageSet depName vr + let allVersions = PackageIndex.lookupPackageName installedPackageSet depName + eligibleVersions = + [ version + | (version, _infos) <- PackageIndex.eligibleDependencies allVersions + ] + in if null $ PackageIndex.matchingDependencies vr allVersions + then + if null eligibleVersions + then Unsatisfied $ MissingPackage + else Unsatisfied $ WrongVersion eligibleVersions + else Satisfied internalDepSatisfiable = - Set.isSubsetOf (NES.toSet sublibs) packageLibraries + let missingLibraries = (NES.toSet sublibs) `Set.difference` packageLibraries + in case nonEmpty $ Set.toList missingLibraries of + Nothing -> Satisfied + Just missingLibraries' -> Unsatisfied $ MissingLibrary missingLibraries' + internalDepSatisfiableExternally = - all (\ln -> not $ null $ PackageIndex.lookupInternalDependency installedPackageSet pn vr ln) sublibs + -- TODO: Might need to propagate information on which versions _are_ available, if any... + let missingLibraries = + NES.filter (null . PackageIndex.lookupInternalDependency installedPackageSet pn vr) sublibs + in case nonEmpty $ Set.toList missingLibraries of + Nothing -> Satisfied + Just missingLibraries' -> Unsatisfied $ MissingLibrary missingLibraries' -- Check whether a library exists and is visible. -- We don't disambiguate between dependency on non-existent or private @@ -1572,7 +1595,7 @@ configureFinalizedPackage -> ConfigFlags -> ComponentRequestedSpec -> [PackageVersionConstraint] - -> (Dependency -> Bool) + -> (Dependency -> DependencySatisfaction) -- ^ tests if a dependency is satisfiable. -- Might say it's satisfiable even when not. -> Compiler diff --git a/Cabal/src/Distribution/Simple/Errors.hs b/Cabal/src/Distribution/Simple/Errors.hs index c1cc75b5ad1..253b2f0dfbe 100644 --- a/Cabal/src/Distribution/Simple/Errors.hs +++ b/Cabal/src/Distribution/Simple/Errors.hs @@ -31,6 +31,7 @@ import Distribution.Simple.InstallDirs import Distribution.Simple.PreProcess.Types (Suffix) import Distribution.Simple.SetupHooks.Errors import Distribution.System (OS) +import Distribution.Types.MissingDependency (MissingDependency) import Distribution.Types.VersionRange.Internal () import Distribution.Version import Text.PrettyPrint @@ -126,7 +127,7 @@ data CabalException | CantFindForeignLibraries [String] | ExpectedAbsoluteDirectory FilePath | FlagsNotSpecified [FlagName] - | EncounteredMissingDependency [Dependency] + | EncounteredMissingDependency [MissingDependency] | CompilerDoesn'tSupportThinning | CompilerDoesn'tSupportReexports | CompilerDoesn'tSupportBackpack @@ -552,7 +553,7 @@ exceptionMessage e = case e of . nest 4 . sep . punctuate comma - . map (pretty . simplifyDependency) + . map pretty $ missing ) CompilerDoesn'tSupportThinning -> diff --git a/Cabal/src/Distribution/Simple/PackageIndex.hs b/Cabal/src/Distribution/Simple/PackageIndex.hs index 927e10ae878..e6944430755 100644 --- a/Cabal/src/Distribution/Simple/PackageIndex.hs +++ b/Cabal/src/Distribution/Simple/PackageIndex.hs @@ -68,6 +68,7 @@ module Distribution.Simple.PackageIndex , lookupSourcePackageId , lookupPackageId , lookupPackageName + , lookupInternalPackageName , lookupDependency , lookupInternalDependency @@ -93,6 +94,10 @@ module Distribution.Simple.PackageIndex , dependencyCycles , dependencyGraph , moduleNameIndex + + -- ** Filters on lookup results + , eligibleDependencies + , matchingDependencies ) where import qualified Data.Map.Strict as Map @@ -474,7 +479,18 @@ lookupPackageName -> [(Version, [a])] lookupPackageName index name = -- Do not match internal libraries - case Map.lookup (name, LMainLibName) (packageIdIndex index) of + lookupInternalPackageName index name LMainLibName + +-- | Does a lookup by source package name and library name. +-- +-- Also looks up internal packages. +lookupInternalPackageName + :: PackageIndex a + -> PackageName + -> LibraryName + -> [(Version, [a])] +lookupInternalPackageName index name library = + case Map.lookup (name, library) (packageIdIndex index) of Nothing -> [] Just pvers -> Map.toList pvers @@ -509,23 +525,46 @@ lookupInternalDependency -> LibraryName -> [(Version, [IPI.InstalledPackageInfo])] lookupInternalDependency index name versionRange libn = - case Map.lookup (name, libn) (packageIdIndex index) of - Nothing -> [] - Just pvers -> - [ (ver, pkgs') - | (ver, pkgs) <- Map.toList pvers - , ver `withinRange` versionRange - , let pkgs' = filter eligible pkgs - , -- Enforce the invariant - not (null pkgs') - ] + matchingDependencies versionRange $ + lookupInternalPackageName index name libn + +-- | Filter a set of installed packages to ones eligible as dependencies. +-- +-- When we select for dependencies, we ONLY want to pick up indefinite +-- packages, or packages with no instantiations. We'll do mix-in linking to +-- improve any such package into an instantiated one later. +-- +-- INVARIANT: List of eligible 'IPI.InstalledPackageInfo' is non-empty. +eligibleDependencies + :: [(Version, [IPI.InstalledPackageInfo])] + -> [(Version, [IPI.InstalledPackageInfo])] +eligibleDependencies versions = + [ (ver, pkgs') + | (ver, pkgs) <- versions + , let pkgs' = filter eligible pkgs + , -- Enforce the invariant + not (null pkgs') + ] where - -- When we select for dependencies, we ONLY want to pick up indefinite - -- packages, or packages with no instantiations. We'll do mix-in - -- linking to improve any such package into an instantiated one - -- later. eligible pkg = IPI.indefinite pkg || null (IPI.instantiatedWith pkg) +-- | Get eligible dependencies from a list of versions. +-- +-- This can be used to filter the output of 'lookupPackageName' or +-- 'lookupInternalPackageName'. +-- +-- INVARIANT: List of eligible 'IPI.InstalledPackageInfo' is non-empty. +matchingDependencies + :: VersionRange + -> [(Version, [IPI.InstalledPackageInfo])] + -> [(Version, [IPI.InstalledPackageInfo])] +matchingDependencies versionRange versions = + let eligibleVersions = eligibleDependencies versions + in [ (ver, pkgs) + | (ver, pkgs) <- eligibleVersions + , ver `withinRange` versionRange + ] + -- -- * Case insensitive name lookups diff --git a/cabal-install/src/Distribution/Client/CmdOutdated.hs b/cabal-install/src/Distribution/Client/CmdOutdated.hs index ed40a1a85e6..7674e67286f 100644 --- a/cabal-install/src/Distribution/Client/CmdOutdated.hs +++ b/cabal-install/src/Distribution/Client/CmdOutdated.hs @@ -129,6 +129,9 @@ import Distribution.Types.ComponentRequestedSpec import Distribution.Types.Dependency ( Dependency (..) ) +import Distribution.Types.DependencySatisfaction + ( DependencySatisfaction (..) + ) import Distribution.Types.PackageVersionConstraint ( PackageVersionConstraint (..) , simplifyPackageVersionConstraint @@ -443,7 +446,7 @@ depsFromPkgDesc verbosity comp platform = do finalizePD mempty (ComponentRequestedSpec True True) - (const True) + (const Satisfied) platform cinfo [] diff --git a/cabal-install/src/Distribution/Client/Configure.hs b/cabal-install/src/Distribution/Client/Configure.hs index 0586a362dd2..34cd4dfea71 100644 --- a/cabal-install/src/Distribution/Client/Configure.hs +++ b/cabal-install/src/Distribution/Client/Configure.hs @@ -116,6 +116,9 @@ import Distribution.Simple.Utils as Utils import Distribution.System ( Platform ) +import Distribution.Types.DependencySatisfaction + ( DependencySatisfaction (..) + ) import Distribution.Types.GivenComponent ( GivenComponent (..) ) @@ -555,7 +558,7 @@ configurePackage pkg = case finalizePD flags (enableStanzas stanzas) - (const True) + (const Satisfied) platform comp [] diff --git a/cabal-install/src/Distribution/Client/Dependency.hs b/cabal-install/src/Distribution/Client/Dependency.hs index ae731cdc64b..d59bc611c44 100644 --- a/cabal-install/src/Distribution/Client/Dependency.hs +++ b/cabal-install/src/Distribution/Client/Dependency.hs @@ -127,6 +127,9 @@ import Distribution.System ( Platform ) import Distribution.Types.Dependency +import Distribution.Types.DependencySatisfaction + ( DependencySatisfaction (..) + ) import Distribution.Verbosity ( normal ) @@ -1092,7 +1095,7 @@ configuredPackageProblems case finalizePD specifiedFlags compSpec - (const True) + (const Satisfied) platform cinfo [] diff --git a/cabal-install/src/Distribution/Client/GenBounds.hs b/cabal-install/src/Distribution/Client/GenBounds.hs index ae78b50c004..0a49f185834 100644 --- a/cabal-install/src/Distribution/Client/GenBounds.hs +++ b/cabal-install/src/Distribution/Client/GenBounds.hs @@ -67,6 +67,9 @@ import Distribution.Types.ComponentRequestedSpec ( defaultComponentRequestedSpec ) import Distribution.Types.Dependency +import Distribution.Types.DependencySatisfaction + ( DependencySatisfaction (..) + ) import Distribution.Utils.Path (relativeSymbolicPath) import Distribution.Version ( LowerBound (..) @@ -138,7 +141,7 @@ genBounds verbosity packageDBs repoCtxt comp platform progdb globalFlags freezeF finalizePD mempty defaultComponentRequestedSpec - (const True) + (const Satisfied) platform cinfo [] diff --git a/cabal-install/src/Distribution/Client/Install.hs b/cabal-install/src/Distribution/Client/Install.hs index 9cf80d3858c..aefc8ef3287 100644 --- a/cabal-install/src/Distribution/Client/Install.hs +++ b/cabal-install/src/Distribution/Client/Install.hs @@ -245,6 +245,9 @@ import Distribution.System , buildOS , buildPlatform ) +import Distribution.Types.DependencySatisfaction + ( DependencySatisfaction (..) + ) import Distribution.Types.Flag ( FlagAssignment , PackageFlag (..) @@ -1677,7 +1680,7 @@ installReadyPackage pkg = case finalizePD flags (enableStanzas stanzas) - (const True) + (const Satisfied) platform cinfo [] diff --git a/cabal-install/src/Distribution/Client/InstallSymlink.hs b/cabal-install/src/Distribution/Client/InstallSymlink.hs index 7a470843779..46e1edaebef 100644 --- a/cabal-install/src/Distribution/Client/InstallSymlink.hs +++ b/cabal-install/src/Distribution/Client/InstallSymlink.hs @@ -74,6 +74,9 @@ import Distribution.Simple.Utils (info, withTempDirectory) import Distribution.System ( Platform ) +import Distribution.Types.DependencySatisfaction + ( DependencySatisfaction (..) + ) import Distribution.Types.UnqualComponentName import System.Directory @@ -205,7 +208,7 @@ symlinkBinaries case finalizePD flags (enableStanzas stanzas) - (const True) + (const Satisfied) platform cinfo [] diff --git a/cabal-install/src/Distribution/Client/ProjectPlanning.hs b/cabal-install/src/Distribution/Client/ProjectPlanning.hs index 4efa5f313b1..4e5f1cb4918 100644 --- a/cabal-install/src/Distribution/Client/ProjectPlanning.hs +++ b/cabal-install/src/Distribution/Client/ProjectPlanning.hs @@ -176,6 +176,9 @@ import Distribution.System import Distribution.Types.AnnotatedId import Distribution.Types.ComponentInclude import Distribution.Types.ComponentName +import Distribution.Types.DependencySatisfaction + ( DependencySatisfaction (..) + ) import Distribution.Types.DumpBuildInfo import Distribution.Types.GivenComponent import Distribution.Types.LibraryName @@ -2130,7 +2133,7 @@ elaborateInstallPlan elabPkgDescription = case PD.finalizePD flags elabEnabledSpec - (const True) + (const Satisfied) platform (compilerInfo compiler) [] diff --git a/cabal-testsuite/PackageTests/ConfigureComponent/SubLib/setup-explicit-fail.out b/cabal-testsuite/PackageTests/ConfigureComponent/SubLib/setup-explicit-fail.out index fec347864e5..da9de233fab 100644 --- a/cabal-testsuite/PackageTests/ConfigureComponent/SubLib/setup-explicit-fail.out +++ b/cabal-testsuite/PackageTests/ConfigureComponent/SubLib/setup-explicit-fail.out @@ -11,4 +11,5 @@ Registering library 'sublib' for Lib-0.1.0.0... Configuring executable 'exe' for Lib-0.1.0.0... Error: [Cabal-8010] Encountered missing or private dependencies: - Lib:sublib + Lib:sublib (missing :sublib), + base ==4.20.0.0 (missing component base)