From 2dc621016f7323bcc9acb702e4f0da63110b0449 Mon Sep 17 00:00:00 2001 From: "Edward Z. Yang" Date: Fri, 30 Dec 2016 18:15:46 -0500 Subject: [PATCH] Distinguish between internal and external libraries in `build-depends` Fixes #4155. We create a new `LibDependency` just used for parsing `build-depends` entries for now, but I hope it has a bright future in the brave new per-component world. Already in 'Cabal', this type will be used instead of 'Dependency' in most cases, implemented in the following commits of this PR. Used in: - Condition Trees - Querying the PackageIndex ----- Not sure about which type should have the (not)ThisPackageVersion function Also need to update some comments. Everything builds, however. --- Cabal/Cabal.cabal | 2 + .../Distribution/Backpack/ComponentsGraph.hs | 22 +- .../Backpack/ConfiguredComponent.hs | 118 +++++----- .../Distribution/PackageDescription/Check.hs | 53 +++-- .../PackageDescription/Configuration.hs | 115 ++++++---- .../Distribution/PackageDescription/Parse.hs | 26 +-- .../PackageDescription/PrettyPrint.hs | 20 +- Cabal/Distribution/Parsec/Class.hs | 16 +- Cabal/Distribution/Simple/Build.hs | 10 +- Cabal/Distribution/Simple/Configure.hs | 201 +++++++----------- Cabal/Distribution/Simple/PackageIndex.hs | 201 +++++++++--------- Cabal/Distribution/Simple/Setup.hs | 14 +- Cabal/Distribution/Types/BuildInfo.hs | 27 ++- Cabal/Distribution/Types/DependencyMap.hs | 26 +-- Cabal/Distribution/Types/ExeDependency.hs | 11 +- .../Types/GenericPackageDescription.hs | 14 +- Cabal/Distribution/Types/LibDependency.hs | 60 ++++++ Cabal/Distribution/Types/LibDependencyMap.hs | 99 +++++++++ Cabal/Distribution/Types/Mixin.hs | 13 +- .../Distribution/Types/PackageDescription.hs | 6 +- Cabal/Distribution/Types/SetupBuildInfo.hs | 2 + Cabal/doc/developing-packages.rst | 18 +- Cabal/tests/ParserHackageTests.hs | 6 +- .../Distribution/Client/Configure.hs | 8 +- .../Distribution/Client/GenBounds.hs | 15 +- cabal-install/Distribution/Client/Install.hs | 9 +- cabal-install/Distribution/Client/List.hs | 11 +- cabal-install/Distribution/Client/Outdated.hs | 4 +- .../Distribution/Client/PackageUtils.hs | 27 +-- .../Distribution/Client/ProjectPlanning.hs | 10 +- .../Distribution/Client/SetupWrapper.hs | 4 +- .../Solver/Modular/IndexConversion.hs | 62 ++---- .../Distribution/Solver/Modular/DSL.hs | 16 +- .../PackageTests/Backpack/Fail1/Fail1.cabal | 3 +- .../Backpack/Includes2/Includes2.cabal | 8 +- .../Backpack/Includes3/Includes3.cabal | 6 +- .../Backpack/Includes4/Includes4.cabal | 4 +- .../Backpack/Includes5/Includes5.cabal | 9 +- .../PackageTests/Backpack/Indef2/Indef2.cabal | 2 +- .../BuildDeps/DepCycle/DepCycle.cabal | 4 +- .../PackageTests/CaretOperator/setup.test.hs | 4 +- .../ConfigureComponent/SubLib/Lib.cabal | 2 +- .../InternalLibraries/Executable/foo.cabal | 2 +- .../Library/foolib/foolib.cabal | 2 +- .../PackageTests/InternalLibraries/p/p.cabal | 4 +- 45 files changed, 729 insertions(+), 567 deletions(-) create mode 100644 Cabal/Distribution/Types/LibDependency.hs create mode 100644 Cabal/Distribution/Types/LibDependencyMap.hs diff --git a/Cabal/Cabal.cabal b/Cabal/Cabal.cabal index 0f3757a3c65..d3bc4aff057 100644 --- a/Cabal/Cabal.cabal +++ b/Cabal/Cabal.cabal @@ -217,8 +217,10 @@ library Distribution.Types.Dependency Distribution.Types.ExeDependency Distribution.Types.LegacyExeDependency + Distribution.Types.LibDependency Distribution.Types.PkgconfigDependency Distribution.Types.DependencyMap + Distribution.Types.LibDependencyMap Distribution.Types.ComponentId Distribution.Types.MungedPackageId Distribution.Types.PackageId diff --git a/Cabal/Distribution/Backpack/ComponentsGraph.hs b/Cabal/Distribution/Backpack/ComponentsGraph.hs index 1ecf080dd71..204ad5bbef5 100644 --- a/Cabal/Distribution/Backpack/ComponentsGraph.hs +++ b/Cabal/Distribution/Backpack/ComponentsGraph.hs @@ -14,10 +14,10 @@ import Distribution.PackageDescription as PD hiding (Flag) import Distribution.Simple.BuildToolDepends import Distribution.Simple.LocalBuildInfo import Distribution.Types.ComponentRequestedSpec -import Distribution.Types.Dependency -import Distribution.Types.UnqualComponentName +import Distribution.Types.LibDependency import Distribution.Compat.Graph (Node(..)) import qualified Distribution.Compat.Graph as Graph +import Distribution.Types.Mixin import Distribution.Text ( Text(disp) ) @@ -57,18 +57,16 @@ toComponentsGraph enabled pkg_descr = -- The dependencies for the given component componentDeps component = (CExeName <$> getAllInternalToolDependencies pkg_descr bi) - - ++ [ if pkgname == packageName pkg_descr - then CLibName - else CSubLibName toolname - | Dependency pkgname _ <- targetBuildDepends bi - , let toolname = packageNameToUnqualComponentName pkgname - , toolname `elem` internalPkgDeps ] + ++ mixin_deps + ++ [ maybe CLibName CSubLibName (libDepLibraryName ld) + | ld <- targetBuildDepends bi + , libDepPackageName ld == packageName pkg_descr ] where bi = componentBuildInfo component - internalPkgDeps = map (conv . libName) (allLibraries pkg_descr) - conv Nothing = packageNameToUnqualComponentName $ packageName pkg_descr - conv (Just s) = s + mixin_deps = + [ maybe CLibName CSubLibName (mixinLibraryName mix) + | mix <- mixins bi + , mixinPackageName mix == packageName pkg_descr ] -- | Error message when there is a cycle; takes the SCC of components. componentCycleMsg :: [ComponentName] -> Doc diff --git a/Cabal/Distribution/Backpack/ConfiguredComponent.hs b/Cabal/Distribution/Backpack/ConfiguredComponent.hs index cf61bdad59a..8f492e2fd14 100644 --- a/Cabal/Distribution/Backpack/ConfiguredComponent.hs +++ b/Cabal/Distribution/Backpack/ConfiguredComponent.hs @@ -22,7 +22,7 @@ import Distribution.Compat.Prelude hiding ((<>)) import Distribution.Backpack.Id import Distribution.Types.AnnotatedId -import Distribution.Types.Dependency +import Distribution.Types.LibDependency import Distribution.Types.ExeDependency import Distribution.Types.IncludeRenaming import Distribution.Types.ComponentId @@ -30,7 +30,6 @@ import Distribution.Types.PackageId import Distribution.Types.PackageName import Distribution.Types.Mixin import Distribution.Types.ComponentName -import Distribution.Types.UnqualComponentName import Distribution.Types.ComponentInclude import Distribution.Package import Distribution.PackageDescription as PD hiding (Flag) @@ -42,7 +41,6 @@ import Distribution.Utils.LogProgress import Distribution.Utils.MapAccum import Control.Monad -import qualified Data.Set as Set import qualified Data.Map as Map import Distribution.Text import Text.PrettyPrint @@ -95,9 +93,20 @@ dispConfiguredComponent cc = | incl <- cc_includes cc ]) +-- | This is a mapping that keeps track of package-internal libraries +-- and executables. Although a component of the key is a general +-- 'ComponentName', actually only 'CLib', 'CSubLib' and 'CExe' will ever +-- be here. type ConfiguredComponentMap = Map PackageName (Map ComponentName (AnnotatedId ComponentId)) +-- Executable map must be different because an executable can +-- have the same name as a library. Ew. + +-- | Given some ambient environment of package names that +-- are "in scope", looks at the 'BuildInfo' to decide +-- what the packages actually resolve to, and then builds +-- a 'ConfiguredComponent'. toConfiguredComponent :: PackageDescription -> ComponentId @@ -105,49 +114,51 @@ toConfiguredComponent -> Component -> LogProgress ConfiguredComponent toConfiguredComponent pkg_descr this_cid dep_map component = do - lib_deps <- - if newPackageDepsBehaviour pkg_descr - then forM (targetBuildDepends bi) $ \(Dependency name _) -> do - let (pn, cn) = fixFakePkgName pkg_descr name - value <- case Map.lookup cn =<< Map.lookup pn dep_map of - Nothing -> - dieProgress $ - text "Dependency on unbuildable" <+> - text (showComponentName cn) <+> - text "from" <+> disp pn - Just v -> return v - return value - else return old_style_lib_deps + let reg_lib_deps = + if newPackageDepsBehaviour pkg_descr + then + [ (pn, cn) + | LibDependency pn mb_ln _ <- targetBuildDepends bi + , let cn = libraryComponentName mb_ln ] + else + -- dep_map contains a mix of internal and external deps. + -- We want all the public libraries (dep_cn == CLibName) + -- of all external deps (dep /= pn). Note that this + -- excludes the public library of the current package: + -- this is not supported by old-style deps behavior + -- because it would imply a cyclic dependency for the + -- library itself. + [ (pn, cn) + | (pn, comp_map) <- Map.toList dep_map + , pn /= packageName pkg_descr + , (cn, _) <- Map.toList comp_map + , cn == CLibName ] + + reg_lib_map, mixin_map :: Map (PackageName, ComponentName) (IncludeRenaming, Bool) + + reg_lib_map = Map.fromList $ + reg_lib_deps `zip` repeat (defaultIncludeRenaming, True) + + mixin_map = Map.fromList + [ ((pn, cn), (rns, False)) + | Mixin pn mb_ln rns <- mixins bi + , let cn = libraryComponentName mb_ln ] - -- Resolve each @mixins@ into the actual dependency - -- from @lib_deps@. - explicit_includes <- forM (mixins bi) $ \(Mixin name rns) -> do - let (pkg, cname) = fixFakePkgName pkg_descr name - aid <- - case Map.lookup cname =<< Map.lookup pkg dep_map of - Nothing -> - dieProgress $ - text "Mix-in refers to non-existent package" <+> - quotes (disp name) $$ - text "(did you forget to add the package to build-depends?)" - Just r -> return r + lib_deps = Map.toList $ reg_lib_map `Map.union` mixin_map + + mixin_includes <- forM lib_deps $ \((pname, cname), (rns, implicit)) -> do + aid <- case Map.lookup cname =<< Map.lookup pname dep_map of + Nothing -> dieProgress $ + text "Dependency on unbuildable" <+> + text (showComponentName cname) <+> + text "from" <+> disp pname + Just r -> return r return ComponentInclude { ci_ann_id = aid, ci_renaming = rns, - ci_implicit = False + ci_implicit = implicit } - -- Any @build-depends@ which is not explicitly mentioned in - -- @backpack-include@ is converted into an "implicit" include. - let used_explicitly = Set.fromList (map ci_id explicit_includes) - implicit_includes - = map (\aid -> ComponentInclude { - ci_ann_id = aid, - ci_renaming = defaultIncludeRenaming, - ci_implicit = True - }) - $ filter (flip Set.notMember used_explicitly . ann_id) lib_deps - return ConfiguredComponent { cc_ann_id = AnnotatedId { ann_id = this_cid, @@ -157,22 +168,10 @@ toConfiguredComponent pkg_descr this_cid dep_map component = do cc_component = component, cc_public = componentName component == CLibName, cc_exe_deps = exe_deps, - cc_includes = explicit_includes ++ implicit_includes + cc_includes = mixin_includes } where bi = componentBuildInfo component - -- dep_map contains a mix of internal and external deps. - -- We want all the public libraries (dep_cn == CLibName) - -- of all external deps (dep /= pn). Note that this - -- excludes the public library of the current package: - -- this is not supported by old-style deps behavior - -- because it would imply a cyclic dependency for the - -- library itself. - old_style_lib_deps = [ e - | (pn, comp_map) <- Map.toList dep_map - , pn /= packageName pkg_descr - , (cn, e) <- Map.toList comp_map - , cn == CLibName ] exe_deps = [ exe | ExeDependency pn cn _ <- getAllToolDependencies pkg_descr bi @@ -259,16 +258,3 @@ newPackageDepsBehaviourMinVersion = mkVersion [1,7,1] newPackageDepsBehaviour :: PackageDescription -> Bool newPackageDepsBehaviour pkg = specVersion pkg >= newPackageDepsBehaviourMinVersion - --- | 'build-depends:' stanzas are currently ambiguous as the external packages --- and internal libraries are specified the same. For now, we assume internal --- libraries shadow, and this function disambiguates accordingly, but soon the --- underlying ambiguity will be addressed. -fixFakePkgName :: PackageDescription -> PackageName -> (PackageName, ComponentName) -fixFakePkgName pkg_descr pn = - if subLibName `elem` internalLibraries - then (packageName pkg_descr, CSubLibName subLibName) - else (pn, CLibName) - where - subLibName = packageNameToUnqualComponentName pn - internalLibraries = mapMaybe libName (allLibraries pkg_descr) diff --git a/Cabal/Distribution/PackageDescription/Check.hs b/Cabal/Distribution/PackageDescription/Check.hs index 7ccf056c714..be6ac28e52d 100644 --- a/Cabal/Distribution/PackageDescription/Check.hs +++ b/Cabal/Distribution/PackageDescription/Check.hs @@ -47,6 +47,7 @@ import Distribution.Simple.CCompiler import Distribution.Types.ComponentRequestedSpec import Distribution.Types.CondTree import Distribution.Types.Dependency +import Distribution.Types.LibDependency import Distribution.Types.ExeDependency import Distribution.Types.PackageName import Distribution.Types.UnqualComponentName @@ -546,6 +547,11 @@ checkFields pkg = ++ ". This version range does not include the current package, and must " ++ "be removed as the current package's library will always be used." + , check (not (null depMissingInternalLibrary)) $ + PackageBuildImpossible $ + "The package depends on a missing internal library: " + ++ commaSep (map display depInternalExecutableWithImpossibleVersion) + , check (not (null depInternalExecutableWithExtraVersion)) $ PackageBuildWarning $ "The package has an extraneous version range for a dependency on an " @@ -588,17 +594,14 @@ checkFields pkg = | (compiler, vr) <- testedWith pkg , isNoVersion vr ] - internalLibraries = - map (maybe (packageName pkg) (unqualComponentNameToPackageName) . libName) - (allLibraries pkg) + internalLibraries = mapMaybe libName $ allLibraries pkg internalExecutables = map exeName $ executables pkg internalLibDeps = [ dep - | bi <- allBuildInfo pkg - , dep@(Dependency name _) <- targetBuildDepends bi - , name `elem` internalLibraries + | dep@(LibDependency name _ _) <- allBuildDepends pkg + , name == packageName pkg ] internalExeDeps = @@ -610,17 +613,23 @@ checkFields pkg = depInternalLibraryWithExtraVersion = [ dep - | dep@(Dependency _ versionRange) <- internalLibDeps + | dep@(LibDependency _ _ versionRange) <- internalLibDeps , not $ isAnyVersion versionRange , packageVersion pkg `withinRange` versionRange ] depInternalLibraryWithImpossibleVersion = [ dep - | dep@(Dependency _ versionRange) <- internalLibDeps + | dep@(LibDependency _ _ versionRange) <- internalLibDeps , not $ packageVersion pkg `withinRange` versionRange ] + depMissingInternalLibrary = + [ dep + | dep@(LibDependency _ (Just lName) _) <- internalLibDeps + , not $ lName `elem` internalLibraries + ] + depInternalExecutableWithExtraVersion = [ dep | dep@(ExeDependency _ _ versionRange) <- internalExeDeps @@ -1139,7 +1148,7 @@ checkCabalVersion pkg = PackageDistInexcusable $ "The package uses full version-range expressions " ++ "in a 'build-depends' field: " - ++ commaSep (map displayRawDependency versionRangeExpressions) + ++ commaSep (map displayRawLibDependency versionRangeExpressions) ++ ". To use this new syntax the package needs to specify at least " ++ "'cabal-version: >= 1.8'. Alternatively, if broader compatibility " ++ "is important, then convert to conjunctive normal form, and use " @@ -1154,7 +1163,7 @@ checkCabalVersion pkg = ++ "'cabal-version: >= 1.6'. Alternatively, if broader compatibility " ++ "is important then use: " ++ commaSep [ display (Dependency name (eliminateWildcardSyntax versionRange)) - | Dependency name versionRange <- depsUsingWildcardSyntax ] + | LibDependency name Nothing versionRange <- depsUsingWildcardSyntax ] -- check use of "build-depends: foo ^>= 1.2.3" syntax , checkVersion [2,0] (not (null depsUsingMajorBoundSyntax)) $ @@ -1165,8 +1174,8 @@ checkCabalVersion pkg = ++ ". To use this new syntax the package need to specify at least " ++ "'cabal-version: >= 2.0'. Alternatively, if broader compatibility " ++ "is important then use: " ++ commaSep - [ display (Dependency name (eliminateMajorBoundSyntax versionRange)) - | Dependency name versionRange <- depsUsingMajorBoundSyntax ] + [ display (LibDependency name lname (eliminateMajorBoundSyntax versionRange)) + | LibDependency name lname versionRange <- depsUsingMajorBoundSyntax ] -- check use of "tested-with: GHC (>= 1.0 && < 1.4) || >=1.8 " syntax , checkVersion [1,8] (not (null testedWithVersionRangeExpressions)) $ @@ -1292,7 +1301,7 @@ checkCabalVersion pkg = _ -> False versionRangeExpressions = - [ dep | dep@(Dependency _ vr) <- allBuildDepends pkg + [ dep | dep@(LibDependency _ _ vr) <- allBuildDepends pkg , usesNewVersionRangeSyntax vr ] testedWithVersionRangeExpressions = @@ -1331,11 +1340,13 @@ checkCabalVersion pkg = (+) (+) (const 3) -- uses new ()'s syntax - depsUsingWildcardSyntax = [ dep | dep@(Dependency _ vr) <- allBuildDepends pkg - , usesWildcardSyntax vr ] + depsUsingWildcardSyntax = [ dep + | dep@(LibDependency _ _ vr) <- allBuildDepends pkg + , usesWildcardSyntax vr ] - depsUsingMajorBoundSyntax = [ dep | dep@(Dependency _ vr) <- allBuildDepends pkg - , usesMajorBoundSyntax vr ] + depsUsingMajorBoundSyntax = [ dep + | dep@(LibDependency _ _ vr) <- allBuildDepends pkg + , usesMajorBoundSyntax vr ] usesBackpackIncludes = any (not . null . mixins) (allBuildInfo pkg) @@ -1475,6 +1486,12 @@ displayRawDependency :: Dependency -> String displayRawDependency (Dependency pkg vr) = display pkg ++ " " ++ displayRawVersionRange vr +displayRawLibDependency :: LibDependency -> String +displayRawLibDependency (LibDependency pkg ml vr) = + display pkg + ++ ":lib:" ++ maybe (display pkg) display ml + ++ " " ++ displayRawVersionRange vr + -- ------------------------------------------------------------ -- * Checks on the GenericPackageDescription @@ -1524,7 +1541,7 @@ checkPackageVersions pkg = foldr intersectVersionRanges anyVersion baseDeps where baseDeps = - [ vr | Dependency pname vr <- allBuildDepends pkg' + [ vr | LibDependency pname _ vr <- allBuildDepends pkg' , pname == mkPackageName "base" ] -- Just in case finalizePD fails for any reason, diff --git a/Cabal/Distribution/PackageDescription/Configuration.hs b/Cabal/Distribution/PackageDescription/Configuration.hs index c4fbadd2dd4..0a0cb951fc1 100644 --- a/Cabal/Distribution/PackageDescription/Configuration.hs +++ b/Cabal/Distribution/PackageDescription/Configuration.hs @@ -50,11 +50,13 @@ import Distribution.Types.ComponentRequestedSpec import Distribution.Types.ForeignLib import Distribution.Types.Component import Distribution.Types.Dependency +import Distribution.Types.LibDependency import Distribution.Types.PackageName import Distribution.Types.UnqualComponentName import Distribution.Types.CondTree import Distribution.Types.Condition import Distribution.Types.DependencyMap +import Distribution.Types.LibDependencyMap import qualified Data.Map as Map import Data.Tree ( Tree(Node) ) @@ -168,20 +170,20 @@ resolveWithFlags :: -> Arch -- ^ Arch as returned by Distribution.System.buildArch -> CompilerInfo -- ^ Compiler information -> [Dependency] -- ^ Additional constraints - -> [CondTree ConfVar [Dependency] PDTagged] - -> ([Dependency] -> DepTestRslt [Dependency]) -- ^ Dependency test function. - -> Either [Dependency] (TargetSet PDTagged, FlagAssignment) + -> [CondTree ConfVar [LibDependency] PDTagged] + -> ([LibDependency] -> DepTestRslt [LibDependency]) -- ^ Dependency test function. + -> Either [LibDependency] (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 [] dom) + either (Left . fromLibDepMapUnion) Right $ explore (build [] dom) where extraConstrs = toDepMap constrs -- simplify trees by (partially) evaluating all conditions and converting -- dependencies to dependency maps. - simplifiedTrees :: [CondTree FlagName DependencyMap PDTagged] - simplifiedTrees = map ( mapTreeConstrs toDepMap -- convert to maps + simplifiedTrees :: [CondTree FlagName LibDependencyMap PDTagged] + simplifiedTrees = map ( mapTreeConstrs toLibDepMap -- convert to maps . addBuildableConditionPDTagged . mapTreeConds (fst . simplifyWithSysParams os arch impl)) trees @@ -192,17 +194,17 @@ resolveWithFlags dom enabled os arch impl constrs trees checkDeps = -- it to backtrack. Since the tree is constructed lazily, we avoid some -- computation overhead in the successful case. explore :: Tree FlagAssignment - -> Either DepMapUnion (TargetSet PDTagged, FlagAssignment) + -> Either LibDepMapUnion (TargetSet PDTagged, FlagAssignment) explore (Node flags ts) = let targetSet = TargetSet $ flip map simplifiedTrees $ -- apply additional constraints to all dependencies first (`constrainBy` extraConstrs) . simplifyCondTree (env flags) deps = overallDependencies enabled targetSet - in case checkDeps (fromDepMap deps) of + in case checkDeps $ fromLibDepMap deps of DepOk | null ts -> Right (targetSet, flags) | otherwise -> tryAll $ map explore ts - MissingDeps mds -> Left (toDepMapUnion mds) + MissingDeps mds -> Left (toLibDepMapUnion mds) -- Builds a tree of all possible flag assignments. Internal nodes -- have only partial assignments. @@ -211,22 +213,21 @@ resolveWithFlags dom enabled os arch impl constrs trees checkDeps = build assigned ((fn, vals) : unassigned) = Node assigned $ map (\v -> build ((fn, v) : assigned) unassigned) vals - tryAll :: [Either DepMapUnion a] -> Either DepMapUnion a + tryAll :: [Either LibDepMapUnion a] -> Either LibDepMapUnion a tryAll = foldr mp mz -- special version of `mplus' for our local purposes - mp :: Either DepMapUnion a -> Either DepMapUnion a -> Either DepMapUnion a + mp :: Either LibDepMapUnion a -> Either LibDepMapUnion a -> Either LibDepMapUnion a mp m@(Right _) _ = m mp _ m@(Right _) = m mp (Left xs) (Left ys) = - let union = Map.foldrWithKey (Map.insertWith' combine) - (unDepMapUnion xs) (unDepMapUnion ys) - combine x y = simplifyVersionRange $ unionVersionRanges x y - in union `seq` Left (DepMapUnion union) + let union = Map.unionWith unionCompVerRange + (unLibDepMapUnion xs) (unLibDepMapUnion ys) + in union `seq` Left (LibDepMapUnion union) -- `mzero' - mz :: Either DepMapUnion a - mz = Left (DepMapUnion Map.empty) + mz :: Either LibDepMapUnion a + mz = Left (LibDepMapUnion Map.empty) env :: FlagAssignment -> FlagName -> Either FlagName Bool env flags flag = (maybe (Left flag) Right . lookup flag) flags @@ -298,15 +299,29 @@ extractConditions f gpkg = ] --- | A map of dependencies that combines version ranges using 'unionVersionRanges'. -newtype DepMapUnion = DepMapUnion { unDepMapUnion :: Map PackageName VersionRange } +-- | A map of library dependencies that combines components version ranges. +-- Note that we have a Map instead of pair of sets. This is because firstly, the +-- 2D union isn't convex like the the 2D intersection, and secondly because +-- components are disjoint. +newtype LibDepMapUnion = LibDepMapUnion { + unLibDepMapUnion :: Map PackageName + (Map (Maybe UnqualComponentName) VersionRange) + } -toDepMapUnion :: [Dependency] -> DepMapUnion -toDepMapUnion ds = - DepMapUnion $ Map.fromListWith unionVersionRanges [ (p,vr) | Dependency p vr <- ds ] +unionCompVerRange :: Map (Maybe UnqualComponentName) VersionRange + -> Map (Maybe UnqualComponentName) VersionRange + -> Map (Maybe UnqualComponentName) VersionRange +unionCompVerRange = Map.unionWith $ \x y -> + simplifyVersionRange $ unionVersionRanges x y -fromDepMapUnion :: DepMapUnion -> [Dependency] -fromDepMapUnion m = [ Dependency p vr | (p,vr) <- Map.toList (unDepMapUnion m) ] +toLibDepMapUnion :: [LibDependency] -> LibDepMapUnion +toLibDepMapUnion ds = LibDepMapUnion $ Map.fromListWith unionCompVerRange + [ (p, Map.singleton c vr) | LibDependency p c vr <- ds ] + +fromLibDepMapUnion :: LibDepMapUnion -> [LibDependency] +fromLibDepMapUnion m = [ LibDependency p c vr + | (p, pairs) <- Map.toList (unLibDepMapUnion m) + , (c, vr) <- Map.toList pairs ] freeVars :: CondTree ConfVar c a -> [FlagName] freeVars t = [ f | Flag f <- freeVars' t ] @@ -324,11 +339,11 @@ freeVars t = [ f | Flag f <- freeVars' t ] ------------------------------------------------------------------------------ -- | A set of targets with their package dependencies -newtype TargetSet a = TargetSet [(DependencyMap, a)] +newtype TargetSet a = TargetSet [(LibDependencyMap, a)] -- | Combine the target-specific dependencies in a TargetSet to give the -- dependencies for the package as a whole. -overallDependencies :: ComponentRequestedSpec -> TargetSet PDTagged -> DependencyMap +overallDependencies :: ComponentRequestedSpec -> TargetSet PDTagged -> LibDependencyMap overallDependencies enabled (TargetSet targets) = mconcat depss where (depss, _) = unzip $ filter (removeDisabledSections . snd) targets @@ -352,7 +367,7 @@ overallDependencies enabled (TargetSet targets) = mconcat depss -- dependencies as we go. flattenTaggedTargets :: TargetSet PDTagged -> (Maybe Library, [(UnqualComponentName, Component)]) flattenTaggedTargets (TargetSet targets) = foldr untag (Nothing, []) targets where - untag (depMap, pdTagged) accum = case (pdTagged, accum) of + untag (libDepMap, pdTagged) accum = case (pdTagged, accum) of (Lib _, (Just _, _)) -> userBug "Only one library expected" (Lib l, (Nothing, comps)) -> (Just $ redoBD lensLibBD l, comps) (SubComp n c, (mb_lib, comps)) @@ -362,7 +377,7 @@ flattenTaggedTargets (TargetSet targets) = foldr untag (Nothing, []) targets whe (PDNull, x) -> x -- actually this should not happen, but let's be liberal where redoBD :: ((BuildInfo -> BuildInfo) -> (a -> a)) -> (a -> a) - redoBD bd_lens = bd_lens $ \bi -> bi { targetBuildDepends = fromDepMap depMap } + redoBD bd_lens = bd_lens $ \bi -> bi { targetBuildDepends = fromLibDepMap libDepMap } lensLibBD :: (BuildInfo -> BuildInfo) -> (Library -> Library) lensLibBD f = \l -> l { libBuildInfo = f $ libBuildInfo l } @@ -416,14 +431,14 @@ instance Semigroup PDTagged where finalizePD :: FlagAssignment -- ^ Explicitly specified flag assignments -> ComponentRequestedSpec - -> (Dependency -> Bool) -- ^ Is a given dependency satisfiable from the set of - -- available packages? If this is unknown then use - -- True. + -> (LibDependency -> Bool) -- ^ Is a given dependency satisfiable from the set + -- of available packages? If this is unknown then + -- use True. -> Platform -- ^ The 'Arch' and 'OS' -> CompilerInfo -- ^ Compiler information -> [Dependency] -- ^ Additional constraints -> GenericPackageDescription - -> Either [Dependency] + -> Either [LibDependency] (PackageDescription, FlagAssignment) -- ^ Either missing dependencies or the resolved package -- description along with the flag assignments chosen. @@ -476,14 +491,14 @@ finalizePD userflags enabled satisfyDep {-# DEPRECATED finalizePackageDescription "This function now always assumes tests and benchmarks are disabled; use finalizePD with ComponentRequestedSpec to specify something more specific." #-} finalizePackageDescription :: FlagAssignment -- ^ Explicitly specified flag assignments - -> (Dependency -> Bool) -- ^ Is a given dependency satisfiable from the set of - -- available packages? If this is unknown then use - -- True. + -> (LibDependency -> Bool) -- ^ Is a given dependency satisfiable from the set + -- of available packages? If this is unknown then + -- use True. -> Platform -- ^ The 'Arch' and 'OS' -> CompilerInfo -- ^ Compiler information -> [Dependency] -- ^ Additional constraints -> GenericPackageDescription - -> Either [Dependency] + -> Either [LibDependency] (PackageDescription, FlagAssignment) finalizePackageDescription flags = finalizePD flags defaultComponentRequestedSpec @@ -607,12 +622,18 @@ transformAllBuildDepends :: (Dependency -> Dependency) -> GenericPackageDescription transformAllBuildDepends f gpd = gpd' where - onBI bi = bi { targetBuildDepends = map f $ targetBuildDepends bi } - onSBI stp = stp { setupDepends = map f $ setupDepends stp } + onBI bi = bi { targetBuildDepends = map transformNB $ targetBuildDepends bi } + onSBI stp = stp { setupDepends = map f $ setupDepends stp } + + -- Transform the name and bound for a library dependency. Since + -- solving (for now) works on entire packages, there is no reason + -- to break compatability and allow the the library name to be + -- transformed too. + transformNB (LibDependency pn mln vb) = LibDependency pn' mln vb' + where Dependency pn' vb' = f $ Dependency pn vb - gpd' = transformAllCondTrees id id id id (map f) - . transformAllBuildInfos onBI onSBI - $ gpd + gpd' = transformAllCondTrees id id id id f + $ transformAllBuildInfos onBI onSBI gpd -- | Walk all 'CondTree's inside a 'GenericPackageDescription' and apply -- appropriate transformations to all nodes. Helper function used by @@ -621,10 +642,10 @@ transformAllCondTrees :: (Library -> Library) -> (Executable -> Executable) -> (TestSuite -> TestSuite) -> (Benchmark -> Benchmark) - -> ([Dependency] -> [Dependency]) + -> (Dependency -> Dependency) -> GenericPackageDescription -> GenericPackageDescription transformAllCondTrees onLibrary onExecutable - onTestSuite onBenchmark onDepends gpd = gpd' + onTestSuite onBenchmark onDepend gpd = gpd' where gpd' = gpd { condLibrary = condLib', @@ -649,6 +670,8 @@ transformAllCondTrees onLibrary onExecutable mapSnd :: (a -> b) -> (c,a) -> (c,b) mapSnd = fmap - onCondTree :: (a -> b) -> CondTree v [Dependency] a - -> CondTree v [Dependency] b - onCondTree g = mapCondTree g onDepends id + onCondTree :: (a -> b) -> CondTree v [LibDependency] a + -> CondTree v [LibDependency] b + onCondTree g = mapCondTree g (map goD) id where + goD (LibDependency n l v) = LibDependency n' l v' + where (Dependency n' v') = onDepend $ Dependency n v diff --git a/Cabal/Distribution/PackageDescription/Parse.hs b/Cabal/Distribution/PackageDescription/Parse.hs index 9981b70da9c..437c923abc8 100644 --- a/Cabal/Distribution/PackageDescription/Parse.hs +++ b/Cabal/Distribution/PackageDescription/Parse.hs @@ -54,10 +54,10 @@ import Prelude () import Distribution.Compat.Prelude import Distribution.Types.BuildInfo -import Distribution.Types.Dependency import Distribution.Types.ForeignLib import Distribution.Types.ForeignLibType import Distribution.Types.UnqualComponentName +import Distribution.Types.LibDependency import Distribution.Types.CondTree import Distribution.Types.PackageId import Distribution.ParseUtils hiding (parseFields) @@ -646,7 +646,7 @@ constraintFieldNames = ["build-depends"] -- they add and define an accessor that specifies what the dependencies -- are. This way we would completely reuse the parsing knowledge from the -- field descriptor. -parseConstraint :: Field -> ParseResult [Dependency] +parseConstraint :: Field -> ParseResult [LibDependency] parseConstraint (F l n v) | n `elem` constraintFieldNames = runP l n (parseCommaList parse) v parseConstraint f = userBug $ "Constraint was expected (got: " ++ show f ++ ")" @@ -915,12 +915,12 @@ parseGenericPackageDescription file = do getBody :: PackageDescription -> PM ([SourceRepo], [Flag] ,Maybe SetupBuildInfo - ,(Maybe (CondTree ConfVar [Dependency] Library)) - ,[(UnqualComponentName, CondTree ConfVar [Dependency] Library)] - ,[(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)] - ,[(UnqualComponentName, CondTree ConfVar [Dependency] Executable)] - ,[(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)] - ,[(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]) + ,(Maybe (CondTree ConfVar [LibDependency] Library)) + ,[(UnqualComponentName, CondTree ConfVar [LibDependency] Library)] + ,[(UnqualComponentName, CondTree ConfVar [LibDependency] ForeignLib)] + ,[(UnqualComponentName, CondTree ConfVar [LibDependency] Executable)] + ,[(UnqualComponentName, CondTree ConfVar [LibDependency] TestSuite)] + ,[(UnqualComponentName, CondTree ConfVar [LibDependency] Benchmark)]) getBody pkg = peekField >>= \mf -> case mf of Just (Section line_no sec_type sec_label sec_fields) | sec_type == "executable" -> do @@ -1091,7 +1091,7 @@ parseGenericPackageDescription file = do -- We have to recurse down into conditionals and we treat fields that -- describe dependencies specially. collectFields :: ([Field] -> PM a) -> [Field] - -> PM (CondTree ConfVar [Dependency] a) + -> PM (CondTree ConfVar [LibDependency] a) collectFields parser allflds = do let simplFlds = [ F l n v | F l n v <- allflds ] @@ -1167,10 +1167,10 @@ parseGenericPackageDescription file = do checkForUndefinedFlags :: [Flag] -> - Maybe (CondTree ConfVar [Dependency] Library) -> - [(UnqualComponentName, CondTree ConfVar [Dependency] Library)] -> - [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)] -> - [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)] -> + Maybe (CondTree ConfVar [LibDependency] Library) -> + [(UnqualComponentName, CondTree ConfVar [LibDependency] Library)] -> + [(UnqualComponentName, CondTree ConfVar [LibDependency] Executable)] -> + [(UnqualComponentName, CondTree ConfVar [LibDependency] TestSuite)] -> PM () checkForUndefinedFlags flags mlib sub_libs exes tests = do let definedFlags = map flagName flags diff --git a/Cabal/Distribution/PackageDescription/PrettyPrint.hs b/Cabal/Distribution/PackageDescription/PrettyPrint.hs index 6abb7d9a47f..fbaa3b9b282 100644 --- a/Cabal/Distribution/PackageDescription/PrettyPrint.hs +++ b/Cabal/Distribution/PackageDescription/PrettyPrint.hs @@ -29,7 +29,7 @@ module Distribution.PackageDescription.PrettyPrint ( import Prelude () import Distribution.Compat.Prelude -import Distribution.Types.Dependency +import Distribution.Types.LibDependency import Distribution.Types.ForeignLib import Distribution.Types.UnqualComponentName import Distribution.Types.CondTree @@ -124,12 +124,12 @@ ppFlag flag@(MkFlag name _ _ _) = where fields = ppFieldsFiltered flagDefaults flagFieldDescrs flag -ppCondLibrary :: Maybe (CondTree ConfVar [Dependency] Library) -> Doc +ppCondLibrary :: Maybe (CondTree ConfVar [LibDependency] Library) -> Doc ppCondLibrary Nothing = mempty ppCondLibrary (Just condTree) = emptyLine $ text "library" $+$ nest indentWith (ppCondTree condTree Nothing ppLib) -ppCondSubLibraries :: [(UnqualComponentName, CondTree ConfVar [Dependency] Library)] -> Doc +ppCondSubLibraries :: [(UnqualComponentName, CondTree ConfVar [LibDependency] Library)] -> Doc ppCondSubLibraries libs = vcat [emptyLine $ (text "library " <+> disp n) $+$ nest indentWith (ppCondTree condTree Nothing ppLib)| (n,condTree) <- libs] @@ -140,7 +140,7 @@ ppLib lib Nothing = ppFieldsFiltered libDefaults libFieldDescrs lib ppLib lib (Just plib) = ppDiffFields libFieldDescrs lib plib $$ ppCustomFields (customFieldsBI (libBuildInfo lib)) -ppCondExecutables :: [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)] -> Doc +ppCondExecutables :: [(UnqualComponentName, CondTree ConfVar [LibDependency] Executable)] -> Doc ppCondExecutables exes = vcat [emptyLine $ (text "executable " <+> disp n) $+$ nest indentWith (ppCondTree condTree Nothing ppExe)| (n,condTree) <- exes] @@ -156,7 +156,7 @@ ppCondExecutables exes = $+$ ppDiffFields binfoFieldDescrs buildInfo' buildInfo2 $+$ ppCustomFields (customFieldsBI buildInfo') -ppCondTestSuites :: [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)] -> Doc +ppCondTestSuites :: [(UnqualComponentName, CondTree ConfVar [LibDependency] TestSuite)] -> Doc ppCondTestSuites suites = emptyLine $ vcat [ (text "test-suite " <+> disp n) $+$ nest indentWith (ppCondTree condTree Nothing ppTestSuite) @@ -188,7 +188,7 @@ ppCondTestSuites suites = TestSuiteLibV09 _ m -> Just m _ -> Nothing -ppCondBenchmarks :: [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)] -> Doc +ppCondBenchmarks :: [(UnqualComponentName, CondTree ConfVar [LibDependency] Benchmark)] -> Doc ppCondBenchmarks suites = emptyLine $ vcat [ (text "benchmark " <+> disp n) $+$ nest indentWith (ppCondTree condTree Nothing ppBenchmark) @@ -231,7 +231,7 @@ ppConfVar (Impl c v) = text "impl" <<>> parens (disp c <+> d ppFlagName :: FlagName -> Doc ppFlagName = text . unFlagName -ppCondTree :: CondTree ConfVar [Dependency] a -> Maybe a -> (a -> Maybe a -> Doc) -> Doc +ppCondTree :: CondTree ConfVar [LibDependency] a -> Maybe a -> (a -> Maybe a -> Doc) -> Doc ppCondTree ct@(CondNode it _ ifs) mbIt ppIt = let res = (vcat $ map ppIf ifs) $+$ ppIt it mbIt @@ -248,7 +248,7 @@ ppIfCondition c = (emptyLine $ text "if" <+> ppCondition c) ppIf' :: a -> (a -> Maybe a -> Doc) -> Condition ConfVar - -> CondTree ConfVar [Dependency] a + -> CondTree ConfVar [LibDependency] a -> Doc ppIf' it ppIt c thenTree = if isEmpty thenDoc @@ -258,8 +258,8 @@ ppIf' it ppIt c thenTree = ppIfElse :: a -> (a -> Maybe a -> Doc) -> Condition ConfVar - -> CondTree ConfVar [Dependency] a - -> CondTree ConfVar [Dependency] a + -> CondTree ConfVar [LibDependency] a + -> CondTree ConfVar [LibDependency] a -> Doc ppIfElse it ppIt c thenTree elseTree = case (isEmpty thenDoc, isEmpty elseDoc) of diff --git a/Cabal/Distribution/Parsec/Class.hs b/Cabal/Distribution/Parsec/Class.hs index 81998618b99..96029b08825 100644 --- a/Cabal/Distribution/Parsec/Class.hs +++ b/Cabal/Distribution/Parsec/Class.hs @@ -41,6 +41,7 @@ import Distribution.Types.BuildType (BuildType (..)) import Distribution.Types.Dependency (Dependency (..)) import Distribution.Types.ExeDependency (ExeDependency (..)) import Distribution.Types.LegacyExeDependency (LegacyExeDependency (..)) +import Distribution.Types.LibDependency (LibDependency(..)) import Distribution.Types.PkgconfigDependency (PkgconfigDependency (..)) import Distribution.Types.PkgconfigName (PkgconfigName, mkPkgconfigName) @@ -376,9 +377,22 @@ instance Parsec IncludeRenaming where instance Parsec Mixin where parsec = do mod_name <- parsec + mb_lib_name <- P.option Nothing $ do + _ <- P.char ':' + fmap Just parsec P.spaces incl <- parsec - return (Mixin mod_name incl) + return (Mixin mod_name mb_lib_name incl) + +instance Parsec LibDependency where + parsec = do + name <- parsec + mb_cname <- P.option Nothing $ do + _ <- P.char ':' + fmap Just parsec + P.spaces + ver <- parsec <|> pure anyVersion + return (LibDependency name mb_cname ver) ------------------------------------------------------------------------------- -- Utilities diff --git a/Cabal/Distribution/Simple/Build.hs b/Cabal/Distribution/Simple/Build.hs index c622ee171cc..f6e4b9090c2 100644 --- a/Cabal/Distribution/Simple/Build.hs +++ b/Cabal/Distribution/Simple/Build.hs @@ -30,7 +30,7 @@ module Distribution.Simple.Build ( import Prelude () import Distribution.Compat.Prelude -import Distribution.Types.Dependency +import Distribution.Types.LibDependency import Distribution.Types.LocalBuildInfo import Distribution.Types.TargetInfo import Distribution.Types.ComponentRequestedSpec @@ -77,6 +77,7 @@ import Distribution.Simple.Utils import Distribution.System import Distribution.Text import Distribution.Verbosity +import Distribution.Version (thisVersion) import Distribution.Compat.Graph (IsNode(..)) @@ -444,6 +445,8 @@ testSuiteLibV09AsLibAndExe pkg_descr PackageIdentifier pkg_name pkg_ver = package pkg_descr compat_name = computeCompatPackageName pkg_name (Just (testName test)) compat_key = computeCompatPackageKey (compiler lbi) compat_name pkg_ver (componentUnitId clbi) + -- Ew + compat_pkg_name = mkPackageName $ unMungedPackageName compat_name libClbi = LibComponentLocalBuildInfo { componentPackageDeps = componentPackageDeps clbi , componentInternalDeps = componentInternalDeps clbi @@ -460,7 +463,7 @@ testSuiteLibV09AsLibAndExe pkg_descr , componentExposedModules = [IPI.ExposedModule m Nothing] } pkg = pkg_descr { - package = (package pkg_descr) { pkgName = mkPackageName $ unMungedPackageName compat_name } + package = (package pkg_descr) { pkgName = compat_pkg_name } , executables = [] , testSuites = [] , subLibraries = [lib] @@ -468,7 +471,8 @@ testSuiteLibV09AsLibAndExe pkg_descr ipi = inplaceInstalledPackageInfo pwd distPref pkg (mkAbiHash "") lib lbi libClbi testDir = buildDir lbi stubName test stubName test ++ "-tmp" - testLibDep = thisPackageVersion $ package pkg + testLibDep = LibDependency compat_pkg_name Nothing + $ thisVersion $ pkgVersion $ package pkg exe = Executable { exeName = mkUnqualComponentName $ stubName test, modulePath = stubFilePath test, diff --git a/Cabal/Distribution/Simple/Configure.hs b/Cabal/Distribution/Simple/Configure.hs index ea0794abffa..18eeb22acc7 100644 --- a/Cabal/Distribution/Simple/Configure.hs +++ b/Cabal/Distribution/Simple/Configure.hs @@ -72,6 +72,7 @@ import qualified Distribution.Simple.PackageIndex as PackageIndex import Distribution.Simple.PackageIndex (InstalledPackageIndex) import Distribution.PackageDescription as PD hiding (Flag) import Distribution.Types.PackageDescription as PD +import Distribution.Types.LibDependency import Distribution.PackageDescription.PrettyPrint import Distribution.PackageDescription.Configuration import Distribution.PackageDescription.Check hiding (doesFileExist) @@ -133,8 +134,8 @@ import System.IO ( hPutStrLn, hClose ) import Distribution.Text ( Text(disp), defaultStyle, display, simpleParse ) -import Text.PrettyPrint - ( Doc, (<+>), ($+$), char, comma, hsep, nest +import Text.PrettyPrint as PP + ( Doc, (<+>), ($+$), char, comma, empty, hsep, nest , punctuate, quotes, render, renderStyle, sep, text ) import Distribution.Compat.Environment ( lookupEnv ) import Distribution.Compat.Exception ( catchExit, catchIO ) @@ -405,11 +406,6 @@ configure (pkg_descr0', pbi) cfg = do <- getInstalledPackages (lessVerbose verbosity) comp packageDbs programDb - -- The set of package names which are "shadowed" by internal - -- packages, and which component they map to - let internalPackageSet :: Map PackageName (Maybe UnqualComponentName) - internalPackageSet = getInternalPackages pkg_descr0 - -- Make a data structure describing what components are enabled. let enabled :: ComponentRequestedSpec enabled = case mb_cname of @@ -445,7 +441,7 @@ configure (pkg_descr0', pbi) cfg = do -- that is not possible to configure a test-suite to use one -- version of a dependency, and the executable to use another. (allConstraints :: [Dependency], - requiredDepsMap :: Map PackageName InstalledPackageInfo) + requiredDepsMap :: Map (PackageName, Maybe UnqualComponentName) InstalledPackageInfo) <- either (die' verbosity) return $ combinedConstraints (configConstraints cfg) (configDependencies cfg) @@ -475,7 +471,6 @@ configure (pkg_descr0', pbi) cfg = do (fromFlagOrDefault False (configExactConfiguration cfg)) (packageName pkg_descr0) installedPackageSet - internalPackageSet requiredDepsMap) comp compPlatform @@ -513,7 +508,6 @@ configure (pkg_descr0', pbi) cfg = do <- configureDependencies verbosity use_external_internal_deps - internalPackageSet installedPackageSet requiredDepsMap pkg_descr @@ -593,7 +587,6 @@ configure (pkg_descr0', pbi) cfg = do -- components (which may build-depends on each other) and form a graph. -- From there, we build a ComponentLocalBuildInfo for each of the -- components, which lets us actually build each component. - -- internalPackageSet -- use_external_internal_deps (buildComponents :: [ComponentLocalBuildInfo], packageDependsIndex :: InstalledPackageIndex) <- @@ -810,8 +803,7 @@ checkExactConfiguration verbosity pkg_descr0 cfg = do -- It must be *any libraries that might be* defined rather than the -- actual definitions, because these depend on conditionals in the .cabal -- file, and we haven't resolved them yet. finalizePD --- does the resolution of conditionals, and it takes internalPackageSet --- as part of its input. +-- does the resolution of conditionals. getInternalPackages :: GenericPackageDescription -> Map PackageName (Maybe UnqualComponentName) getInternalPackages pkg_descr0 = @@ -830,13 +822,17 @@ dependencySatisfiable -> Bool -- ^ exact configuration? -> PackageName -> InstalledPackageIndex -- ^ installed set - -> Map PackageName (Maybe UnqualComponentName) -- ^ internal set - -> Map PackageName InstalledPackageInfo -- ^ required dependencies - -> (Dependency -> Bool) + -> Map (PackageName, Maybe UnqualComponentName) InstalledPackageInfo -- ^ required dependencies + -> (LibDependency -> Bool) dependencySatisfiable use_external_internal_deps - exact_config pn installedPackageSet internalPackageSet requiredDepsMap - d@(Dependency depName vr) + exact_config pn installedPackageSet requiredDepsMap + d@(LibDependency dep_pkgName dep_mb_libName _) + + | dep_pkgName == pn && not use_external_internal_deps + -- when we're NOT per-component mode, and the dep is internal component, the + -- dep is always satisfiable (we're going to build it ourselves) + = True | exact_config -- When we're given '--exact-configuration', we assume that all @@ -847,41 +843,10 @@ dependencySatisfiable -- 'finalizePD' will fail. -- TODO: mention '--exact-configuration' in the error message -- when this fails? - = if isInternalDep && not use_external_internal_deps - -- Except for internal deps, when we're NOT per-component mode; - -- those are just True. - then True - else depName `Map.member` requiredDepsMap - - | isInternalDep - = if use_external_internal_deps - -- When we are doing per-component configure, we now need to - -- test if the internal dependency is in the index. This has - -- DIFFERENT semantics from normal dependency satisfiability. - then internalDepSatisfiable - -- If a 'PackageName' is defined by an internal component, the dep is - -- satisfiable (we're going to build it ourselves) - else True + = (dep_pkgName, dep_mb_libName) `Map.member` requiredDepsMap | otherwise - = depSatisfiable - - where - isInternalDep = Map.member depName internalPackageSet - - depSatisfiable = - not . null $ PackageIndex.lookupDependency installedPackageSet d - - internalDepSatisfiable = - not . null $ PackageIndex.lookupInternalDependency - installedPackageSet (Dependency pn vr) cn - where - cn | pn == depName - = Nothing - | otherwise - -- Reinterpret the "package name" as an unqualified component - -- name - = Just (mkUnqualComponentName (unPackageName depName)) + = not . null $ PackageIndex.lookupDependency installedPackageSet d -- | Relax the dependencies of this package if needed. relaxPackageDeps :: (VersionRange -> VersionRange) @@ -918,8 +883,8 @@ configureFinalizedPackage -> ConfigFlags -> ComponentRequestedSpec -> [Dependency] - -> (Dependency -> Bool) -- ^ tests if a dependency is satisfiable. - -- Might say it's satisfiable even when not. + -> (LibDependency -> Bool) -- ^ tests if a dependency is satisfiable. + -- Might say it's satisfiable even when not. -> Compiler -> Platform -> GenericPackageDescription @@ -940,7 +905,7 @@ configureFinalizedPackage verbosity cfg enabled Left missing -> die' verbosity $ "Encountered missing dependencies:\n" ++ (render . nest 4 . sep . punctuate comma - . map (disp . simplifyDependency) + . map (disp . simplifyLibDependency) $ missing) -- add extra include/lib dirs as specified in cfg @@ -991,25 +956,24 @@ checkCompilerProblems verbosity comp pkg_descr enabled = do configureDependencies :: Verbosity -> UseExternalInternalDeps - -> Map PackageName (Maybe UnqualComponentName) -- ^ internal packages -> InstalledPackageIndex -- ^ installed packages - -> Map PackageName InstalledPackageInfo -- ^ required deps + -> Map (PackageName, Maybe UnqualComponentName) InstalledPackageInfo -- ^ required deps -> PackageDescription -> ComponentRequestedSpec -> IO [PreExistingComponent] configureDependencies verbosity use_external_internal_deps - internalPackageSet installedPackageSet requiredDepsMap pkg_descr enableSpec = do + installedPackageSet requiredDepsMap pkg_descr enableSpec = do let failedDeps :: [FailedDependency] allPkgDeps :: [ResolvedDependency] (failedDeps, allPkgDeps) = partitionEithers [ (\s -> (dep, s)) <$> status | dep <- enabledBuildDepends pkg_descr enableSpec , let status = selectDependency (package pkg_descr) - internalPackageSet installedPackageSet + installedPackageSet requiredDepsMap use_external_internal_deps dep ] - internalPkgDeps = [ pkgid - | (_, InternalDependency pkgid) <- allPkgDeps ] + internalPkgDeps = [ dep + | (dep, InternalDependency _) <- allPkgDeps ] -- NB: we have to SAVE the package name, because this is the only -- way we can be able to resolve package names in the package -- description. @@ -1019,7 +983,7 @@ configureDependencies verbosity use_external_internal_deps when (not (null internalPkgDeps) && not (newPackageDepsBehaviour pkg_descr)) $ die' verbosity $ "The field 'build-depends: " - ++ intercalate ", " (map (display . packageName) internalPkgDeps) + ++ intercalate ", " (map display internalPkgDeps) ++ "' refers to a library which is defined within the same " ++ "package. To use this feature the package must specify at " ++ "least 'cabal-version: >= 1.8'." @@ -1146,7 +1110,7 @@ reportProgram verbosity prog (Just configuredProg) hackageUrl :: String hackageUrl = "http://hackage.haskell.org/package/" -type ResolvedDependency = (Dependency, DependencyResolution) +type ResolvedDependency = (LibDependency, DependencyResolution) data DependencyResolution -- | An external dependency from the package database, OR an @@ -1160,77 +1124,56 @@ data DependencyResolution | InternalDependency PackageId data FailedDependency = DependencyNotExists PackageName - | DependencyMissingInternal PackageName PackageName + | DependencyMissingInternal PackageName UnqualComponentName | DependencyNoVersion Dependency -- | Test for a package dependency and record the version we have installed. selectDependency :: PackageId -- ^ Package id of current package - -> Map PackageName (Maybe UnqualComponentName) -> InstalledPackageIndex -- ^ Installed packages - -> Map PackageName InstalledPackageInfo + -> Map (PackageName, Maybe UnqualComponentName) InstalledPackageInfo -- ^ Packages for which we have been given specific deps to -- use -> UseExternalInternalDeps -- ^ Are we configuring a -- single component? - -> Dependency + -> LibDependency -> Either FailedDependency DependencyResolution -selectDependency pkgid internalIndex installedIndex requiredDepsMap +selectDependency pkgid installedIndex requiredDepsMap use_external_internal_deps - dep@(Dependency dep_pkgname vr) = - -- If the dependency specification matches anything in the internal package - -- index, then we prefer that match to anything in the second. - -- For example: - -- - -- Name: MyLibrary - -- Version: 0.1 - -- Library - -- .. - -- Executable my-exec - -- build-depends: MyLibrary - -- - -- We want "build-depends: MyLibrary" always to match the internal library - -- even if there is a newer installed library "MyLibrary-0.2". - case Map.lookup dep_pkgname internalIndex of - Just cname -> if use_external_internal_deps - then do_external (Just cname) - else do_internal - _ -> do_external Nothing + dep@(LibDependency dep_pkgname dep_mb_libname _) = + -- If external sublibs can someday we be used, we can simplify this + -- case. For now, we do the error as a basic sanity + -- check. PackageDescription.Check should give the user a nicer + -- error earlier in the pipeline. + case (dep_mb_libname, dep_pkgname == packageName pkgid, use_external_internal_deps) of + (_, True, False) -> do_internal + (Just _, False, _) -> error + "Should have already checked that external sub-libs are not depended on" + (_, _, _) -> do_external where -- It's an internal library, and we're not per-component build do_internal = Right $ InternalDependency $ PackageIdentifier dep_pkgname $ packageVersion pkgid - - -- We have to look it up externally - do_external is_internal = do - ipi <- case Map.lookup dep_pkgname requiredDepsMap of + do_external = do + ipi <- case Map.lookup (dep_pkgname, dep_mb_libname) requiredDepsMap of -- If we know the exact pkg to use, then use it. Just pkginstance -> Right pkginstance -- Otherwise we just pick an arbitrary instance of the latest version. - Nothing -> - case is_internal of - Nothing -> do_external_external - Just mb_uqn -> do_external_internal mb_uqn - return $ ExternalDependency $ ipiToPreExistingComponent ipi - - -- It's an external package, normal situation - do_external_external = - case PackageIndex.lookupDependency installedIndex dep of - [] -> Left (DependencyNotExists dep_pkgname) - pkgs -> Right $ head $ snd $ last pkgs - - -- It's an internal library, being looked up externally - do_external_internal mb_uqn = - case PackageIndex.lookupInternalDependency installedIndex - (Dependency (packageName pkgid) vr) mb_uqn of - [] -> Left (DependencyMissingInternal dep_pkgname (packageName pkgid)) + Nothing -> case PackageIndex.lookupDependency installedIndex dep of + [] -> Left errVal pkgs -> Right $ head $ snd $ last pkgs + -- Fix metadata that may be stripped by old ghc-pkg + return $ ExternalDependency $ ipiToPreExistingComponent $ ipi + where + errVal = case dep_mb_libname of + Nothing -> DependencyNotExists dep_pkgname + Just intLibName -> DependencyMissingInternal dep_pkgname intLibName reportSelectedDependencies :: Verbosity -> [ResolvedDependency] -> IO () reportSelectedDependencies verbosity deps = info verbosity $ unlines - [ "Dependency " ++ display (simplifyDependency dep) + [ "Dependency " ++ display (simplifyLibDependency dep) ++ ": using " ++ display pkgid | (dep, resolution) <- deps , let pkgid = case resolution of @@ -1340,10 +1283,10 @@ interpretPackageDbFlags userInstall specificDBs = -- deps in the end. So we still need to remember which installed packages to -- pick. combinedConstraints :: [Dependency] -> - [(PackageName, ComponentId)] -> + [(PackageName, Maybe UnqualComponentName, ComponentId)] -> InstalledPackageIndex -> Either String ([Dependency], - Map PackageName InstalledPackageInfo) + Map (PackageName, Maybe UnqualComponentName) InstalledPackageInfo) combinedConstraints constraints dependencies installedPackages = do when (not (null badComponentIds)) $ @@ -1356,24 +1299,36 @@ combinedConstraints constraints dependencies installedPackages = do return (allConstraints, idConstraintMap) where + -- Speculation: The [Dependency] we calculate here is going to be + -- used to decide how to toggle flags in the final package. But + -- this also makes it impossible for a package manager that knows + -- better to forcibly link up components from the same package + -- with inconsistent version numbers. + -- + -- If we're given all the constraints, why do we even need the + -- version ranges at all? The reason is that we still need to + -- pick a flag assignment when finalizing the PackageDescription. + -- But what if the user picks the flags too? In that case, we + -- really should just let the user do what they want. + allConstraints :: [Dependency] allConstraints = constraints - ++ [ thisPackageVersion (packageId pkg) - | (_, _, Just pkg) <- dependenciesPkgInfo ] + ++ [ Dependency pn (thisVersion (packageVersion pkg)) + | (pn, _, _, Just pkg) <- dependenciesPkgInfo ] - idConstraintMap :: Map PackageName InstalledPackageInfo + idConstraintMap :: Map (PackageName, Maybe UnqualComponentName) InstalledPackageInfo idConstraintMap = Map.fromList -- NB: do NOT use the packageName from -- dependenciesPkgInfo! - [ (pn, pkg) - | (pn, _, Just pkg) <- dependenciesPkgInfo ] + [ ((pn, mb_cn), pkg) + | (pn, mb_cn, _, Just pkg) <- dependenciesPkgInfo ] -- The dependencies along with the installed package info, if it exists - dependenciesPkgInfo :: [(PackageName, ComponentId, + dependenciesPkgInfo :: [(PackageName, Maybe UnqualComponentName, ComponentId, Maybe InstalledPackageInfo)] dependenciesPkgInfo = - [ (pkgname, cid, mpkg) - | (pkgname, cid) <- dependencies + [ (pkgname, mb_cname, cid, mpkg) + | (pkgname, mb_cname, cid) <- dependencies , let mpkg = PackageIndex.lookupComponentId installedPackages cid ] @@ -1382,13 +1337,13 @@ combinedConstraints constraints dependencies installedPackages = do -- (i.e. someone has written a hash) and didn't find it then it's -- an error. badComponentIds = - [ (pkgname, cid) - | (pkgname, cid, Nothing) <- dependenciesPkgInfo ] + [ (pkgname, mb_cname, cid) + | (pkgname, mb_cname, cid, Nothing) <- dependenciesPkgInfo ] dispDependencies deps = - hsep [ text "--dependency=" - <<>> quotes (disp pkgname <<>> char '=' <<>> disp cid) - | (pkgname, cid) <- deps ] + hsep [ text "--dependency=" + <<>> quotes (disp pkgname <<>> (maybe PP.empty disp mb_cname) <<>> char '=' <<>> disp cid) + | (pkgname, mb_cname, cid) <- deps ] -- ----------------------------------------------------------------------------- -- Configuring program dependencies diff --git a/Cabal/Distribution/Simple/PackageIndex.hs b/Cabal/Distribution/Simple/PackageIndex.hs index 326ebdd08a4..0d66fe730a6 100644 --- a/Cabal/Distribution/Simple/PackageIndex.hs +++ b/Cabal/Distribution/Simple/PackageIndex.hs @@ -70,7 +70,6 @@ module Distribution.Simple.PackageIndex ( lookupPackageId, lookupPackageName, lookupDependency, - lookupInternalDependency, -- ** Case-insensitive searches searchByName, @@ -109,7 +108,7 @@ import Distribution.ModuleName import qualified Distribution.InstalledPackageInfo as IPI import Distribution.Version import Distribution.Simple.Utils -import Distribution.Types.Dependency +import Distribution.Types.LibDependency import Distribution.Types.UnqualComponentName import Control.Exception (assert) @@ -134,18 +133,17 @@ data PackageIndex a = PackageIndex { unitIdIndex :: !(Map UnitId a), -- This auxiliary index maps package names (case-sensitively) to all the - -- versions and instances of that package. This allows us to find all - -- versions satisfying a dependency. + -- versions and instances of that package. This allows us to find all versions + -- satisfying a dependency. -- - -- It is a three-level index. The first level is the package name, - -- the second is the package version and the final level is instances - -- of the same package version. These are unique by UnitId - -- and are kept in preference order. + -- It is a four-level index. The first level is the package name, the second + -- is the package version, the third is the library name (Nothing if + -- primrary), and the final level is instances matching those keys. These are + -- unique by UnitId and are kept in preference order. -- -- FIXME: Clarify what "preference order" means. Check that this invariant is -- preserved. See #1463 for discussion. - packageIdIndex :: !(Map (PackageName, Maybe UnqualComponentName) (Map Version [a])) - + packageIdIndex :: !(Map PackageName (Map Version (Map (Maybe UnqualComponentName) [a]))) } deriving (Eq, Generic, Show, Read) instance Binary a => Binary (PackageIndex a) @@ -173,9 +171,10 @@ invariant (PackageIndex pids pnames) = pids' = map installedUnitId (Map.elems pids) pnames' = sort [ assert pinstOk (installedUnitId pinst) - | ((pname, plib), pvers) <- Map.toList pnames + | (pname, pvers) <- Map.toList pnames , let pversOk = not (Map.null pvers) - , (pver, pinsts) <- assert pversOk $ Map.toList pvers + , (pver, plibs) <- assert pversOk $ Map.toList pvers + , (plib, pinsts) <- Map.toList plibs , let pinsts' = sortBy (comparing installedUnitId) pinsts pinstsOk = all (\g -> length g == 1) (groupBy (equating installedUnitId) pinsts') @@ -196,8 +195,10 @@ invariant (PackageIndex pids pnames) = -- mkPackageIndex :: WithCallStack (Map UnitId IPI.InstalledPackageInfo - -> Map (PackageName, Maybe UnqualComponentName) - (Map Version [IPI.InstalledPackageInfo]) + -> Map PackageName + (Map Version + (Map (Maybe UnqualComponentName) + [IPI.InstalledPackageInfo])) -> InstalledPackageIndex) mkPackageIndex pids pnames = assert (invariant index) index where index = PackageIndex pids pnames @@ -215,20 +216,16 @@ mkPackageIndex pids pnames = assert (invariant index) index fromList :: [IPI.InstalledPackageInfo] -> InstalledPackageIndex fromList pkgs = mkPackageIndex pids pnames where - pids = Map.fromList [ (installedUnitId pkg, pkg) | pkg <- pkgs ] - pnames = - Map.fromList - [ (liftM2 (,) packageName IPI.sourceLibName (head pkgsN), pvers) - | pkgsN <- groupBy (equating (liftM2 (,) packageName IPI.sourceLibName)) - . sortBy (comparing (liftM2 (,) packageId IPI.sourceLibName)) - $ pkgs - , let pvers = - Map.fromList - [ (packageVersion (head pkgsNV), - nubBy (equating installedUnitId) (reverse pkgsNV)) - | pkgsNV <- groupBy (equating packageVersion) pkgsN - ] - ] + pids = Map.fromList [ (installedUnitId pkg, pkg) | pkg <- pkgs ] + + -- | Build relation with projected key + projectSort :: Ord k => (v -> k) -> [v] -> Map k [v] + projectSort proj = Map.fromListWith mappend . fmap (\v -> (proj v, pure v)) + + pnames = (fmap . fmap) (projectSort IPI.sourceLibName) + $ fmap (projectSort packageVersion) + $ projectSort packageName + $ Map.elems pids -- With unit id duplicates removed as per above -- -- * Updates @@ -248,7 +245,8 @@ merge :: InstalledPackageIndex -> InstalledPackageIndex -> InstalledPackageIndex merge (PackageIndex pids1 pnames1) (PackageIndex pids2 pnames2) = mkPackageIndex (Map.unionWith (\_ y -> y) pids1 pids2) - (Map.unionWith (Map.unionWith mergeBuckets) pnames1 pnames2) + (Map.unionWith (Map.unionWith (Map.unionWith mergeBuckets)) + pnames1 pnames2) where -- Packages in the second list mask those in the first, however preferred -- packages go first in the list. @@ -268,15 +266,22 @@ insert pkg (PackageIndex pids pnames) = where pids' = Map.insert (installedUnitId pkg) pkg pids pnames' = insertPackageName pnames + insertPackageName = Map.insertWith (\_ -> insertPackageVersion) - (packageName pkg, IPI.sourceLibName pkg) - (Map.singleton (packageVersion pkg) [pkg]) + (packageName pkg) versionSingleton + versionSingleton = Map.singleton (packageVersion pkg) componentSingleton insertPackageVersion = + Map.insertWith (\_ -> insertPackageComponent) + (packageVersion pkg) componentSingleton + + componentSingleton = Map.singleton (IPI.sourceLibName pkg) instanceSingleton + insertPackageComponent = Map.insertWith (\_ -> insertPackageInstance) - (packageVersion pkg) [pkg] + (IPI.sourceLibName pkg) instanceSingleton + instanceSingleton = [pkg] insertPackageInstance pkgs = pkg : deleteBy (equating installedUnitId) pkg pkgs @@ -288,20 +293,22 @@ deleteUnitId :: UnitId -> InstalledPackageIndex deleteUnitId ipkgid original@(PackageIndex pids pnames) = case Map.updateLookupWithKey (\_ _ -> Nothing) ipkgid pids of (Nothing, _) -> original - (Just spkgid, pids') -> mkPackageIndex pids' - (deletePkgName spkgid pnames) + (Just spkgid, pids') -> mkPackageIndex pids' (deletePkgName pnames) + where + deletePkgName = + Map.update deletePkgVersion (packageName spkgid) - where - deletePkgName spkgid = - Map.update (deletePkgVersion spkgid) (packageName spkgid, IPI.sourceLibName spkgid) + deletePkgVersion = + (\m -> if Map.null m then Nothing else Just m) + . Map.update deletePkgComponent (packageVersion spkgid) - deletePkgVersion spkgid = - (\m -> if Map.null m then Nothing else Just m) - . Map.update deletePkgInstance (packageVersion spkgid) + deletePkgComponent = + (\m -> if Map.null m then Nothing else Just m) + . Map.update deletePkgInstance (IPI.sourceLibName spkgid) - deletePkgInstance = - (\xs -> if null xs then Nothing else Just xs) - . List.deleteBy (\_ pkg -> installedUnitId pkg == ipkgid) undefined + deletePkgInstance = + (\xs -> if null xs then Nothing else Just xs) + . List.deleteBy (\_ pkg -> installedUnitId pkg == ipkgid) undefined -- | Backwards compatibility wrapper for Cabal pre-1.24. {-# DEPRECATED deleteInstalledPackageId "Use deleteUnitId instead" #-} @@ -313,37 +320,33 @@ deleteInstalledPackageId = deleteUnitId -- deleteSourcePackageId :: PackageId -> InstalledPackageIndex -> InstalledPackageIndex -deleteSourcePackageId pkgid original@(PackageIndex pids pnames) = +deleteSourcePackageId bad@(PackageIdentifier bname bver) + original@(PackageIndex pids pnames) = -- NB: Doesn't delete internal packages - case Map.lookup (packageName pkgid, Nothing) pnames of + case Map.lookup bname pnames of Nothing -> original - Just pvers -> case Map.lookup (packageVersion pkgid) pvers of + Just pvers -> case Map.lookup bver pvers of Nothing -> original - Just pkgs -> mkPackageIndex - (foldl' (flip (Map.delete . installedUnitId)) pids pkgs) - (deletePkgName pnames) + Just _pgs -> mkPackageIndex (Map.filter ((bad /=) . packageId) pids) + (deletePkgName pnames) where deletePkgName = - Map.update deletePkgVersion (packageName pkgid, Nothing) + Map.update deletePkgVersion bname deletePkgVersion = (\m -> if Map.null m then Nothing else Just m) - . Map.delete (packageVersion pkgid) + . Map.delete bver -- | Removes all packages with this (case-sensitive) name from the index. -- --- NB: Does NOT delete internal libraries from this package. --- deletePackageName :: PackageName -> InstalledPackageIndex -> InstalledPackageIndex deletePackageName name original@(PackageIndex pids pnames) = - case Map.lookup (name, Nothing) pnames of + case Map.lookup name pnames of Nothing -> original - Just pvers -> mkPackageIndex - (foldl' (flip (Map.delete . installedUnitId)) pids - (concat (Map.elems pvers))) - (Map.delete (name, Nothing) pnames) + Just _pvers -> mkPackageIndex (Map.filter ((name /=) . packageName) pids) + (Map.delete name pnames) {- -- | Removes all packages satisfying this dependency from the index. @@ -370,8 +373,8 @@ allPackages = Map.elems . unitIdIndex -- allPackagesByName :: PackageIndex a -> [(PackageName, [a])] allPackagesByName index = - [ (pkgname, concat (Map.elems pvers)) - | ((pkgname, Nothing), pvers) <- Map.toList (packageIdIndex index) ] + [ (pkgname, concat $ concat $ fmap Map.elems $ Map.elems pvers) + | (pkgname, pvers) <- Map.toList (packageIdIndex index) ] -- | Get all the packages from the index. -- @@ -383,8 +386,9 @@ allPackagesBySourcePackageId :: HasUnitId a => PackageIndex a -> [(PackageId, [a])] allPackagesBySourcePackageId index = [ (packageId ipkg, ipkgs) - | ((_, Nothing), pvers) <- Map.toList (packageIdIndex index) - , ipkgs@(ipkg:_) <- Map.elems pvers ] + | pvers <- Map.elems (packageIdIndex index) + , plibs <- Map.elems pvers + , ipkgs@(ipkg:_) <- maybeToList $ Map.lookup Nothing plibs ] -- | Get all the packages from the index. -- @@ -395,8 +399,9 @@ allPackagesBySourcePackageIdAndLibName :: HasUnitId a => PackageIndex a -> [((PackageId, Maybe UnqualComponentName), [a])] allPackagesBySourcePackageIdAndLibName index = [ ((packageId ipkg, ln), ipkgs) - | ((_, ln), pvers) <- Map.toList (packageIdIndex index) - , ipkgs@(ipkg:_) <- Map.elems pvers ] + | pvers <- Map.elems (packageIdIndex index) + , plibs <- Map.elems pvers + , (ln, ipkgs@(ipkg:_)) <- Map.toList plibs ] -- -- * Lookups @@ -433,13 +438,12 @@ lookupInstalledPackageId = lookupUnitId -- preference, with the most preferred first. -- lookupSourcePackageId :: PackageIndex a -> PackageId -> [a] -lookupSourcePackageId index pkgid = +lookupSourcePackageId index pkgid = do + pvers <- maybeToList $ Map.lookup (packageName pkgid) (packageIdIndex index) + plibs <- maybeToList $ Map.lookup (packageVersion pkgid) pvers -- Do not lookup internal libraries - case Map.lookup (packageName pkgid, Nothing) (packageIdIndex index) of - Nothing -> [] - Just pvers -> case Map.lookup (packageVersion pkgid) pvers of - Nothing -> [] - Just pkgs -> pkgs -- in preference order + pinsts <- maybeToList $ Map.lookup Nothing plibs + pinsts -- | Convenient alias of 'lookupSourcePackageId', but assuming only -- one package per package ID. @@ -453,11 +457,12 @@ lookupPackageId index pkgid = case lookupSourcePackageId index pkgid of -- lookupPackageName :: PackageIndex a -> PackageName -> [(Version, [a])] -lookupPackageName index name = - -- Do not match internal libraries - case Map.lookup (name, Nothing) (packageIdIndex index) of - Nothing -> [] - Just pvers -> Map.toList pvers +lookupPackageName index name = do + pvers <- maybeToList $ Map.lookup name (packageIdIndex index) + (ln, plibs) <- Map.toList pvers + -- Do not lookup internal libraries + pinsts <- maybeToList $ Map.lookup Nothing plibs + pure (ln, pinsts) -- | Does a lookup by source package name and a range of versions. @@ -470,28 +475,15 @@ lookupPackageName index name = -- -- INVARIANT: List of eligible 'IPI.InstalledPackageInfo' is non-empty. -- -lookupDependency :: InstalledPackageIndex -> Dependency - -> [(Version, [IPI.InstalledPackageInfo])] -lookupDependency index dep = - -- Yes, a little bit of a misnomer here! - lookupInternalDependency index dep Nothing - --- | Does a lookup by source package name and a range of versions. --- --- We get back any number of versions of the specified package name, all --- satisfying the version range constraint. --- --- INVARIANT: List of eligible 'IPI.InstalledPackageInfo' is non-empty. --- -lookupInternalDependency :: InstalledPackageIndex -> Dependency - -> Maybe UnqualComponentName +lookupDependency :: InstalledPackageIndex -> LibDependency -> [(Version, [IPI.InstalledPackageInfo])] -lookupInternalDependency index (Dependency name versionRange) libn = - case Map.lookup (name, libn) (packageIdIndex index) of +lookupDependency index (LibDependency name lname versionRange) = + case Map.lookup name (packageIdIndex index) of Nothing -> [] Just pvers -> [ (ver, pkgs') - | (ver, pkgs) <- Map.toList pvers + | (ver, pcomp) <- Map.toList pvers , ver `withinRange` versionRange + , pkgs <- maybeToList $ Map.lookup lname pcomp , let pkgs' = filter eligible pkgs -- Enforce the invariant , not (null pkgs') @@ -523,13 +515,19 @@ lookupInternalDependency index (Dependency name versionRange) libn = searchByName :: PackageIndex a -> String -> SearchResult [a] searchByName index name = -- Don't match internal packages - case [ pkgs | pkgs@((pname, Nothing),_) <- Map.toList (packageIdIndex index) - , lowercase (unPackageName pname) == lname ] of + case do + (pname, pver) <- Map.toList (packageIdIndex index) + guard $ lowercase (unPackageName pname) == lname + let pinsts = do + plibs <- Map.elems pver + concat $ maybeToList $ Map.lookup Nothing plibs + pure (pname, pinsts) + of [] -> None - [(_,pvers)] -> Unambiguous (concat (Map.elems pvers)) - pkgss -> case find ((mkPackageName name ==) . fst . fst) pkgss of - Just (_,pvers) -> Unambiguous (concat (Map.elems pvers)) - Nothing -> Ambiguous (map (concat . Map.elems . snd) pkgss) + [(_,pvers)] -> Unambiguous pvers + pkgss -> case find ((mkPackageName name ==) . fst) pkgss of + Just (_,pvers) -> Unambiguous pvers + Nothing -> Ambiguous . map snd $ pkgss where lname = lowercase name data SearchResult a = None | Unambiguous a | Ambiguous [a] @@ -542,9 +540,10 @@ searchByNameSubstring :: PackageIndex a -> String -> [a] searchByNameSubstring index searchterm = [ pkg -- Don't match internal packages - | ((pname, Nothing), pvers) <- Map.toList (packageIdIndex index) + | (pname, pvers) <- Map.toList (packageIdIndex index) , lsearchterm `isInfixOf` lowercase (unPackageName pname) - , pkgs <- Map.elems pvers + , plibs <- Map.elems pvers + , pkgs <- maybeToList $ Map.lookup Nothing plibs , pkg <- pkgs ] where lsearchterm = lowercase searchterm diff --git a/Cabal/Distribution/Simple/Setup.hs b/Cabal/Distribution/Simple/Setup.hs index 729c5a96df3..68f3ae3922f 100644 --- a/Cabal/Distribution/Simple/Setup.hs +++ b/Cabal/Distribution/Simple/Setup.hs @@ -98,6 +98,7 @@ import Distribution.Types.Dependency import Distribution.Types.ComponentId import Distribution.Types.Module import Distribution.Types.PackageName +import Distribution.Types.UnqualComponentName import Distribution.Compat.Semigroup (Last' (..)) @@ -418,7 +419,7 @@ data ConfigFlags = ConfigFlags { configStripLibs :: Flag Bool, -- ^Enable library stripping configConstraints :: [Dependency], -- ^Additional constraints for -- dependencies. - configDependencies :: [(PackageName, ComponentId)], + configDependencies :: [(PackageName, Maybe UnqualComponentName, ComponentId)], -- ^The packages depended on. configInstantiateWith :: [(ModuleName, Module)], -- ^ The requested Backpack instantiation. If empty, either this @@ -795,7 +796,7 @@ configureOptions showOrParseArgs = configDependencies (\v flags -> flags { configDependencies = v}) (reqArg "NAME=CID" (readP_to_E (const "dependency expected") ((\x -> [x]) `fmap` parseDependency)) - (map (\x -> display (fst x) ++ "=" ++ display (snd x)))) + (map (\(pn,mb_cn,cid) -> display pn ++ (maybe "" (\x -> ":" ++ display x) mb_cn) ++ "=" ++ display cid))) ,option "" ["instantiate-with"] "A mapping of signature names to concrete module instantiations." @@ -886,12 +887,15 @@ showProfDetailLevelFlag :: Flag ProfDetailLevel -> [String] showProfDetailLevelFlag NoFlag = [] showProfDetailLevelFlag (Flag dl) = [showProfDetailLevel dl] -parseDependency :: Parse.ReadP r (PackageName, ComponentId) +parseDependency :: Parse.ReadP r (PackageName, Maybe UnqualComponentName, ComponentId) parseDependency = do x <- parse + y <- Parse.option Nothing $ do + _ <- Parse.char ':' + fmap Just parse _ <- Parse.char '=' - y <- parse - return (x, y) + z <- parse + return (x, y, z) installDirsOptions :: [OptionField (InstallDirs (Flag PathTemplate))] installDirsOptions = diff --git a/Cabal/Distribution/Types/BuildInfo.hs b/Cabal/Distribution/Types/BuildInfo.hs index 7b0b8d184b0..7bc44149dbf 100644 --- a/Cabal/Distribution/Types/BuildInfo.hs +++ b/Cabal/Distribution/Types/BuildInfo.hs @@ -18,10 +18,10 @@ import Prelude () import Distribution.Compat.Prelude import Distribution.Types.Mixin -import Distribution.Types.Dependency import Distribution.Types.ExeDependency import Distribution.Types.LegacyExeDependency import Distribution.Types.PkgconfigDependency +import Distribution.Types.LibDependency import Distribution.ModuleName import Distribution.Compiler @@ -77,7 +77,30 @@ data BuildInfo = BuildInfo { customFieldsBI :: [(String,String)], -- ^Custom fields starting -- with x-, stored in a -- simple assoc-list. - targetBuildDepends :: [Dependency], -- ^ Dependencies specific to a library or executable target + + -- | These are the library-level dependencies we have on + -- other packages. This corresponds closely to @build-depends@, + -- but this field drops any component names (anywhere you + -- see @pkg:lib >= 2.0@, this actually indicates the + -- 'Dependency' @pkg >= 2.0@. This field does NOT control + -- what libraries are brought into scope, for import in + -- Haskell (for that, see 'implicitMixins' and 'mixins'). + -- This combined with 'implicitMixins' constitute the "full" + -- meaning of @build-depends@; for backwards compatibility + -- we don't keep these together. + -- + -- Historically, this got the name 'targetBuildDepends' because + -- it was the @build-depends@ specific to a "target" (i.e., + -- a component); 'buildDepends' was reserved for the + -- package-wide @build-depends@. These days, target-specific + -- dependencies are the standard mode of use, so we really + -- ought to rename this. + targetBuildDepends :: [LibDependency], + + -- | Explicitly specified mix-ins specified by the @mixins@ + -- field. If there is a 'Mixin' for a + -- 'PackageName'/'UnqualComponentName' combination here, it + -- overrides the corresponding entry from 'implicitMixins'. mixins :: [Mixin] } deriving (Generic, Show, Read, Eq, Typeable, Data) diff --git a/Cabal/Distribution/Types/DependencyMap.hs b/Cabal/Distribution/Types/DependencyMap.hs index f7dc3a20a9a..40932e84e92 100644 --- a/Cabal/Distribution/Types/DependencyMap.hs +++ b/Cabal/Distribution/Types/DependencyMap.hs @@ -13,10 +13,10 @@ #endif module Distribution.Types.DependencyMap ( - DependencyMap, + DependencyMap(..), toDepMap, fromDepMap, - constrainBy, + lookupDepMap, ) where import Prelude () @@ -52,23 +52,5 @@ toDepMap ds = fromDepMap :: DependencyMap -> [Dependency] fromDepMap m = [ Dependency p vr | (p,vr) <- Map.toList (unDependencyMap m) ] --- Apply extra constraints to a dependency map. --- Combines dependencies where the result will only contain keys from the left --- (first) map. If a key also exists in the right map, both constraints will --- be intersected. -constrainBy :: DependencyMap -- ^ Input map - -> DependencyMap -- ^ Extra constraints - -> DependencyMap -constrainBy left extra = - DependencyMap $ -#ifdef MIN_VERSION_containers_0_5_0 - Map.foldrWithKey tightenConstraint (unDependencyMap left) - (unDependencyMap extra) -#else - Map.foldWithKey tightenConstraint (unDependencyMap left) - (unDependencyMap extra) -#endif - where tightenConstraint n c l = - case Map.lookup n l of - Nothing -> l - Just vr -> Map.insert n (intersectVersionRanges vr c) l +lookupDepMap :: DependencyMap -> PackageName -> Maybe VersionRange +lookupDepMap (DependencyMap m) pn = Map.lookup pn m diff --git a/Cabal/Distribution/Types/ExeDependency.hs b/Cabal/Distribution/Types/ExeDependency.hs index 20fc4a3aa3b..a47d270e521 100644 --- a/Cabal/Distribution/Types/ExeDependency.hs +++ b/Cabal/Distribution/Types/ExeDependency.hs @@ -21,11 +21,12 @@ import Text.PrettyPrint ((<+>), text) -- | Describes a dependency on an executable from a package -- -data ExeDependency = ExeDependency - PackageName - UnqualComponentName -- name of executable component of package - VersionRange - deriving (Generic, Read, Show, Eq, Typeable, Data) +data ExeDependency = ExeDependency { + exeDepPackageName :: PackageName, + exeDepExecutableName :: UnqualComponentName, + exeDepVersionRange :: VersionRange + } + deriving (Generic, Read, Show, Eq, Typeable, Data) instance Binary ExeDependency instance NFData ExeDependency where rnf = genericRnf diff --git a/Cabal/Distribution/Types/GenericPackageDescription.hs b/Cabal/Distribution/Types/GenericPackageDescription.hs index 01d9936dedc..d8bcccfff93 100644 --- a/Cabal/Distribution/Types/GenericPackageDescription.hs +++ b/Cabal/Distribution/Types/GenericPackageDescription.hs @@ -25,7 +25,7 @@ import Distribution.Compat.ReadP ((+++)) import Distribution.Types.PackageDescription -import Distribution.Types.Dependency +import Distribution.Types.LibDependency import Distribution.Types.Library import Distribution.Types.ForeignLib import Distribution.Types.Executable @@ -46,12 +46,12 @@ data GenericPackageDescription = GenericPackageDescription { packageDescription :: PackageDescription, genPackageFlags :: [Flag], - condLibrary :: Maybe (CondTree ConfVar [Dependency] Library), - condSubLibraries :: [(UnqualComponentName, CondTree ConfVar [Dependency] Library)], - condForeignLibs :: [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)], - condExecutables :: [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)], - condTestSuites :: [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)], - condBenchmarks :: [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)] + condLibrary :: Maybe (CondTree ConfVar [LibDependency] Library), + condSubLibraries :: [(UnqualComponentName, CondTree ConfVar [LibDependency] Library)], + condForeignLibs :: [(UnqualComponentName, CondTree ConfVar [LibDependency] ForeignLib)], + condExecutables :: [(UnqualComponentName, CondTree ConfVar [LibDependency] Executable)], + condTestSuites :: [(UnqualComponentName, CondTree ConfVar [LibDependency] TestSuite)], + condBenchmarks :: [(UnqualComponentName, CondTree ConfVar [LibDependency] Benchmark)] } deriving (Show, Eq, Typeable, Data, Generic) diff --git a/Cabal/Distribution/Types/LibDependency.hs b/Cabal/Distribution/Types/LibDependency.hs new file mode 100644 index 00000000000..a9732e835e7 --- /dev/null +++ b/Cabal/Distribution/Types/LibDependency.hs @@ -0,0 +1,60 @@ +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DeriveDataTypeable #-} +module Distribution.Types.LibDependency + ( LibDependency(..) + , thisPackageVersion + , notThisPackageVersion + , libDependencyToDependency + , simplifyLibDependency + ) where + +import Prelude () +import Distribution.Compat.Prelude + +import Distribution.Types.PackageName +import Distribution.Types.UnqualComponentName +import Distribution.Types.Dependency +import Distribution.Version ( VersionRange, anyVersion + , simplifyVersionRange ) +import Distribution.Compat.ReadP +import Distribution.Text +import Text.PrettyPrint as PP ((<+>), text, empty) + +-- | Like 'Dependency', but this corresponds exactly to the syntax we support in +-- a Cabal file. +data LibDependency = LibDependency { + libDepPackageName :: PackageName, + libDepLibraryName :: Maybe UnqualComponentName, + libDepVersionRange :: VersionRange + } + deriving (Generic, Read, Show, Eq, Typeable, Data) + +instance Binary LibDependency +instance NFData LibDependency where rnf = genericRnf + +instance Text LibDependency where + disp (LibDependency name mCname ver) = + (disp name <<>> dispMaybeCname) <+> disp ver + where + dispMaybeCname = case mCname of + Nothing -> PP.empty + Just cname -> text ":" <<>> disp cname + + parse = do name <- parse + mb_cname <- option Nothing $ do + _ <- char ':' + fmap Just parse + skipSpaces + ver <- parse <++ return anyVersion + return (LibDependency name mb_cname ver) + +libDependencyToDependency :: LibDependency -> Dependency +libDependencyToDependency (LibDependency pn _ vr) = Dependency pn vr + + +-- | Simplify the 'VersionRange' expression in a 'Dependency'. +-- See 'simplifyVersionRange'. +-- +simplifyLibDependency :: LibDependency -> LibDependency +simplifyLibDependency (LibDependency name mb_cname range) = + LibDependency name mb_cname (simplifyVersionRange range) diff --git a/Cabal/Distribution/Types/LibDependencyMap.hs b/Cabal/Distribution/Types/LibDependencyMap.hs new file mode 100644 index 00000000000..cabb7b6bafa --- /dev/null +++ b/Cabal/Distribution/Types/LibDependencyMap.hs @@ -0,0 +1,99 @@ +{-# LANGUAGE CPP #-} + +#ifdef MIN_VERSION_containers +#if MIN_VERSION_containers(0,5,0) +#define MIN_VERSION_containers_0_5_0 +#endif +#endif + +#ifndef MIN_VERSION_containers +#if __GLASGOW_HASKELL__ >= 706 +#define MIN_VERSION_containers_0_5_0 +#endif +#endif + +module Distribution.Types.LibDependencyMap + ( LibDependencyMap + , toLibDepMap + , fromLibDepMap + , lookupLibDepMap + , discardLibNames + , constrainBy + ) where + +import Prelude () +import Distribution.Compat.Prelude + +import Distribution.Types.PackageName +import Distribution.Types.LibDependency +import Distribution.Types.DependencyMap +import Distribution.Types.UnqualComponentName +import Distribution.Version + +#ifdef MIN_VERSION_containers_0_5_0 +import qualified Data.Map.Lazy as Map +#else +import qualified Data.Map as Map +#endif +import qualified Data.Set as Set + +-- | A map of dependencies. Newtyped since the default monoid instance is not +-- appropriate. The monoid instance uses 'intersectVersionRanges'. +newtype LibDependencyMap = LibDependencyMap { + unLibDependencyMap :: Map PackageName ( Set.Set (Maybe UnqualComponentName) + , VersionRange ) + } + deriving (Show, Read) + +instance Monoid LibDependencyMap where + mempty = LibDependencyMap Map.empty + mappend = (<>) + +instance Semigroup LibDependencyMap where + (LibDependencyMap a) <> (LibDependencyMap b) = + LibDependencyMap (Map.unionWith combineValue a b) + +combineValue :: (Set.Set (Maybe UnqualComponentName), VersionRange) + -> (Set.Set (Maybe UnqualComponentName), VersionRange) + -> (Set.Set (Maybe UnqualComponentName), VersionRange) +combineValue (cs0, vr0) (cs1, vr1) = ( Set.union cs0 cs1 + , intersectVersionRanges vr0 vr1 ) + +toLibDepMap :: [LibDependency] -> LibDependencyMap +toLibDepMap ds = LibDependencyMap $ Map.fromListWith + combineValue + [ (p, (Set.singleton l, vr)) | LibDependency p l vr <- ds ] + +fromLibDepMap :: LibDependencyMap -> [LibDependency] +fromLibDepMap m = [ LibDependency p l vr + | (p, (ls, vr)) <- Map.toList (unLibDependencyMap m) + , l <- Set.toList ls ] + +lookupLibDepMap :: LibDependencyMap + -> PackageName + -> Maybe (Set.Set (Maybe UnqualComponentName), VersionRange) +lookupLibDepMap (LibDependencyMap m) pn = Map.lookup pn m + +discardLibNames :: LibDependencyMap -> DependencyMap +discardLibNames = DependencyMap . fmap (\(_, vr) -> vr) . unLibDependencyMap + +-- Apply extra constraints to a dependency map. +-- Combines dependencies where the result will only contain keys from the left +-- (first) map. If a key also exists in the right map, both constraints will +-- be intersected. +constrainBy :: LibDependencyMap -- ^ Input map + -> DependencyMap -- ^ Extra constraints + -> LibDependencyMap +constrainBy left extra = LibDependencyMap $ + fold tightenConstraint (unLibDependencyMap left) + (unDependencyMap extra) + where tightenConstraint n v l = + case Map.lookup n l of + Nothing -> l + Just entry -> Map.insert n (combineValue entry (Set.empty, v)) l + fold = +#ifdef MIN_VERSION_containers_0_5_0 + Map.foldrWithKey +#else + Map.foldWithKey +#endif diff --git a/Cabal/Distribution/Types/Mixin.hs b/Cabal/Distribution/Types/Mixin.hs index daf4f33757b..521c701f0ac 100644 --- a/Cabal/Distribution/Types/Mixin.hs +++ b/Cabal/Distribution/Types/Mixin.hs @@ -8,25 +8,32 @@ module Distribution.Types.Mixin ( import Prelude () import Distribution.Compat.Prelude -import Text.PrettyPrint ((<+>)) +import Text.PrettyPrint ((<+>), colon) import Distribution.Compat.ReadP import Distribution.Text import Distribution.Types.PackageName import Distribution.Types.IncludeRenaming +import Distribution.Types.UnqualComponentName data Mixin = Mixin { mixinPackageName :: PackageName + , mixinLibraryName :: Maybe UnqualComponentName , mixinIncludeRenaming :: IncludeRenaming } deriving (Show, Read, Eq, Ord, Typeable, Data, Generic) instance Binary Mixin instance Text Mixin where - disp (Mixin pkg_name incl) = + disp (Mixin pkg_name Nothing incl) = disp pkg_name <+> disp incl + disp (Mixin pkg_name (Just lib_name) incl) = + disp pkg_name <<>> colon <<>> disp lib_name <+> disp incl parse = do pkg_name <- parse + mb_lib_name <- option Nothing $ do + _ <- char ':' + fmap Just parse skipSpaces incl <- parse - return (Mixin pkg_name incl) + return (Mixin pkg_name mb_lib_name incl) diff --git a/Cabal/Distribution/Types/PackageDescription.hs b/Cabal/Distribution/Types/PackageDescription.hs index 50efaf9294e..d355c25e631 100644 --- a/Cabal/Distribution/Types/PackageDescription.hs +++ b/Cabal/Distribution/Types/PackageDescription.hs @@ -68,7 +68,7 @@ import Distribution.Types.ForeignLib import Distribution.Types.Component import Distribution.Types.ComponentRequestedSpec -import Distribution.Types.Dependency +import Distribution.Types.LibDependency import Distribution.Types.PackageId import Distribution.Types.ComponentName import Distribution.Types.PackageName @@ -329,10 +329,10 @@ enabledBuildInfos pkg enabled = -- * Utils -- ------------------------------------------------------------ -allBuildDepends :: PackageDescription -> [Dependency] +allBuildDepends :: PackageDescription -> [LibDependency] allBuildDepends = targetBuildDepends <=< allBuildInfo -enabledBuildDepends :: PackageDescription -> ComponentRequestedSpec -> [Dependency] +enabledBuildDepends :: PackageDescription -> ComponentRequestedSpec -> [LibDependency] enabledBuildDepends spec pd = targetBuildDepends =<< enabledBuildInfos spec pd diff --git a/Cabal/Distribution/Types/SetupBuildInfo.hs b/Cabal/Distribution/Types/SetupBuildInfo.hs index 3afc922b54b..fbfb245555b 100644 --- a/Cabal/Distribution/Types/SetupBuildInfo.hs +++ b/Cabal/Distribution/Types/SetupBuildInfo.hs @@ -19,6 +19,8 @@ import Distribution.Types.Dependency data SetupBuildInfo = SetupBuildInfo { setupDepends :: [Dependency], + -- ^ This will become `[LibDependency]` if when external named + -- libraries are usabable as dependencies. defaultSetupDepends :: Bool -- ^ Is this a default 'custom-setup' section added by the cabal-install -- code (as opposed to user-provided)? This field is only used diff --git a/Cabal/doc/developing-packages.rst b/Cabal/doc/developing-packages.rst index d20119c2aa4..2df3c3c3750 100644 --- a/Cabal/doc/developing-packages.rst +++ b/Cabal/doc/developing-packages.rst @@ -1054,26 +1054,22 @@ look something like this: cabal-version: >= 1.23 build-type: Simple - library foo-internal + library internal exposed-modules: Foo.Internal build-depends: base library exposed-modules: Foo.Public - build-depends: foo-internal, base + build-depends: base, foo:internal test-suite test-foo type: exitcode-stdio-1.0 main-is: test-foo.hs - build-depends: foo-internal, base - -Internal libraries are also useful for packages that define multiple -executables, but do not define a publically accessible library. Internal -libraries are only visible internally in the package (so they can only -be added to the :pkg-field:`build-depends` of same-package libraries, -executables, test suites, etc.) Internal libraries locally shadow any -packages which have the same name (so don't name an internal library -with the same name as an external dependency.) + build-depends: base, foo:internal + +An internal library is referenced by qualifying the library name with +the name of the package it comes from. At the moment, referencing +internal libraries of external packages is not supported. Opening an interpreter session ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ diff --git a/Cabal/tests/ParserHackageTests.hs b/Cabal/tests/ParserHackageTests.hs index 6552c1b5952..734a5059a13 100644 --- a/Cabal/tests/ParserHackageTests.hs +++ b/Cabal/tests/ParserHackageTests.hs @@ -17,7 +17,7 @@ import System.Environment (getArgs) import System.Exit (exitFailure) import System.FilePath (()) -import Distribution.Types.Dependency +import Distribution.Types.LibDependency import Distribution.Types.UnqualComponentName import Distribution.PackageDescription @@ -327,10 +327,10 @@ _2 = lens snd $ \(a, _) b -> (a, b) packageDescription_ :: Lens' GenericPackageDescription PackageDescription packageDescription_ = lens packageDescription $ \s a -> s { packageDescription = a } -condLibrary_ :: Lens' GenericPackageDescription (Maybe (CondTree ConfVar [Dependency] Library)) +condLibrary_ :: Lens' GenericPackageDescription (Maybe (CondTree ConfVar [LibDependency] Library)) condLibrary_ = lens condLibrary $ \s a -> s { condLibrary = a} -condExecutables_ :: Lens' GenericPackageDescription [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)] +condExecutables_ :: Lens' GenericPackageDescription [(UnqualComponentName, CondTree ConfVar [LibDependency] Executable)] condExecutables_ = lens condExecutables $ \s a -> s { condExecutables = a } condTreeData_ :: Lens' (CondTree v c a) a diff --git a/cabal-install/Distribution/Client/Configure.hs b/cabal-install/Distribution/Client/Configure.hs index 23fa1fcfbc6..6d645068ff8 100644 --- a/cabal-install/Distribution/Client/Configure.hs +++ b/cabal-install/Distribution/Client/Configure.hs @@ -410,8 +410,12 @@ configurePackage verbosity platform comp scriptOptions configFlags -- depending on the Cabal version we are talking to. configConstraints = [ thisPackageVersion srcid | ConfiguredId srcid (Just PkgDesc.CLibName) _uid <- CD.nonSetupDeps deps ], - configDependencies = [ (packageName srcid, uid) - | ConfiguredId srcid (Just PkgDesc.CLibName) uid <- CD.nonSetupDeps deps ], + configDependencies = [ (packageName srcid, lname, uid) + | ConfiguredId srcid cname uid <- CD.nonSetupDeps deps + , lname <- case cname of + Just (PkgDesc.CLibName) -> [Nothing] + Just (PkgDesc.CSubLibName sl) -> [Just sl] + _ -> [] ], -- Use '--exact-configuration' if supported. configExactConfiguration = toFlag True, configVerbosity = toFlag verbosity, diff --git a/cabal-install/Distribution/Client/GenBounds.hs b/cabal-install/Distribution/Client/GenBounds.hs index b25f166efc4..c98712f40c2 100644 --- a/cabal-install/Distribution/Client/GenBounds.hs +++ b/cabal-install/Distribution/Client/GenBounds.hs @@ -38,7 +38,8 @@ import Distribution.PackageDescription.Parse #endif import Distribution.Types.ComponentRequestedSpec ( defaultComponentRequestedSpec ) -import Distribution.Types.Dependency +import Distribution.Types.LibDependency + ( libDepPackageName, libDepVersionRange ) import Distribution.Simple.Compiler ( Compiler, PackageDBStack, compilerInfo ) import Distribution.Simple.Program @@ -123,7 +124,7 @@ genBounds verbosity packageDBs repoCtxt comp platform progdb mSandboxPkgInfo case epd of Left _ -> putStrLn "finalizePD failed" Right (pd,_) -> do - let needBounds = filter (not . hasUpperBound . depVersion) $ + let needBounds = filter (not . hasUpperBound . libDepVersionRange) $ enabledBuildDepends pd defaultComponentRequestedSpec if (null needBounds) @@ -138,19 +139,13 @@ genBounds verbosity packageDBs repoCtxt comp platform progdb mSandboxPkgInfo putStrLn boundsNeededMsg - let isNeeded pkg = unPackageName (packageName pkg) - `elem` map depName needBounds + let isNeeded pkg = packageName pkg + `elem` map libDepPackageName needBounds let thePkgs = filter isNeeded pkgs let padTo = maximum $ map (length . unPackageName . packageName) pkgs mapM_ (putStrLn . (++",") . showBounds padTo) thePkgs - depName :: Dependency -> String - depName (Dependency pn _) = unPackageName pn - - depVersion :: Dependency -> VersionRange - depVersion (Dependency _ vr) = vr - -- | The message printed when some dependencies are found to be lacking proper -- PVP-mandated bounds. boundsNeededMsg :: String diff --git a/cabal-install/Distribution/Client/Install.hs b/cabal-install/Distribution/Client/Install.hs index 2a40d0c5c45..d1b0d02a6e2 100644 --- a/cabal-install/Distribution/Client/Install.hs +++ b/cabal-install/Distribution/Client/Install.hs @@ -1243,9 +1243,12 @@ installReadyPackage platform cinfo configFlags configConstraints = [ thisPackageVersion srcid | ConfiguredId srcid (Just PackageDescription.CLibName) _ipid <- CD.nonSetupDeps deps ], - configDependencies = [ (packageName srcid, dep_ipid) - | ConfiguredId srcid (Just PackageDescription.CLibName) dep_ipid - <- CD.nonSetupDeps deps ], + configDependencies = [ (packageName srcid, lname, uid) + | ConfiguredId srcid cname uid <- CD.nonSetupDeps deps + , lname <- case cname of + Just (PackageDescription.CLibName) -> [Nothing] + Just (PackageDescription.CSubLibName sl) -> [Just sl] + _ -> [] ], -- Use '--exact-configuration' if supported. configExactConfiguration = toFlag True, configBenchmarks = toFlag False, diff --git a/cabal-install/Distribution/Client/List.hs b/cabal-install/Distribution/Client/List.hs index 72ec047e948..ec49d8d7ac8 100644 --- a/cabal-install/Distribution/Client/List.hs +++ b/cabal-install/Distribution/Client/List.hs @@ -17,6 +17,8 @@ import Distribution.Package ( PackageName, Package(..), packageName , packageVersion, UnitId ) import Distribution.Types.Dependency +import Distribution.Types.LibDependency + ( LibDependency(..), libDependencyToDependency ) import Distribution.Types.UnqualComponentName import Distribution.ModuleName (ModuleName) import Distribution.License (License) @@ -229,7 +231,8 @@ info verbosity packageDBs repoCtxt comp progdb selectedInstalledPkgs = InstalledPackageIndex.lookupDependency installedPkgIndex - (Dependency name verConstraint) + -- Nothing is OK for now, list sublibs later + (LibDependency name Nothing verConstraint) selectedSourcePkgs = PackageIndex.lookupDependency sourcePkgIndex (Dependency name verConstraint) selectedSourcePkg' = latestWithPref pref selectedSourcePkgs @@ -468,9 +471,9 @@ mergePackageInfo versionPref installedPkgs sourcePkgs selectedPkg showVer = -- NB: only for the PUBLIC library (concatMap getListOfExposedModules . maybeToList . Source.library) source, - dependencies = - combine (map (SourceDependency . simplifyDependency) - . Source.allBuildDepends) source + dependencies = combine + (map (SourceDependency . simplifyDependency . libDependencyToDependency) + . Source.allBuildDepends) source (map InstalledDependency . Installed.depends) installed, haddockHtml = fromMaybe "" . join . fmap (listToMaybe . Installed.haddockHTMLs) diff --git a/cabal-install/Distribution/Client/Outdated.hs b/cabal-install/Distribution/Client/Outdated.hs index 6b5ee99e276..3762f613f7a 100644 --- a/cabal-install/Distribution/Client/Outdated.hs +++ b/cabal-install/Distribution/Client/Outdated.hs @@ -39,6 +39,7 @@ import Distribution.Text (display) import Distribution.Types.ComponentRequestedSpec (ComponentRequestedSpec(..)) import Distribution.Types.Dependency (Dependency(..), depPkgName, simplifyDependency) +import Distribution.Types.LibDependency (libDependencyToDependency) import Distribution.Verbosity (Verbosity, silent) import Distribution.Version (Version, LowerBound(..), UpperBound(..) @@ -151,10 +152,11 @@ depsFromPkgDesc verbosity comp platform = do case epd of Left _ -> die' verbosity "finalizePD failed" Right (pd, _) -> do + -- TODO: What about setup dependencies? let bd = allBuildDepends pd debug verbosity "Reading the list of dependencies from the package description" - return bd + return $ libDependencyToDependency <$> bd -- | Various knobs for customising the behaviour of 'listOutdated'. data ListOutdatedSettings = ListOutdatedSettings { diff --git a/cabal-install/Distribution/Client/PackageUtils.hs b/cabal-install/Distribution/Client/PackageUtils.hs index b1236fb38b1..b79c84181e7 100644 --- a/cabal-install/Distribution/Client/PackageUtils.hs +++ b/cabal-install/Distribution/Client/PackageUtils.hs @@ -15,26 +15,21 @@ module Distribution.Client.PackageUtils ( ) where import Distribution.Package - ( packageVersion, packageName ) + ( packageName ) import Distribution.Types.ComponentRequestedSpec ( ComponentRequestedSpec ) import Distribution.Types.Dependency -import Distribution.Types.UnqualComponentName +import Distribution.Types.LibDependency import Distribution.PackageDescription - ( PackageDescription(..), libName, enabledBuildDepends ) -import Distribution.Version - ( withinRange, isAnyVersion ) + ( PackageDescription(..), enabledBuildDepends ) --- | The list of dependencies that refer to external packages --- rather than internal package components. +-- | The list of dependencies that refer to external packages rather than +-- internal package components. -- +-- External deps should not be on a sub-lib, and internal deps should have a +-- compatable version range with the current package (or none at all), but Cabal +-- enforces these invariants so we need not worry about them. externalBuildDepends :: PackageDescription -> ComponentRequestedSpec -> [Dependency] -externalBuildDepends pkg spec = filter (not . internal) (enabledBuildDepends pkg spec) - where - -- True if this dependency is an internal one (depends on a library - -- defined in the same package). - internal (Dependency depName versionRange) = - (depName == packageName pkg && - packageVersion pkg `withinRange` versionRange) || - (Just (packageNameToUnqualComponentName depName) `elem` map libName (subLibraries pkg) && - isAnyVersion versionRange) +externalBuildDepends pkg spec = [ libDependencyToDependency dep + | dep <- enabledBuildDepends pkg spec + , libDepPackageName dep /= packageName pkg ] diff --git a/cabal-install/Distribution/Client/ProjectPlanning.hs b/cabal-install/Distribution/Client/ProjectPlanning.hs index 1f20da35da3..a5220dcb42b 100644 --- a/cabal-install/Distribution/Client/ProjectPlanning.hs +++ b/cabal-install/Distribution/Client/ProjectPlanning.hs @@ -3058,14 +3058,8 @@ setupHsConfigureFlags (ReadyPackage elab@ElaboratedConfiguredPackage{..}) -- NB: This does NOT use InstallPlan.depends, which includes executable -- dependencies which should NOT be fed in here (also you don't have -- enough info anyway) - configDependencies = [ (case mb_cn of - -- Special case for internal libraries - Just (CSubLibName uqn) - | packageId elab == srcid - -> mkPackageName (unUnqualComponentName uqn) - _ -> packageName srcid, - cid) - | ConfiguredId srcid mb_cn cid <- elabLibDependencies elab ] + configDependencies = [ (packageName srcid, componentNameString =<< libname, cid) + | ConfiguredId srcid libname cid <- elabLibDependencies elab ] configConstraints = case elabPkgOrComp of ElabPackage _ -> diff --git a/cabal-install/Distribution/Client/SetupWrapper.hs b/cabal-install/Distribution/Client/SetupWrapper.hs index b81a4780ba2..530da9bbb59 100644 --- a/cabal-install/Distribution/Client/SetupWrapper.hs +++ b/cabal-install/Distribution/Client/SetupWrapper.hs @@ -35,7 +35,7 @@ import qualified Distribution.Backpack as Backpack import Distribution.Package ( newSimpleUnitId, unsafeMkDefUnitId, ComponentId, PackageId, mkPackageName , PackageIdentifier(..), packageVersion, packageName ) -import Distribution.Types.Dependency +import Distribution.Types.LibDependency import Distribution.PackageDescription ( GenericPackageDescription(packageDescription) , PackageDescription(..), specVersion @@ -710,7 +710,7 @@ getExternalSetupMethod verbosity options pkg bt = do ,SetupScriptOptions) installedCabalVersion options' compiler progdb = do index <- maybeGetInstalledPackages options' compiler progdb - let cabalDep = Dependency (mkPackageName "Cabal") (useCabalVersion options') + let cabalDep = LibDependency (mkPackageName "Cabal") Nothing (useCabalVersion options') options'' = options' { usePackageIndex = Just index } case PackageIndex.lookupDependency index cabalDep of [] -> die' verbosity $ "The package '" ++ display (packageName pkg) diff --git a/cabal-install/Distribution/Solver/Modular/IndexConversion.hs b/cabal-install/Distribution/Solver/Modular/IndexConversion.hs index 0f59ae566b3..0c01780a6df 100644 --- a/cabal-install/Distribution/Solver/Modular/IndexConversion.hs +++ b/cabal-install/Distribution/Solver/Modular/IndexConversion.hs @@ -6,7 +6,6 @@ import Data.List as L import Data.Map as M import Data.Maybe import Data.Monoid as Mon -import Data.Set as S import Prelude hiding (pi) import Distribution.Compiler @@ -14,10 +13,10 @@ import Distribution.InstalledPackageInfo as IPI import Distribution.Package -- from Cabal import Distribution.Simple.BuildToolDepends -- from Cabal import Distribution.Types.Dependency -- from Cabal +import Distribution.Types.LibDependency -- from Cabal import Distribution.Types.ExeDependency -- from Cabal import Distribution.Types.PkgconfigDependency -- from Cabal import Distribution.Types.ComponentName -- from Cabal -import Distribution.Types.UnqualComponentName -- from Cabal import Distribution.Types.CondTree -- from Cabal import Distribution.Types.MungedPackageId -- from Cabal import Distribution.Types.MungedPackageName -- from Cabal @@ -162,18 +161,9 @@ convGPD os arch cinfo strfl sexes pi let fds = flagInfo strfl flags - -- | We have to be careful to filter out dependencies on - -- internal libraries, since they don't refer to real packages - -- and thus cannot actually be solved over. We'll do this - -- by creating a set of package names which are "internal" - -- and dropping them as we convert. - - ipns = S.fromList $ [ unqualComponentNameToPackageName nm - | (nm, _) <- sub_libs ] - conv :: Mon.Monoid a => Component -> (a -> BuildInfo) -> - CondTree ConfVar [Dependency] a -> FlaggedDeps Component PN - conv comp getInfo = convCondTree pkg os arch cinfo pi fds comp getInfo ipns sexes . + CondTree ConfVar [LibDependency] a -> FlaggedDeps Component PN + conv comp getInfo = convCondTree pkg os arch cinfo pi fds comp getInfo sexes . PDC.addBuildableCondition getInfo flagged_deps @@ -207,34 +197,26 @@ flagInfo (StrongFlags strfl) = weak m = WeakOrTrivial $ not (strfl || m) flagType m = if m then Manual else Automatic --- | Internal package names, which should not be interpreted as true --- dependencies. -type IPNs = Set PN - --- | Convenience function to delete a 'FlaggedDep' if it's --- for a 'PN' that isn't actually real. -filterIPNs :: IPNs -> Dependency -> FlaggedDep Component PN -> FlaggedDeps Component PN -filterIPNs ipns (Dependency pn _) fd - | S.notMember pn ipns = [fd] - | otherwise = [] - -- | Convert condition trees to flagged dependencies. Mutually -- recursive with 'convBranch'. See 'convBranch' for an explanation -- of all arguments preceeding the input 'CondTree'. convCondTree :: PackageDescription -> OS -> Arch -> CompilerInfo -> PI PN -> FlagInfo -> Component -> (a -> BuildInfo) -> - IPNs -> SolveExecutables -> - CondTree ConfVar [Dependency] a -> FlaggedDeps Component PN -convCondTree pkg os arch cinfo pi@(PI pn _) fds comp getInfo ipns sexes@(SolveExecutables sexes') (CondNode info ds branches) = - concatMap - (\d -> filterIPNs ipns d (D.Simple (convLibDep pn d) comp)) - ds -- unconditional package dependencies + CondTree ConfVar [LibDependency] a -> FlaggedDeps Component PN +convCondTree pkg os arch cinfo pi@(PI pn _) fds comp getInfo sexes@(SolveExecutables sexes') (CondNode info ds branches) = + [ D.Simple (convLibDep pn d) comp + | d <- ds -- unconditional package dependencies + -- | We have to be careful to filter out dependencies on + -- internal libraries, since they don't refer to real packages + -- and thus cannot actually be solved over. + , packageName pkg /= libDepPackageName d + ] ++ L.map (\e -> D.Simple (Ext e) comp) (PD.allExtensions bi) -- unconditional extension dependencies ++ L.map (\l -> D.Simple (Lang l) comp) (PD.allLanguages bi) -- unconditional language dependencies ++ L.map (\(PkgconfigDependency pkn vr) -> D.Simple (Pkg pkn vr) comp) (PD.pkgconfigDepends bi) -- unconditional pkg-config dependencies - ++ concatMap (convBranch pkg os arch cinfo pi fds comp getInfo ipns sexes) branches + ++ concatMap (convBranch pkg os arch cinfo pi fds comp getInfo sexes) branches -- build-tools dependencies -- NB: Only include these dependencies if SolveExecutables -- is True. It might be false in the legacy solver @@ -283,13 +265,12 @@ convBranch :: PackageDescription -> OS -> Arch -> CompilerInfo -> PI PN -> FlagInfo -> Component -> (a -> BuildInfo) -> - IPNs -> SolveExecutables -> - CondBranch ConfVar [Dependency] a -> + CondBranch ConfVar [LibDependency] a -> FlaggedDeps Component PN -convBranch pkg os arch cinfo pi@(PI pn _) fds comp getInfo ipns sexes (CondBranch c' t' mf') = - go c' ( convCondTree pkg os arch cinfo pi fds comp getInfo ipns sexes t') - (maybe [] (convCondTree pkg os arch cinfo pi fds comp getInfo ipns sexes) mf') +convBranch pkg os arch cinfo pi@(PI pn _) fds comp getInfo sexes (CondBranch c' t' mf') = + go c' ( convCondTree pkg os arch cinfo pi fds comp getInfo sexes t') + (maybe [] (convCondTree pkg os arch cinfo pi fds comp getInfo sexes) mf') where go :: Condition ConfVar -> FlaggedDeps Component PN -> FlaggedDeps Component PN -> FlaggedDeps Component PN @@ -336,9 +317,12 @@ convBranch pkg os arch cinfo pi@(PI pn _) fds comp getInfo ipns sexes (CondBranc , is_exe1 == is_exe2 ] +convDep :: PN -> Dependency -> Dep PN +convDep pn' (Dependency pn vr) = Dep False {- not exe -} pn (Constrained [(vr, P pn')]) + -- | Convert a Cabal dependency on a library to a solver-specific dependency. -convLibDep :: PN -> Dependency -> Dep PN -convLibDep pn' (Dependency pn vr) = Dep False {- not exe -} pn (Constrained [(vr, P pn')]) +convLibDep :: PN -> LibDependency -> Dep PN +convLibDep pn ldep = convDep pn $ libDependencyToDependency ldep -- | Convert a Cabal dependency on a executable (build-tools) to a solver-specific dependency. -- TODO do something about the name of the exe component itself @@ -348,4 +332,4 @@ convExeDep pn' (ExeDependency pn _ vr) = Dep True pn (Constrained [(vr, P pn')]) -- | Convert setup dependencies convSetupBuildInfo :: PI PN -> SetupBuildInfo -> FlaggedDeps Component PN convSetupBuildInfo (PI pn _i) nfo = - L.map (\d -> D.Simple (convLibDep pn d) ComponentSetup) (PD.setupDepends nfo) + L.map (\d -> D.Simple (convDep pn d) ComponentSetup) (PD.setupDepends nfo) diff --git a/cabal-install/tests/UnitTests/Distribution/Solver/Modular/DSL.hs b/cabal-install/tests/UnitTests/Distribution/Solver/Modular/DSL.hs index 8cb3e4ad1c8..af5d840ef4a 100644 --- a/cabal-install/tests/UnitTests/Distribution/Solver/Modular/DSL.hs +++ b/cabal-install/tests/UnitTests/Distribution/Solver/Modular/DSL.hs @@ -52,6 +52,7 @@ import qualified Distribution.ModuleName as Module import qualified Distribution.Package as C hiding (HasUnitId(..)) import qualified Distribution.Types.Dependency as C +import qualified Distribution.Types.LibDependency as C import qualified Distribution.Types.LegacyExeDependency as C import qualified Distribution.Types.PkgconfigDependency as C import qualified Distribution.Types.UnqualComponentName as C @@ -289,9 +290,9 @@ exInst pn v hash deps = ExInst pn v hash (map exInstHash deps) -- these packages. type ExampleDb = [Either ExampleInstalled ExampleAvailable] -type DependencyTree a = C.CondTree C.ConfVar [C.Dependency] a +type DependencyTree a = C.CondTree C.ConfVar [C.LibDependency] a -type DependencyComponent a = C.CondBranch C.ConfVar [C.Dependency] a +type DependencyComponent a = C.CondBranch C.ConfVar [C.LibDependency] a exDbPkgs :: ExampleDb -> [ExamplePkgName] exDbPkgs = map (either exInstName exAvName) @@ -489,8 +490,11 @@ exAvSrcPkg ex = , C.condTreeComponents = map mkFlagged flaggedDeps } - mkDirect :: (ExamplePkgName, C.VersionRange) -> C.Dependency - mkDirect (dep, vr) = C.Dependency (C.mkPackageName dep) vr + mkDirectSetup :: (ExamplePkgName, C.VersionRange) -> C.Dependency + mkDirectSetup (dep, vr) = C.Dependency (C.mkPackageName dep) vr + + mkDirect :: (ExamplePkgName, C.VersionRange) -> C.LibDependency + mkDirect (dep, vr) = C.LibDependency (C.mkPackageName dep) Nothing vr mkFlagged :: (ExampleFlagName, Dependencies, Dependencies) -> DependencyComponent C.BuildInfo @@ -501,7 +505,7 @@ exAvSrcPkg ex = -- Split a set of dependencies into direct dependencies and flagged -- dependencies. A direct dependency is a tuple of the name of package and - -- its version range meant to be converted to a 'C.Dependency' with + -- its version range meant to be converted to a 'C.LibDependency' with -- 'mkDirect' for example. A flagged dependency is the set of dependencies -- guarded by a flag. splitDeps :: [ExampleDependency] @@ -527,7 +531,7 @@ exAvSrcPkg ex = -- custom-setup only supports simple dependencies mkSetupDeps :: [ExampleDependency] -> [C.Dependency] mkSetupDeps deps = - let (directDeps, []) = splitDeps deps in map mkDirect directDeps + let (directDeps, []) = splitDeps deps in map mkDirectSetup directDeps mkVersion :: ExamplePkgVersion -> C.Version mkVersion n = C.mkVersion [n, 0, 0] diff --git a/cabal-testsuite/PackageTests/Backpack/Fail1/Fail1.cabal b/cabal-testsuite/PackageTests/Backpack/Fail1/Fail1.cabal index 83204e52e90..3884693faa1 100644 --- a/cabal-testsuite/PackageTests/Backpack/Fail1/Fail1.cabal +++ b/cabal-testsuite/PackageTests/Backpack/Fail1/Fail1.cabal @@ -12,6 +12,5 @@ library sig default-language: Haskell2010 library - build-depends: sig - mixins: sig requires (MissingReq as A) + mixins: Fail1:sig requires (MissingReq as A) default-language: Haskell2010 diff --git a/cabal-testsuite/PackageTests/Backpack/Includes2/Includes2.cabal b/cabal-testsuite/PackageTests/Backpack/Includes2/Includes2.cabal index 0c07c997d8d..0f8d4d107f8 100644 --- a/cabal-testsuite/PackageTests/Backpack/Includes2/Includes2.cabal +++ b/cabal-testsuite/PackageTests/Backpack/Includes2/Includes2.cabal @@ -26,10 +26,12 @@ library postgresql default-language: Haskell2010 library - build-depends: base, mysql, postgresql, mylib + build-depends: base mixins: - mylib (Mine as Mine.MySQL) requires (Database as Database.MySQL), - mylib (Mine as Mine.PostgreSQL) requires (Database as Database.PostgreSQL) + Includes2:mysql, + Includes2:postgresql, + Includes2:mylib (Mine as Mine.MySQL) requires (Database as Database.MySQL), + Includes2:mylib (Mine as Mine.PostgreSQL) requires (Database as Database.PostgreSQL) exposed-modules: App hs-source-dirs: src default-language: Haskell2010 diff --git a/cabal-testsuite/PackageTests/Backpack/Includes3/Includes3.cabal b/cabal-testsuite/PackageTests/Backpack/Includes3/Includes3.cabal index ff6493de0a2..5d723d51e59 100644 --- a/cabal-testsuite/PackageTests/Backpack/Includes3/Includes3.cabal +++ b/cabal-testsuite/PackageTests/Backpack/Includes3/Includes3.cabal @@ -13,13 +13,15 @@ library sigs default-language: Haskell2010 library indef - build-depends: base, sigs + build-depends: base + mixins: Includes3:sigs exposed-modules: Foo hs-source-dirs: indef default-language: Haskell2010 executable exe - build-depends: base, containers, indef + build-depends: base, containers + mixins: Includes3:indef main-is: Main.hs hs-source-dirs: exe default-language: Haskell2010 diff --git a/cabal-testsuite/PackageTests/Backpack/Includes4/Includes4.cabal b/cabal-testsuite/PackageTests/Backpack/Includes4/Includes4.cabal index ea7b01d4fe2..39255c794ba 100644 --- a/cabal-testsuite/PackageTests/Backpack/Includes4/Includes4.cabal +++ b/cabal-testsuite/PackageTests/Backpack/Includes4/Includes4.cabal @@ -20,6 +20,8 @@ library impl default-language: Haskell2010 executable exe - build-depends: indef, impl, base + build-depends: base + mixins: Includes4:indef, + Includes4:impl main-is: Main.hs default-language: Haskell2010 diff --git a/cabal-testsuite/PackageTests/Backpack/Includes5/Includes5.cabal b/cabal-testsuite/PackageTests/Backpack/Includes5/Includes5.cabal index a4b2530a873..c38618803f6 100644 --- a/cabal-testsuite/PackageTests/Backpack/Includes5/Includes5.cabal +++ b/cabal-testsuite/PackageTests/Backpack/Includes5/Includes5.cabal @@ -13,13 +13,14 @@ library impl default-language: Haskell2010 library good - build-depends: base, impl - mixins: impl hiding (Foobar) + build-depends: base + mixins: Includes5:impl hiding (Foobar) exposed-modules: A default-language: Haskell2010 library bad - build-depends: base, impl, good - mixins: impl hiding (Foobar) + build-depends: base + mixins: Includes5:impl hiding (Foobar), + Includes5:good exposed-modules: B default-language: Haskell2010 diff --git a/cabal-testsuite/PackageTests/Backpack/Indef2/Indef2.cabal b/cabal-testsuite/PackageTests/Backpack/Indef2/Indef2.cabal index 880230fec36..fa5ecf3e6b0 100644 --- a/cabal-testsuite/PackageTests/Backpack/Indef2/Indef2.cabal +++ b/cabal-testsuite/PackageTests/Backpack/Indef2/Indef2.cabal @@ -12,5 +12,5 @@ library asig1 default-language: Haskell2010 library - build-depends: asig1 + mixins: Indef2:asig1 default-language: Haskell2010 diff --git a/cabal-testsuite/PackageTests/BuildDeps/DepCycle/DepCycle.cabal b/cabal-testsuite/PackageTests/BuildDeps/DepCycle/DepCycle.cabal index 22ba92a4d2e..201b30572a5 100644 --- a/cabal-testsuite/PackageTests/BuildDeps/DepCycle/DepCycle.cabal +++ b/cabal-testsuite/PackageTests/BuildDeps/DepCycle/DepCycle.cabal @@ -4,9 +4,9 @@ build-type: Simple cabal-version: >= 1.10 library foo - build-depends: bar + build-depends: DepCycle:bar default-language: Haskell2010 library bar - build-depends: foo + build-depends: DepCycle:foo default-language: Haskell2010 diff --git a/cabal-testsuite/PackageTests/CaretOperator/setup.test.hs b/cabal-testsuite/PackageTests/CaretOperator/setup.test.hs index b3eee723add..35ec93de39d 100644 --- a/cabal-testsuite/PackageTests/CaretOperator/setup.test.hs +++ b/cabal-testsuite/PackageTests/CaretOperator/setup.test.hs @@ -4,7 +4,7 @@ import Control.Monad import Distribution.Version import Distribution.Simple.LocalBuildInfo import Distribution.Package -import Distribution.Types.Dependency +import Distribution.Types.LibDependency import Distribution.PackageDescription import Language.Haskell.Extension (Language(..)) @@ -22,7 +22,7 @@ main = setupTest $ do let Just gotLib = library (localPkgDescr lbi) bi = libBuildInfo gotLib assertEqual "defaultLanguage" (Just Haskell2010) (defaultLanguage bi) - forM_ (targetBuildDepends bi) $ \(Dependency pn vr) -> + forM_ (targetBuildDepends bi) $ \(LibDependency pn _ vr) -> when (pn == mkPackageName "pretty") $ assertEqual "targetBuildDepends/pretty" vr (majorBoundVersion (mkVersion [1,1,1,0])) diff --git a/cabal-testsuite/PackageTests/ConfigureComponent/SubLib/Lib.cabal b/cabal-testsuite/PackageTests/ConfigureComponent/SubLib/Lib.cabal index 85f5d879a9d..6f03ac60bb7 100644 --- a/cabal-testsuite/PackageTests/ConfigureComponent/SubLib/Lib.cabal +++ b/cabal-testsuite/PackageTests/ConfigureComponent/SubLib/Lib.cabal @@ -13,6 +13,6 @@ library sublib executable exe main-is: Exe.hs - build-depends: base, sublib + build-depends: base, Lib:sublib hs-source-dirs: exe default-language: Haskell2010 diff --git a/cabal-testsuite/PackageTests/InternalLibraries/Executable/foo.cabal b/cabal-testsuite/PackageTests/InternalLibraries/Executable/foo.cabal index 8f0e8507e28..89a61b67e1f 100644 --- a/cabal-testsuite/PackageTests/InternalLibraries/Executable/foo.cabal +++ b/cabal-testsuite/PackageTests/InternalLibraries/Executable/foo.cabal @@ -14,6 +14,6 @@ library foo-internal executable foo main-is: Main.hs - build-depends: base, foo-internal + build-depends: base, foo:foo-internal hs-source-dirs: exe default-language: Haskell2010 diff --git a/cabal-testsuite/PackageTests/InternalLibraries/Library/foolib/foolib.cabal b/cabal-testsuite/PackageTests/InternalLibraries/Library/foolib/foolib.cabal index 0a5d05397c4..99f0e4939e6 100644 --- a/cabal-testsuite/PackageTests/InternalLibraries/Library/foolib/foolib.cabal +++ b/cabal-testsuite/PackageTests/InternalLibraries/Library/foolib/foolib.cabal @@ -13,5 +13,5 @@ library foolib-internal library exposed-modules: Foo - build-depends: base, foolib-internal + build-depends: base, foolib:foolib-internal default-language: Haskell2010 diff --git a/cabal-testsuite/PackageTests/InternalLibraries/p/p.cabal b/cabal-testsuite/PackageTests/InternalLibraries/p/p.cabal index 30546bfb507..bce5ae8b1e0 100644 --- a/cabal-testsuite/PackageTests/InternalLibraries/p/p.cabal +++ b/cabal-testsuite/PackageTests/InternalLibraries/p/p.cabal @@ -13,12 +13,12 @@ library q default-language: Haskell2010 library - build-depends: base, q + build-depends: base, p:q exposed-modules: P hs-source-dirs: p default-language: Haskell2010 executable foo - build-depends: base, q + build-depends: base, p, p:q main-is: Foo.hs default-language: Haskell2010