diff --git a/Cabal/Distribution/Backpack/ComponentsGraph.hs b/Cabal/Distribution/Backpack/ComponentsGraph.hs index bcd30fe0729..e29d5bebf05 100644 --- a/Cabal/Distribution/Backpack/ComponentsGraph.hs +++ b/Cabal/Distribution/Backpack/ComponentsGraph.hs @@ -68,7 +68,7 @@ mkComponentsGraph enabled pkg_descr = ++ [ if pkgname == packageName pkg_descr then CLibName LMainLibName else CLibName (LSubLibName toolname) - | Dependency pkgname _ <- targetBuildDepends bi + | Dependency pkgname _ _ <- targetBuildDepends bi , let toolname = packageNameToUnqualComponentName pkgname , toolname `elem` internalPkgDeps ] where diff --git a/Cabal/Distribution/Backpack/ConfiguredComponent.hs b/Cabal/Distribution/Backpack/ConfiguredComponent.hs index 1bfd84965ad..9a642425fec 100644 --- a/Cabal/Distribution/Backpack/ConfiguredComponent.hs +++ b/Cabal/Distribution/Backpack/ConfiguredComponent.hs @@ -30,6 +30,7 @@ import Distribution.Types.PackageId import Distribution.Types.PackageName import Distribution.Types.Mixin import Distribution.Types.ComponentName +import Distribution.Types.LibraryName import Distribution.Types.UnqualComponentName import Distribution.Types.ComponentInclude import Distribution.Package @@ -165,16 +166,40 @@ toConfiguredComponent toConfiguredComponent pkg_descr this_cid lib_dep_map exe_dep_map component = do lib_deps <- if newPackageDepsBehaviour pkg_descr - then forM (targetBuildDepends bi) $ \(Dependency name _) -> do + then fmap concat $ forM (targetBuildDepends bi) $ \(Dependency name _ sublibs) -> do let (pn, cn) = fixFakePkgName pkg_descr name - value <- case Map.lookup cn =<< Map.lookup pn lib_dep_map of + pkg <- case Map.lookup pn lib_dep_map of + Nothing -> + dieProgress $ + text "Dependency on unbuildable" <+> + text "package" <+> disp pn + Just p -> return p + mainLibraryComponent <- + if sublibs /= Set.singleton LMainLibName + then pure Nothing + -- No sublibraries were specified, so we may be in the + -- legacy case where the package name is used as library + -- name + else Just <$> + case Map.lookup cn pkg of Nothing -> dieProgress $ text "Dependency on unbuildable (i.e. 'buildable: False')" <+> text (showComponentName cn) <+> text "from" <+> disp pn Just v -> return v - return value + subLibrariesComponents <- forM (Set.toList sublibs) $ \lib -> + let comp = CLibName lib in + case Map.lookup (CLibName $ LSubLibName $ packageNameToUnqualComponentName name) pkg + <|> Map.lookup comp pkg + of + Nothing -> + dieProgress $ + text "Dependency on unbuildable" <+> + text (showLibraryName lib) <+> + text "from" <+> disp pn + Just v -> return v + return (maybeToList mainLibraryComponent ++ subLibrariesComponents) else return old_style_lib_deps mkConfiguredComponent pkg_descr this_cid diff --git a/Cabal/Distribution/PackageDescription/Check.hs b/Cabal/Distribution/PackageDescription/Check.hs index 115844781db..3205df036da 100644 --- a/Cabal/Distribution/PackageDescription/Check.hs +++ b/Cabal/Distribution/PackageDescription/Check.hs @@ -585,7 +585,7 @@ checkFields pkg = , name `elem` map display knownLanguages ] testedWithImpossibleRanges = - [ Dependency (mkPackageName (display compiler)) vr + [ Dependency (mkPackageName (display compiler)) vr Set.empty | (compiler, vr) <- testedWith pkg , isNoVersion vr ] @@ -598,7 +598,7 @@ checkFields pkg = internalLibDeps = [ dep | bi <- allBuildInfo pkg - , dep@(Dependency name _) <- targetBuildDepends bi + , dep@(Dependency name _ _) <- targetBuildDepends bi , name `elem` internalLibraries ] @@ -611,14 +611,14 @@ checkFields pkg = depInternalLibraryWithExtraVersion = [ dep - | dep@(Dependency _ versionRange) <- internalLibDeps + | dep@(Dependency _ versionRange _) <- internalLibDeps , not $ isAnyVersion versionRange , packageVersion pkg `withinRange` versionRange ] depInternalLibraryWithImpossibleVersion = [ dep - | dep@(Dependency _ versionRange) <- internalLibDeps + | dep@(Dependency _ versionRange _) <- internalLibDeps , not $ packageVersion pkg `withinRange` versionRange ] @@ -1243,8 +1243,8 @@ checkCabalVersion pkg = ++ ". To use this new syntax the package need to specify at least " ++ "'cabal-version: >= 1.6'. Alternatively, if broader compatibility " ++ "is important then use: " ++ commaSep - [ display (Dependency name (eliminateWildcardSyntax versionRange)) - | Dependency name versionRange <- depsUsingWildcardSyntax ] + [ display (Dependency name (eliminateWildcardSyntax versionRange) Set.empty) + | Dependency name versionRange _ <- depsUsingWildcardSyntax ] -- check use of "build-depends: foo ^>= 1.2.3" syntax , checkVersion [2,0] (not (null depsUsingMajorBoundSyntax)) $ @@ -1255,8 +1255,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 (Dependency name (eliminateMajorBoundSyntax versionRange) Set.empty) + | Dependency name versionRange _ <- depsUsingMajorBoundSyntax ] , checkVersion [2,1] (any (not . null) (concatMap buildInfoField @@ -1292,8 +1292,8 @@ checkCabalVersion pkg = ++ ". To use this new syntax the package need to specify at least " ++ "'cabal-version: >= 1.6'. Alternatively, if broader compatibility " ++ "is important then use: " ++ commaSep - [ display (Dependency name (eliminateWildcardSyntax versionRange)) - | Dependency name versionRange <- testedWithUsingWildcardSyntax ] + [ display (Dependency name (eliminateWildcardSyntax versionRange) Set.empty) + | Dependency name versionRange _ <- testedWithUsingWildcardSyntax ] -- check use of "source-repository" section , checkVersion [1,6] (not (null (sourceRepos pkg))) $ @@ -1367,11 +1367,11 @@ checkCabalVersion pkg = buildInfoField field = map field (allBuildInfo pkg) versionRangeExpressions = - [ dep | dep@(Dependency _ vr) <- allBuildDepends pkg + [ dep | dep@(Dependency _ vr _) <- allBuildDepends pkg , usesNewVersionRangeSyntax vr ] testedWithVersionRangeExpressions = - [ Dependency (mkPackageName (display compiler)) vr + [ Dependency (mkPackageName (display compiler)) vr Set.empty | (compiler, vr) <- testedWith pkg , usesNewVersionRangeSyntax vr ] @@ -1395,16 +1395,16 @@ checkCabalVersion pkg = alg (VersionRangeParensF _) = 3 alg _ = 1 :: Int - depsUsingWildcardSyntax = [ dep | dep@(Dependency _ vr) <- allBuildDepends pkg + depsUsingWildcardSyntax = [ dep | dep@(Dependency _ vr _) <- allBuildDepends pkg , usesWildcardSyntax vr ] - depsUsingMajorBoundSyntax = [ dep | dep@(Dependency _ vr) <- allBuildDepends pkg + depsUsingMajorBoundSyntax = [ dep | dep@(Dependency _ vr _) <- allBuildDepends pkg , usesMajorBoundSyntax vr ] usesBackpackIncludes = any (not . null . mixins) (allBuildInfo pkg) testedWithUsingWildcardSyntax = - [ Dependency (mkPackageName (display compiler)) vr + [ Dependency (mkPackageName (display compiler)) vr Set.empty | (compiler, vr) <- testedWith pkg , usesWildcardSyntax vr ] @@ -1493,7 +1493,7 @@ checkCabalVersion pkg = allModuleNamesAutogen = concatMap autogenModules (allBuildInfo pkg) displayRawDependency :: Dependency -> String -displayRawDependency (Dependency pkg vr) = +displayRawDependency (Dependency pkg vr _sublibs) = display pkg ++ " " ++ display vr @@ -1545,7 +1545,7 @@ checkPackageVersions pkg = foldr intersectVersionRanges anyVersion baseDeps where baseDeps = - [ vr | Dependency pname vr <- allBuildDepends pkg' + [ vr | Dependency 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 59c8cb1cc43..daf5ee79269 100644 --- a/Cabal/Distribution/PackageDescription/Configuration.hs +++ b/Cabal/Distribution/PackageDescription/Configuration.hs @@ -65,6 +65,8 @@ import Distribution.Types.DependencyMap import qualified Data.Map.Strict as Map.Strict import qualified Data.Map.Lazy as Map +import Data.Set ( Set ) +import qualified Data.Set as Set import Data.Tree ( Tree(Node) ) ------------------------------------------------------------------------------ @@ -229,7 +231,7 @@ resolveWithFlags dom enabled os arch impl constrs trees checkDeps = mp (Left xs) (Left ys) = let union = Map.foldrWithKey (Map.Strict.insertWith combine) (unDepMapUnion xs) (unDepMapUnion ys) - combine x y = simplifyVersionRange $ unionVersionRanges x y + combine x y = (\(vr, cs) -> (simplifyVersionRange vr,cs)) $ unionVersionRanges' x y in union `seq` Left (DepMapUnion union) -- `mzero' @@ -307,14 +309,22 @@ extractConditions f gpkg = -- | A map of dependencies that combines version ranges using 'unionVersionRanges'. -newtype DepMapUnion = DepMapUnion { unDepMapUnion :: Map PackageName VersionRange } +newtype DepMapUnion = DepMapUnion { unDepMapUnion :: Map PackageName (VersionRange, Set LibraryName) } + +-- An union of versions should correspond to an intersection of the components. +-- The intersection may not be necessary. +unionVersionRanges' :: (VersionRange, Set LibraryName) + -> (VersionRange, Set LibraryName) + -> (VersionRange, Set LibraryName) +unionVersionRanges' (vra, csa) (vrb, csb) = + (unionVersionRanges vra vrb, Set.intersection csa csb) toDepMapUnion :: [Dependency] -> DepMapUnion toDepMapUnion ds = - DepMapUnion $ Map.fromListWith unionVersionRanges [ (p,vr) | Dependency p vr <- ds ] + DepMapUnion $ Map.fromListWith unionVersionRanges' [ (p,(vr,cs)) | Dependency p vr cs <- ds ] fromDepMapUnion :: DepMapUnion -> [Dependency] -fromDepMapUnion m = [ Dependency p vr | (p,vr) <- Map.toList (unDepMapUnion m) ] +fromDepMapUnion m = [ Dependency p vr cs | (p,(vr,cs)) <- Map.toList (unDepMapUnion m) ] freeVars :: CondTree ConfVar c a -> [FlagName] freeVars t = [ f | Flag f <- freeVars' t ] diff --git a/Cabal/Distribution/Simple/Configure.hs b/Cabal/Distribution/Simple/Configure.hs index 80699950804..74790c4007c 100644 --- a/Cabal/Distribution/Simple/Configure.hs +++ b/Cabal/Distribution/Simple/Configure.hs @@ -143,6 +143,8 @@ import Text.PrettyPrint import Distribution.Compat.Environment ( lookupEnv ) import Distribution.Compat.Exception ( catchExit, catchIO ) +import qualified Data.Set as Set + type UseExternalInternalDeps = Bool @@ -874,7 +876,7 @@ dependencySatisfiable dependencySatisfiable use_external_internal_deps exact_config pn installedPackageSet internalPackageSet requiredDepsMap - d@(Dependency depName vr) + (Dependency depName vr sublibs) | exact_config -- When we're given '--exact-configuration', we assume that all @@ -889,7 +891,19 @@ dependencySatisfiable -- Except for internal deps, when we're NOT per-component mode; -- those are just True. then True - else (depName, CLibName LMainLibName) `Map.member` requiredDepsMap + else + -- Backward compatibility for the old sublibrary syntax + (sublibs == Set.singleton LMainLibName + && Map.member + (pn, CLibName $ LSubLibName $ packageNameToUnqualComponentName depName) + requiredDepsMap) + + || all + (\lib -> + (depName, CLibName lib) + `Map.member` + requiredDepsMap) + sublibs | isInternalDep = if use_external_internal_deps @@ -908,11 +922,11 @@ dependencySatisfiable isInternalDep = Map.member depName internalPackageSet depSatisfiable = - not . null $ PackageIndex.lookupDependency installedPackageSet d + not . null $ PackageIndex.lookupDependency installedPackageSet depName vr internalDepSatisfiable = not . null $ PackageIndex.lookupInternalDependency - installedPackageSet (Dependency pn vr) cn + installedPackageSet pn vr cn where cn | pn == depName = Nothing @@ -1025,8 +1039,8 @@ configureDependencies verbosity use_external_internal_deps internalPackageSet installedPackageSet requiredDepsMap pkg_descr enableSpec = do let failedDeps :: [FailedDependency] allPkgDeps :: [ResolvedDependency] - (failedDeps, allPkgDeps) = partitionEithers - [ (\s -> (dep, s)) <$> status + (failedDeps, allPkgDeps) = partitionEithers $ concat + [ fmap (\s -> (dep, s)) <$> status | dep <- enabledBuildDepends pkg_descr enableSpec , let status = selectDependency (package pkg_descr) internalPackageSet installedPackageSet @@ -1197,10 +1211,10 @@ selectDependency :: PackageId -- ^ Package id of current package -> UseExternalInternalDeps -- ^ Are we configuring a -- single component? -> Dependency - -> Either FailedDependency DependencyResolution + -> [Either FailedDependency DependencyResolution] selectDependency pkgid internalIndex installedIndex requiredDepsMap use_external_internal_deps - dep@(Dependency dep_pkgname vr) = + (Dependency dep_pkgname vr libs) = -- If the dependency specification matches anything in the internal package -- index, then we prefer that match to anything in the second. -- For example: @@ -1216,18 +1230,19 @@ selectDependency pkgid internalIndex installedIndex requiredDepsMap -- 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) + then do_external (Just cname) <$> Set.toList libs else do_internal - _ -> do_external Nothing + _ -> do_external Nothing <$> Set.toList libs where -- It's an internal library, and we're not per-component build - do_internal = Right $ InternalDependency - $ PackageIdentifier dep_pkgname $ packageVersion pkgid + 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, CLibName LMainLibName) requiredDepsMap of + do_external :: Maybe (Maybe UnqualComponentName) -> LibraryName -> Either FailedDependency DependencyResolution + do_external is_internal lib = do + ipi <- case Map.lookup (dep_pkgname, CLibName lib) 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. @@ -1239,14 +1254,14 @@ selectDependency pkgid internalIndex installedIndex requiredDepsMap -- It's an external package, normal situation do_external_external = - case PackageIndex.lookupDependency installedIndex dep of + case PackageIndex.lookupDependency installedIndex dep_pkgname vr 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 + (packageName pkgid) vr mb_uqn of [] -> Left (DependencyMissingInternal dep_pkgname (packageName pkgid)) pkgs -> Right $ head $ snd $ last pkgs diff --git a/Cabal/Distribution/Simple/PackageIndex.hs b/Cabal/Distribution/Simple/PackageIndex.hs index 1d4e5abb8a7..94ee979bc01 100644 --- a/Cabal/Distribution/Simple/PackageIndex.hs +++ b/Cabal/Distribution/Simple/PackageIndex.hs @@ -469,11 +469,11 @@ lookupPackageName index name = -- -- INVARIANT: List of eligible 'IPI.InstalledPackageInfo' is non-empty. -- -lookupDependency :: InstalledPackageIndex -> Dependency +lookupDependency :: InstalledPackageIndex -> PackageName -> VersionRange -> [(Version, [IPI.InstalledPackageInfo])] -lookupDependency index dep = +lookupDependency index pn vr = -- Yes, a little bit of a misnomer here! - lookupInternalDependency index dep Nothing + lookupInternalDependency index pn vr Nothing -- | Does a lookup by source package name and a range of versions. -- @@ -482,10 +482,10 @@ lookupDependency index dep = -- -- INVARIANT: List of eligible 'IPI.InstalledPackageInfo' is non-empty. -- -lookupInternalDependency :: InstalledPackageIndex -> Dependency +lookupInternalDependency :: InstalledPackageIndex -> PackageName -> VersionRange -> Maybe UnqualComponentName -> [(Version, [IPI.InstalledPackageInfo])] -lookupInternalDependency index (Dependency name versionRange) libn = +lookupInternalDependency index name versionRange libn = case Map.lookup (name, libn) (packageIdIndex index) of Nothing -> [] Just pvers -> [ (ver, pkgs') diff --git a/Cabal/Distribution/Types/Dependency.hs b/Cabal/Distribution/Types/Dependency.hs index ce05392ce73..b721d55ce41 100644 --- a/Cabal/Distribution/Types/Dependency.hs +++ b/Cabal/Distribution/Types/Dependency.hs @@ -4,6 +4,7 @@ module Distribution.Types.Dependency ( Dependency(..) , depPkgName , depVerRange + , depLibraries , thisPackageVersion , notThisPackageVersion , simplifyDependency @@ -20,53 +21,95 @@ import qualified Distribution.Compat.ReadP as Parse import Distribution.Text import Distribution.Pretty +import qualified Text.PrettyPrint as PP import Distribution.Parsec.Class +import Distribution.Compat.CharParsing (char, spaces) +import Distribution.Compat.Parsing (between, option) import Distribution.Types.PackageId import Distribution.Types.PackageName +import Distribution.Types.LibraryName +import Distribution.Types.UnqualComponentName import Text.PrettyPrint ((<+>)) +import Data.Set (Set) +import qualified Data.Set as Set -- | Describes a dependency on a source package (API) -- -data Dependency = Dependency PackageName VersionRange +data Dependency = Dependency + PackageName + VersionRange + (Set LibraryName) + -- ^ The set of libraries required from the package. + -- Only the selected libraries will be built. + -- It does not affect the cabal-install solver yet. deriving (Generic, Read, Show, Eq, Typeable, Data) depPkgName :: Dependency -> PackageName -depPkgName (Dependency pn _) = pn +depPkgName (Dependency pn _ _) = pn depVerRange :: Dependency -> VersionRange -depVerRange (Dependency _ vr) = vr +depVerRange (Dependency _ vr _) = vr + +depLibraries :: Dependency -> Set LibraryName +depLibraries (Dependency _ _ cs) = cs instance Binary Dependency instance NFData Dependency where rnf = genericRnf instance Pretty Dependency where - pretty (Dependency name ver) = pretty name <+> pretty ver + pretty (Dependency name ver sublibs) = pretty name + <+> optionalMonoid + (sublibs /= Set.singleton LMainLibName) + (PP.colon <+> PP.braces prettySublibs) + <+> pretty ver + where + optionalMonoid True x = x + optionalMonoid False _ = mempty + prettySublibs = PP.hsep $ PP.punctuate PP.comma $ prettySublib <$> Set.toList sublibs + prettySublib LMainLibName = PP.text $ unPackageName name + prettySublib (LSubLibName un) = PP.text $ unUnqualComponentName un instance Parsec Dependency where parsec = do name <- lexemeParsec + libs <- option [LMainLibName] + $ (char ':' *> spaces *>) + $ between (char '{' *> spaces) (spaces <* char '}') + $ parsecCommaList (makeLib name <$> parsecUnqualComponentName) ver <- parsec <|> pure anyVersion - return (Dependency name ver) + return $ Dependency name ver $ Set.fromList libs + where makeLib pn ln | unPackageName pn == ln = LMainLibName + | otherwise = LSubLibName $ mkUnqualComponentName ln instance Text Dependency where parse = do name <- parse Parse.skipSpaces + libs <- option [LMainLibName] + $ (char ':' *>) + $ between (char '{') (char '}') + $ parsecCommaList (makeLib name <$> parsecUnqualComponentName) + Parse.skipSpaces ver <- parse Parse.<++ return anyVersion Parse.skipSpaces - return (Dependency name ver) + return $ Dependency name ver $ Set.fromList libs + where makeLib pn ln | unPackageName pn == ln = LMainLibName + | otherwise = LSubLibName $ mkUnqualComponentName ln +-- mempty should never be in a Dependency-as-dependency. +-- This is only here until the Dependency-as-constraint problem is solved #5570. +-- Same for below. thisPackageVersion :: PackageIdentifier -> Dependency thisPackageVersion (PackageIdentifier n v) = - Dependency n (thisVersion v) + Dependency n (thisVersion v) Set.empty notThisPackageVersion :: PackageIdentifier -> Dependency notThisPackageVersion (PackageIdentifier n v) = - Dependency n (notThisVersion v) + Dependency n (notThisVersion v) Set.empty -- | Simplify the 'VersionRange' expression in a 'Dependency'. -- See 'simplifyVersionRange'. -- simplifyDependency :: Dependency -> Dependency -simplifyDependency (Dependency name range) = - Dependency name (simplifyVersionRange range) +simplifyDependency (Dependency name range comps) = + Dependency name (simplifyVersionRange range) comps diff --git a/Cabal/Distribution/Types/DependencyMap.hs b/Cabal/Distribution/Types/DependencyMap.hs index fbd2cc2b10b..0bc0e06025a 100644 --- a/Cabal/Distribution/Types/DependencyMap.hs +++ b/Cabal/Distribution/Types/DependencyMap.hs @@ -10,13 +10,15 @@ import Distribution.Compat.Prelude import Distribution.Types.Dependency import Distribution.Types.PackageName +import Distribution.Types.LibraryName import Distribution.Version +import Data.Set (Set) import qualified Data.Map.Lazy as Map -- | A map of dependencies. Newtyped since the default monoid instance is not -- appropriate. The monoid instance uses 'intersectVersionRanges'. -newtype DependencyMap = DependencyMap { unDependencyMap :: Map PackageName VersionRange } +newtype DependencyMap = DependencyMap { unDependencyMap :: Map PackageName (VersionRange, Set LibraryName) } deriving (Show, Read) instance Monoid DependencyMap where @@ -25,14 +27,20 @@ instance Monoid DependencyMap where instance Semigroup DependencyMap where (DependencyMap a) <> (DependencyMap b) = - DependencyMap (Map.unionWith intersectVersionRanges a b) + DependencyMap (Map.unionWith intersectVersionRangesAndJoinComponents a b) + +intersectVersionRangesAndJoinComponents :: (VersionRange, Set LibraryName) + -> (VersionRange, Set LibraryName) + -> (VersionRange, Set LibraryName) +intersectVersionRangesAndJoinComponents (va, ca) (vb, cb) = + (intersectVersionRanges va vb, ca <> cb) toDepMap :: [Dependency] -> DependencyMap toDepMap ds = - DependencyMap $ Map.fromListWith intersectVersionRanges [ (p,vr) | Dependency p vr <- ds ] + DependencyMap $ Map.fromListWith intersectVersionRangesAndJoinComponents [ (p,(vr,cs)) | Dependency p vr cs <- ds ] fromDepMap :: DependencyMap -> [Dependency] -fromDepMap m = [ Dependency p vr | (p,vr) <- Map.toList (unDependencyMap m) ] +fromDepMap m = [ Dependency p vr cs | (p,(vr,cs)) <- Map.toList (unDependencyMap m) ] -- Apply extra constraints to a dependency map. -- Combines dependencies where the result will only contain keys from the left @@ -48,4 +56,4 @@ constrainBy left extra = where tightenConstraint n c l = case Map.lookup n l of Nothing -> l - Just vr -> Map.insert n (intersectVersionRanges vr c) l + Just vrcs -> Map.insert n (intersectVersionRangesAndJoinComponents vrcs c) l diff --git a/Cabal/Distribution/Types/LibraryName.hs b/Cabal/Distribution/Types/LibraryName.hs index 63a1d849712..15d7c2bcb5e 100644 --- a/Cabal/Distribution/Types/LibraryName.hs +++ b/Cabal/Distribution/Types/LibraryName.hs @@ -23,9 +23,10 @@ import Text.PrettyPrint as Disp data LibraryName = LMainLibName | LSubLibName UnqualComponentName - deriving (Eq, Generic, Ord, Read, Show, Typeable) + deriving (Eq, Generic, Ord, Read, Show, Typeable, Data) instance Binary LibraryName +instance NFData LibraryName where rnf = genericRnf -- Build-target-ish syntax instance Pretty LibraryName where diff --git a/Cabal/tests/Instances/TreeDiff.hs b/Cabal/tests/Instances/TreeDiff.hs index 9044fdc855a..6d386ca2054 100644 --- a/Cabal/tests/Instances/TreeDiff.hs +++ b/Cabal/tests/Instances/TreeDiff.hs @@ -70,6 +70,7 @@ instance ToExpr InstalledPackageInfo instance ToExpr LegacyExeDependency where toExpr = defaultExprViaShow instance ToExpr LibVersionInfo where toExpr = defaultExprViaShow instance ToExpr Library +instance ToExpr LibraryName instance ToExpr Mixin where toExpr = defaultExprViaShow instance ToExpr ModuleName where toExpr = defaultExprViaShow instance ToExpr ModuleReexport diff --git a/cabal-install/Distribution/Client/CmdRepl.hs b/cabal-install/Distribution/Client/CmdRepl.hs index 662b7118991..ce603e2a7b7 100644 --- a/cabal-install/Distribution/Client/CmdRepl.hs +++ b/cabal-install/Distribution/Client/CmdRepl.hs @@ -72,6 +72,8 @@ import Distribution.Types.Dependency ( Dependency(..) ) import Distribution.Types.GenericPackageDescription ( emptyGenericPackageDescription ) +import Distribution.Types.LibraryName + ( LibraryName(..) ) import Distribution.Types.PackageDescription ( PackageDescription(..), emptyPackageDescription ) import Distribution.Types.Library @@ -370,7 +372,7 @@ withoutProject config verbosity extraArgs = do { targetBuildDepends = [baseDep] , defaultLanguage = Just Haskell2010 } - baseDep = Dependency "base" anyVersion + baseDep = Dependency "base" anyVersion (Set.singleton LMainLibName) pkgId = PackageIdentifier "fake-package" version0 writeGenericPackageDescription (tempDir "fake-package.cabal") genericPackageDescription diff --git a/cabal-install/Distribution/Client/Configure.hs b/cabal-install/Distribution/Client/Configure.hs index 7bc870b1fef..3ad58fefc81 100644 --- a/cabal-install/Distribution/Client/Configure.hs +++ b/cabal-install/Distribution/Client/Configure.hs @@ -278,7 +278,7 @@ checkConfigExFlags verbosity installedPkgIndex sourcePkgIndex flags = do where unknownConstraints = filter (unknown . userConstraintPackageName . fst) $ configExConstraints flags - unknownPreferences = filter (unknown . \(Dependency name _) -> name) $ + unknownPreferences = filter (unknown . \(Dependency name _ _) -> name) $ configPreferences flags unknown pkg = null (lookupPackageName installedPkgIndex pkg) && not (elemByPackageName sourcePkgIndex pkg) @@ -325,7 +325,7 @@ planLocalPackage verbosity comp platform configFlags configExFlags . addPreferences -- preferences from the config file or command line [ PackageVersionPreference name ver - | Dependency name ver <- configPreferences configExFlags ] + | Dependency name ver _ <- configPreferences configExFlags ] . addConstraints -- version constraints from the config file or command line diff --git a/cabal-install/Distribution/Client/Dependency.hs b/cabal-install/Distribution/Client/Dependency.hs index 1b04111ad84..ab5c314d0dd 100644 --- a/cabal-install/Distribution/Client/Dependency.hs +++ b/cabal-install/Distribution/Client/Dependency.hs @@ -472,8 +472,8 @@ relaxPackageDeps _ rd gpd | not (isRelaxDeps rd) = gpd -- subsumed by no-op case relaxPackageDeps relKind RelaxDepsAll gpd = PD.transformAllBuildDepends relaxAll gpd where relaxAll :: Dependency -> Dependency - relaxAll (Dependency pkgName verRange) = - Dependency pkgName (removeBound relKind RelaxDepModNone verRange) + relaxAll (Dependency pkgName verRange cs) = + Dependency pkgName (removeBound relKind RelaxDepModNone verRange) cs relaxPackageDeps relKind (RelaxDepsSome depsToRelax0) gpd = PD.transformAllBuildDepends relaxSome gpd @@ -493,13 +493,13 @@ relaxPackageDeps relKind (RelaxDepsSome depsToRelax0) gpd = | otherwise -> Nothing relaxSome :: Dependency -> Dependency - relaxSome d@(Dependency depName verRange) + relaxSome d@(Dependency depName verRange cs) | Just relMod <- Map.lookup RelaxDepSubjectAll depsToRelax = -- a '*'-subject acts absorbing, for consistency with -- the 'Semigroup RelaxDeps' instance - Dependency depName (removeBound relKind relMod verRange) + Dependency depName (removeBound relKind relMod verRange) cs | Just relMod <- Map.lookup (RelaxDepSubjectPkg depName) depsToRelax = - Dependency depName (removeBound relKind relMod verRange) + Dependency depName (removeBound relKind relMod verRange) cs | otherwise = d -- no-op -- | Internal helper for 'relaxPackageDeps' @@ -645,7 +645,7 @@ standardInstallPolicy installedPkgIndex sourcePkgDb pkgSpecifiers mkDefaultSetupDeps :: UnresolvedSourcePackage -> Maybe [Dependency] mkDefaultSetupDeps srcpkg | affected = Just [Dependency (mkPackageName "Cabal") - (orLaterVersion $ mkVersion [1,24])] + (orLaterVersion $ mkVersion [1,24]) (Set.singleton PD.LMainLibName)] | otherwise = Nothing where gpkgdesc = packageDescription srcpkg @@ -943,10 +943,10 @@ configuredPackageProblems platform cinfo packageSatisfiesDependency (PackageIdentifier name version) - (Dependency name' versionRange) = assert (name == name') $ + (Dependency name' versionRange _) = assert (name == name') $ version `withinRange` versionRange - dependencyName (Dependency name _) = name + dependencyName (Dependency name _ _) = name mergedDeps :: [MergeResult Dependency PackageId] mergedDeps = mergeDeps requiredDeps (CD.flatDeps specifiedDeps) @@ -1018,9 +1018,9 @@ resolveWithoutDependencies (DepResolverParams targets constraints where -- Constraints requiredVersions = packageConstraints pkgname - pkgDependency = Dependency pkgname requiredVersions choices = PackageIndex.lookupDependency sourcePkgIndex - pkgDependency + pkgname + requiredVersions -- Preferences PackagePreferences preferredVersions preferInstalled _ diff --git a/cabal-install/Distribution/Client/GenBounds.hs b/cabal-install/Distribution/Client/GenBounds.hs index 0f2727ad2fc..95b4bdb0daf 100644 --- a/cabal-install/Distribution/Client/GenBounds.hs +++ b/cabal-install/Distribution/Client/GenBounds.hs @@ -144,10 +144,10 @@ genBounds verbosity packageDBs repoCtxt comp platform progdb mSandboxPkgInfo traverse_ (putStrLn . (++",") . showBounds padTo) thePkgs depName :: Dependency -> String - depName (Dependency pn _) = unPackageName pn + depName (Dependency pn _ _) = unPackageName pn depVersion :: Dependency -> VersionRange - depVersion (Dependency _ vr) = vr + depVersion (Dependency _ vr _) = vr -- | The message printed when some dependencies are found to be lacking proper -- PVP-mandated bounds. diff --git a/cabal-install/Distribution/Client/IndexUtils.hs b/cabal-install/Distribution/Client/IndexUtils.hs index ffa2b4b0539..cebf5fc5869 100644 --- a/cabal-install/Distribution/Client/IndexUtils.hs +++ b/cabal-install/Distribution/Client/IndexUtils.hs @@ -275,7 +275,7 @@ getSourcePackagesAtIndexState verbosity repoCtxt mb_idxState = do let (pkgs, prefs) = mconcat pkgss prefs' = Map.fromListWith intersectVersionRanges - [ (name, range) | Dependency name range <- prefs ] + [ (name, range) | Dependency name range _ <- prefs ] _ <- evaluate pkgs _ <- evaluate prefs' return SourcePackageDb { @@ -703,7 +703,7 @@ packageListFromCache verbosity mkPkg hnd Cache{..} = accum mempty [] mempty cach let srcpkg = mkPkg (BuildTreeRef refType (packageId pkg) pkg path blockno) accum srcpkgs (srcpkg:btrs) prefs entries - accum srcpkgs btrs prefs (CachePreference pref@(Dependency pn _) _ _ : entries) = + accum srcpkgs btrs prefs (CachePreference pref@(Dependency pn _ _) _ _ : entries) = accum srcpkgs btrs (Map.insert pn pref prefs) entries getEntryContent :: BlockNo -> IO ByteString diff --git a/cabal-install/Distribution/Client/Init.hs b/cabal-install/Distribution/Client/Init.hs index cd7ea083add..8fb45a18046 100644 --- a/cabal-install/Distribution/Client/Init.hs +++ b/cabal-install/Distribution/Client/Init.hs @@ -39,6 +39,7 @@ import Data.List import Data.Function ( on ) import qualified Data.Map as M +import qualified Data.Set as Set import Control.Monad ( (>=>), join, forM_, mapM, mapM_ ) import Control.Arrow @@ -56,6 +57,8 @@ import Distribution.ModuleName import Distribution.InstalledPackageInfo ( InstalledPackageInfo, exposed ) import qualified Distribution.Package as P +import Distribution.Types.LibraryName + ( LibraryName(..) ) import Language.Haskell.Extension ( Language(..) ) import Distribution.Client.Init.Types @@ -527,13 +530,14 @@ chooseDep flags (m, Just ps) toDep :: [P.PackageIdentifier] -> IO P.Dependency -- If only one version, easy. We change e.g. 0.4.2 into 0.4.* - toDep [pid] = return $ P.Dependency (P.pkgName pid) (pvpize desugar . P.pkgVersion $ pid) + toDep [pid] = return $ P.Dependency (P.pkgName pid) (pvpize desugar . P.pkgVersion $ pid) (Set.singleton LMainLibName) --TODO sublibraries -- Otherwise, choose the latest version and issue a warning. toDep pids = do message flags ("\nWarning: multiple versions of " ++ display (P.pkgName . head $ pids) ++ " provide " ++ display m ++ ", choosing the latest.") return $ P.Dependency (P.pkgName . head $ pids) (pvpize desugar . maximum . map P.pkgVersion $ pids) + (Set.singleton LMainLibName) --TODO take into account sublibraries -- | Given a version, return an API-compatible (according to PVP) version range. -- diff --git a/cabal-install/Distribution/Client/Install.hs b/cabal-install/Distribution/Client/Install.hs index 77bb0328f02..b4326b09824 100644 --- a/cabal-install/Distribution/Client/Install.hs +++ b/cabal-install/Distribution/Client/Install.hs @@ -407,7 +407,7 @@ planPackages verbosity comp platform mSandboxPkgInfo solver . addPreferences -- preferences from the config file or command line [ PackageVersionPreference name ver - | Dependency name ver <- configPreferences configExFlags ] + | Dependency name ver _ <- configPreferences configExFlags ] . addConstraints -- version constraints from the config file or command line diff --git a/cabal-install/Distribution/Client/List.hs b/cabal-install/Distribution/Client/List.hs index 5a72ce7a709..cc465ff9bf5 100644 --- a/cabal-install/Distribution/Client/List.hs +++ b/cabal-install/Distribution/Client/List.hs @@ -231,9 +231,9 @@ info verbosity packageDBs repoCtxt comp progdb selectedInstalledPkgs = InstalledPackageIndex.lookupDependency installedPkgIndex - (Dependency name verConstraint) + name verConstraint selectedSourcePkgs = PackageIndex.lookupDependency sourcePkgIndex - (Dependency name verConstraint) + name verConstraint selectedSourcePkg' = latestWithPref pref selectedSourcePkgs -- display a specific package version if the user diff --git a/cabal-install/Distribution/Client/Outdated.hs b/cabal-install/Distribution/Client/Outdated.hs index 017aae42123..7a9b7d53c92 100644 --- a/cabal-install/Distribution/Client/Outdated.hs +++ b/cabal-install/Distribution/Client/Outdated.hs @@ -43,7 +43,7 @@ import Distribution.Types.Dependency (Dependency(..), depPkgName, simplifyDependency) import Distribution.Verbosity (Verbosity, silent) import Distribution.Version - (Version, LowerBound(..), UpperBound(..) + (Version, VersionRange, LowerBound(..), UpperBound(..) ,asVersionIntervals, majorBoundVersion) import Distribution.PackageDescription.Parsec (readGenericPackageDescription) @@ -107,7 +107,7 @@ showResult verbosity outdatedDeps simpleOutput = then do when (not simpleOutput) $ notice verbosity "Outdated dependencies:" - for_ outdatedDeps $ \(d@(Dependency pn _), v) -> + for_ outdatedDeps $ \(d@(Dependency pn _ _), v) -> let outdatedDep = if simpleOutput then display pn else display d ++ " (latest: " ++ display v ++ ")" in notice verbosity outdatedDep @@ -179,10 +179,10 @@ listOutdated deps pkgIndex (ListOutdatedSettings ignorePred minorPred) = mapMaybe isOutdated $ map simplifyDependency deps where isOutdated :: Dependency -> Maybe (Dependency, Version) - isOutdated dep + isOutdated dep@(Dependency pname vr _) | ignorePred (depPkgName dep) = Nothing | otherwise = - let this = map packageVersion $ lookupDependency pkgIndex dep + let this = map packageVersion $ lookupDependency pkgIndex pname vr latest = lookupLatest dep in (\v -> (dep, v)) `fmap` isOutdated' this latest @@ -195,17 +195,16 @@ listOutdated deps pkgIndex (ListOutdatedSettings ignorePred minorPred) = in if this' < latest' then Just latest' else Nothing lookupLatest :: Dependency -> [Version] - lookupLatest dep + lookupLatest dep@(Dependency pname vr _) | minorPred (depPkgName dep) = - map packageVersion $ lookupDependency pkgIndex (relaxMinor dep) + map packageVersion $ lookupDependency pkgIndex pname (relaxMinor vr) | otherwise = map packageVersion $ lookupPackageName pkgIndex (depPkgName dep) - relaxMinor :: Dependency -> Dependency - relaxMinor (Dependency pn vr) = (Dependency pn vr') - where - vr' = let vis = asVersionIntervals vr - (LowerBound v0 _,upper) = last vis - in case upper of - NoUpperBound -> vr - UpperBound _v1 _ -> majorBoundVersion v0 + relaxMinor :: VersionRange -> VersionRange + relaxMinor vr = + let vis = asVersionIntervals vr + (LowerBound v0 _,upper) = last vis + in case upper of + NoUpperBound -> vr + UpperBound _v1 _ -> majorBoundVersion v0 diff --git a/cabal-install/Distribution/Client/PackageUtils.hs b/cabal-install/Distribution/Client/PackageUtils.hs index b1236fb38b1..8c24762af22 100644 --- a/cabal-install/Distribution/Client/PackageUtils.hs +++ b/cabal-install/Distribution/Client/PackageUtils.hs @@ -33,7 +33,7 @@ externalBuildDepends pkg spec = filter (not . internal) (enabledBuildDepends pkg where -- True if this dependency is an internal one (depends on a library -- defined in the same package). - internal (Dependency depName versionRange) = + internal (Dependency depName versionRange _) = (depName == packageName pkg && packageVersion pkg `withinRange` versionRange) || (Just (packageNameToUnqualComponentName depName) `elem` map libName (subLibraries pkg) && diff --git a/cabal-install/Distribution/Client/ProjectConfig.hs b/cabal-install/Distribution/Client/ProjectConfig.hs index 9243f79334b..ed99ee0aff4 100644 --- a/cabal-install/Distribution/Client/ProjectConfig.hs +++ b/cabal-install/Distribution/Client/ProjectConfig.hs @@ -992,7 +992,7 @@ fetchAndReadSourcePackages verbosity distDirLayout let pkgsNamed = [ NamedPackage pkgname [PackagePropertyVersion verrange] - | ProjectPackageNamed (Dependency pkgname verrange) <- pkgLocations ] + | ProjectPackageNamed (Dependency pkgname verrange _) <- pkgLocations ] return $ concat [ pkgsLocalDirectory diff --git a/cabal-install/Distribution/Client/ProjectPlanning.hs b/cabal-install/Distribution/Client/ProjectPlanning.hs index 32ebbc230b5..a581d511598 100644 --- a/cabal-install/Distribution/Client/ProjectPlanning.hs +++ b/cabal-install/Distribution/Client/ProjectPlanning.hs @@ -988,7 +988,7 @@ planPackages verbosity comp platform solver SolverSettings{..} . addPreferences -- preferences from the config file or command line [ PackageVersionPreference name ver - | Dependency name ver <- solverSettingPreferences ] + | Dependency name ver _ <- solverSettingPreferences ] . addConstraints -- version constraints from the config file or command line @@ -3001,9 +3001,9 @@ defaultSetupDeps compiler platform pkg = -- of other packages. SetupCustomImplicitDeps -> Just $ - [ Dependency depPkgname anyVersion + [ Dependency depPkgname anyVersion (Set.singleton LMainLibName) | depPkgname <- legacyCustomSetupPkgs compiler platform ] ++ - [ Dependency cabalPkgname cabalConstraint + [ Dependency cabalPkgname cabalConstraint (Set.singleton LMainLibName) | packageName pkg /= cabalPkgname ] where -- The Cabal dep is slightly special: @@ -3026,8 +3026,8 @@ defaultSetupDeps compiler platform pkg = -- external Setup.hs, it'll be one of the simple ones that only depends -- on Cabal and base. SetupNonCustomExternalLib -> - Just [ Dependency cabalPkgname cabalConstraint - , Dependency basePkgname anyVersion ] + Just [ Dependency cabalPkgname cabalConstraint (Set.singleton LMainLibName) + , Dependency basePkgname anyVersion (Set.singleton LMainLibName)] where cabalConstraint = orLaterVersion (PD.specVersion pkg) diff --git a/cabal-install/Distribution/Client/Setup.hs b/cabal-install/Distribution/Client/Setup.hs index 202c549cd5c..7acb97177e3 100644 --- a/cabal-install/Distribution/Client/Setup.hs +++ b/cabal-install/Distribution/Client/Setup.hs @@ -110,13 +110,12 @@ import Distribution.Simple.InstallDirs import Distribution.Version ( Version, mkVersion, nullVersion, anyVersion, thisVersion ) import Distribution.Package - ( PackageIdentifier, PackageName, packageName, mkPackageName - , packageVersion ) + ( PackageName, PackageIdentifier, packageName, packageVersion ) import Distribution.Types.Dependency import Distribution.Types.GivenComponent ( GivenComponent(..) ) import Distribution.Types.UnqualComponentName - ( unUnqualComponentName ) + ( unqualComponentNameToPackageName ) import Distribution.PackageDescription ( BuildType(..), RepoKind(..), LibraryName(..) ) import Distribution.System ( Platform ) @@ -139,6 +138,7 @@ import Distribution.Client.GlobalFlags import Data.List ( deleteFirstsBy ) +import qualified Data.Set as Set import System.FilePath ( () ) import Network.URI @@ -530,12 +530,13 @@ filterConfigureFlags flags cabalLibVersion } flags_2_5_0 = flags_latest { - -- Cabal < 2.5.0 does not understand --dependency=pkg:COMPONENT=cid - -- (public sublibraries) + -- Cabal < 2.5.0 does not understand --dependency=pkg:component=cid + -- (public sublibraries), so we convert it to the legacy + -- --dependency=pkg_or_internal_compoent=cid configDependencies = let convertToLegacyInternalDep (GivenComponent _ (LSubLibName cn) cid) = Just $ GivenComponent - (mkPackageName $ unUnqualComponentName cn) + (unqualComponentNameToPackageName cn) LMainLibName cid convertToLegacyInternalDep (GivenComponent pn LMainLibName cid) = @@ -2833,8 +2834,8 @@ parseDependencyOrPackageId = parse Parse.+++ liftM pkgidToDependency parse where pkgidToDependency :: PackageIdentifier -> Dependency pkgidToDependency p = case packageVersion p of - v | v == nullVersion -> Dependency (packageName p) anyVersion - | otherwise -> Dependency (packageName p) (thisVersion v) + v | v == nullVersion -> Dependency (packageName p) anyVersion (Set.singleton LMainLibName) + | otherwise -> Dependency (packageName p) (thisVersion v) (Set.singleton LMainLibName) showRepo :: RemoteRepo -> String showRepo repo = remoteRepoName repo ++ ":" diff --git a/cabal-install/Distribution/Client/SetupWrapper.hs b/cabal-install/Distribution/Client/SetupWrapper.hs index 67c369d2d21..d06c0845f2d 100644 --- a/cabal-install/Distribution/Client/SetupWrapper.hs +++ b/cabal-install/Distribution/Client/SetupWrapper.hs @@ -36,7 +36,6 @@ import Distribution.Package ( newSimpleUnitId, unsafeMkDefUnitId, ComponentId , PackageId, mkPackageName , PackageIdentifier(..), packageVersion, packageName ) -import Distribution.Types.Dependency import Distribution.PackageDescription ( GenericPackageDescription(packageDescription) , PackageDescription(..), specVersion, buildType @@ -719,10 +718,10 @@ getExternalSetupMethod verbosity options pkg bt = do return (packageVersion pkg, Nothing, options') installedCabalVersion options' compiler progdb = do index <- maybeGetInstalledPackages options' compiler progdb - let cabalDep = Dependency (mkPackageName "Cabal") - (useCabalVersion options') - options'' = options' { usePackageIndex = Just index } - case PackageIndex.lookupDependency index cabalDep of + let cabalDepName = mkPackageName "Cabal" + cabalDepVersion = useCabalVersion options' + options'' = options' { usePackageIndex = Just index } + case PackageIndex.lookupDependency index cabalDepName cabalDepVersion of [] -> die' verbosity $ "The package '" ++ display (packageName pkg) ++ "' requires Cabal library version " ++ display (useCabalVersion options) diff --git a/cabal-install/Distribution/Client/Targets.hs b/cabal-install/Distribution/Client/Targets.hs index 69ca5dec0d9..88d5fba42cf 100644 --- a/cabal-install/Distribution/Client/Targets.hs +++ b/cabal-install/Distribution/Client/Targets.hs @@ -54,6 +54,7 @@ import Distribution.Package ( Package(..), PackageName, unPackageName, mkPackageName , PackageIdentifier(..), packageName, packageVersion ) import Distribution.Types.Dependency +import Distribution.Types.LibraryName import Distribution.Client.Types ( PackageLocation(..), ResolvedPkgLoc, UnresolvedSourcePackage , PackageSpecifier(..) ) @@ -91,6 +92,7 @@ import Distribution.PackageDescription.Parsec import Data.Either ( partitionEithers ) import qualified Data.Map as Map +import qualified Data.Set as Set import qualified Data.ByteString.Lazy as BS import qualified Distribution.Client.GZipUtils as GZipUtils import Control.Monad (mapM) @@ -187,7 +189,7 @@ data UserTargetProblem readUserTarget :: String -> IO (Either UserTargetProblem UserTarget) readUserTarget targetstr = case testNamedTargets targetstr of - Just (Dependency pkgn verrange) + Just (Dependency pkgn verrange _) | pkgn == mkPackageName "world" -> return $ if verrange == anyVersion then Right UserTargetWorld @@ -255,8 +257,8 @@ readUserTarget targetstr = where pkgidToDependency :: PackageIdentifier -> Dependency pkgidToDependency p = case packageVersion p of - v | v == nullVersion -> Dependency (packageName p) anyVersion - | otherwise -> Dependency (packageName p) (thisVersion v) + v | v == nullVersion -> Dependency (packageName p) anyVersion (Set.singleton LMainLibName) + | otherwise -> Dependency (packageName p) (thisVersion v) (Set.singleton LMainLibName) reportUserTargetProblems :: Verbosity -> [UserTargetProblem] -> IO () @@ -376,7 +378,7 @@ expandUserTarget :: Verbosity -> IO [PackageTarget (PackageLocation ())] expandUserTarget verbosity worldFile userTarget = case userTarget of - UserTargetNamed (Dependency name vrange) -> + UserTargetNamed (Dependency name vrange _cs) -> let props = [ PackagePropertyVersion vrange | not (isAnyVersion vrange) ] in return [PackageTargetNamedFuzzy name props userTarget] @@ -385,7 +387,7 @@ expandUserTarget verbosity worldFile userTarget = case userTarget of worldPkgs <- World.getContents verbosity worldFile --TODO: should we warn if there are no world targets? return [ PackageTargetNamed name props userTarget - | World.WorldPkgInfo (Dependency name vrange) flags <- worldPkgs + | World.WorldPkgInfo (Dependency name vrange _) flags <- worldPkgs , let props = [ PackagePropertyVersion vrange | not (isAnyVersion vrange) ] ++ [ PackagePropertyFlags flags diff --git a/cabal-install/Distribution/Client/World.hs b/cabal-install/Distribution/Client/World.hs index 7a2dda5a246..67bf5e098dc 100644 --- a/cabal-install/Distribution/Client/World.hs +++ b/cabal-install/Distribution/Client/World.hs @@ -74,8 +74,8 @@ delete = modifyWorld $ flip (deleteFirstsBy equalUDep) -- | WorldPkgInfo values are considered equal if they refer to -- the same package, i.e., we don't care about differing versions or flags. equalUDep :: WorldPkgInfo -> WorldPkgInfo -> Bool -equalUDep (WorldPkgInfo (Dependency pkg1 _) _) - (WorldPkgInfo (Dependency pkg2 _) _) = pkg1 == pkg2 +equalUDep (WorldPkgInfo (Dependency pkg1 _ _) _) + (WorldPkgInfo (Dependency pkg2 _ _) _) = pkg1 == pkg2 -- | Modifies the world file by applying an update-function ('unionBy' -- for 'insert', 'deleteFirstsBy' for 'delete') to the given list of diff --git a/cabal-install/Distribution/Solver/Modular/IndexConversion.hs b/cabal-install/Distribution/Solver/Modular/IndexConversion.hs index 228ce3a6f7d..05896706c86 100644 --- a/cabal-install/Distribution/Solver/Modular/IndexConversion.hs +++ b/cabal-install/Distribution/Solver/Modular/IndexConversion.hs @@ -335,7 +335,7 @@ type IPNs = Set PN -- | Convenience function to delete a 'Dependency' if it's -- for a 'PN' that isn't actually real. filterIPNs :: IPNs -> Dependency -> Maybe Dependency -filterIPNs ipns d@(Dependency pn _) +filterIPNs ipns d@(Dependency pn _ _) | S.notMember pn ipns = Just d | otherwise = Nothing @@ -562,7 +562,7 @@ unionDRs (DependencyReason pn' fs1 ss1) (DependencyReason _ fs2 ss2) = -- | Convert a Cabal dependency on a library to a solver-specific dependency. convLibDep :: DependencyReason PN -> Dependency -> LDep PN -convLibDep dr (Dependency pn vr) = LDep dr $ Dep (PkgComponent pn ExposedLib) (Constrained vr) +convLibDep dr (Dependency pn vr _) = LDep dr $ Dep (PkgComponent pn ExposedLib) (Constrained vr) -- | Convert a Cabal dependency on an executable (build-tools) to a solver-specific dependency. convExeDep :: DependencyReason PN -> ExeDependency -> LDep PN diff --git a/cabal-install/Distribution/Solver/Types/PackageConstraint.hs b/cabal-install/Distribution/Solver/Types/PackageConstraint.hs index 46eb29ee92a..5156c097928 100644 --- a/cabal-install/Distribution/Solver/Types/PackageConstraint.hs +++ b/cabal-install/Distribution/Solver/Types/PackageConstraint.hs @@ -22,6 +22,7 @@ import Distribution.Compat.Binary (Binary(..)) import Distribution.Package (PackageName) import Distribution.PackageDescription (FlagAssignment, dispFlagAssignment) import Distribution.Types.Dependency (Dependency(..)) +import Distribution.Types.LibraryName (LibraryName(..)) import Distribution.Version (VersionRange, simplifyVersionRange) import Distribution.Solver.Compat.Prelude ((<<>>)) @@ -32,6 +33,7 @@ import Distribution.Text (disp, flatStyle) import GHC.Generics (Generic) import Text.PrettyPrint ((<+>)) import qualified Text.PrettyPrint as Disp +import qualified Data.Set as Set -- | Determines to what packages and in what contexts a @@ -142,7 +144,7 @@ packageConstraintToDependency :: PackageConstraint -> Maybe Dependency packageConstraintToDependency (PackageConstraint scope prop) = toDep prop where toDep (PackagePropertyVersion vr) = - Just $ Dependency (scopeToPackageName scope) vr + Just $ Dependency (scopeToPackageName scope) vr (Set.singleton LMainLibName) toDep (PackagePropertyInstalled) = Nothing toDep (PackagePropertySource) = Nothing toDep (PackagePropertyFlags _) = Nothing diff --git a/cabal-install/Distribution/Solver/Types/PackageIndex.hs b/cabal-install/Distribution/Solver/Types/PackageIndex.hs index a9272307179..9946ba26b81 100644 --- a/cabal-install/Distribution/Solver/Types/PackageIndex.hs +++ b/cabal-install/Distribution/Solver/Types/PackageIndex.hs @@ -55,9 +55,8 @@ import Data.List (groupBy, isInfixOf) import Distribution.Package ( PackageName, unPackageName, PackageIdentifier(..) , Package(..), packageName, packageVersion ) -import Distribution.Types.Dependency import Distribution.Version - ( withinRange ) + ( VersionRange, withinRange ) import Distribution.Simple.Utils ( lowercase, comparing ) @@ -210,10 +209,10 @@ deletePackageName name = delete name (\pkg -> packageName pkg == name) -- | Removes all packages satisfying this dependency from the index. --- -deleteDependency :: Package pkg => Dependency -> PackageIndex pkg +deleteDependency :: Package pkg + => PackageName -> VersionRange -> PackageIndex pkg -> PackageIndex pkg -deleteDependency (Dependency name verstionRange) = +deleteDependency name verstionRange = delete name (\pkg -> packageVersion pkg `withinRange` verstionRange) -- @@ -269,8 +268,11 @@ lookupPackageName index name = -- We get back any number of versions of the specified package name, all -- satisfying the version range constraint. -- -lookupDependency :: Package pkg => PackageIndex pkg -> Dependency -> [pkg] -lookupDependency index (Dependency name versionRange) = +lookupDependency :: Package pkg + => PackageIndex pkg + -> PackageName -> VersionRange + -> [pkg] +lookupDependency index name versionRange = [ pkg | pkg <- lookup index name , packageName pkg == name , packageVersion pkg `withinRange` versionRange ] diff --git a/cabal-install/solver-dsl/UnitTests/Distribution/Solver/Modular/DSL.hs b/cabal-install/solver-dsl/UnitTests/Distribution/Solver/Modular/DSL.hs index 50152963ebb..3396a540cb4 100644 --- a/cabal-install/solver-dsl/UnitTests/Distribution/Solver/Modular/DSL.hs +++ b/cabal-install/solver-dsl/UnitTests/Distribution/Solver/Modular/DSL.hs @@ -44,6 +44,7 @@ import Distribution.Solver.Compat.Prelude import Control.Arrow (second) import Data.Either (partitionEithers) import qualified Data.Map as Map +import qualified Data.Set as Set -- Cabal import qualified Distribution.Compiler as C @@ -545,7 +546,7 @@ exAvSrcPkg ex = } mkDirect :: (ExamplePkgName, C.VersionRange) -> C.Dependency - mkDirect (dep, vr) = C.Dependency (C.mkPackageName dep) vr + mkDirect (dep, vr) = C.Dependency (C.mkPackageName dep) vr (Set.singleton C.LMainLibName) mkFlagged :: (ExampleFlagName, Dependencies, Dependencies) -> DependencyComponent C.BuildInfo diff --git a/cabal-install/tests/UnitTests/Distribution/Client/ArbitraryInstances.hs b/cabal-install/tests/UnitTests/Distribution/Client/ArbitraryInstances.hs index b5f66ad6ed7..03a2d35d72c 100644 --- a/cabal-install/tests/UnitTests/Distribution/Client/ArbitraryInstances.hs +++ b/cabal-install/tests/UnitTests/Distribution/Client/ArbitraryInstances.hs @@ -22,6 +22,8 @@ import Control.Monad import Distribution.Version import Distribution.Types.Dependency +import Distribution.Types.UnqualComponentName +import Distribution.Types.LibraryName import Distribution.Package import Distribution.System import Distribution.Verbosity @@ -119,7 +121,14 @@ instance Arbitrary PackageName where packageChars = filter isAlphaNum ['\0'..'\127'] instance Arbitrary Dependency where - arbitrary = Dependency <$> arbitrary <*> arbitrary + arbitrary = Dependency <$> arbitrary <*> arbitrary <*> fmap getNonMEmpty arbitrary + +instance Arbitrary UnqualComponentName where + -- same rules as package names + arbitrary = packageNameToUnqualComponentName <$> arbitrary + +instance Arbitrary LibraryName where + arbitrary = elements =<< sequenceA [LSubLibName <$> arbitrary, pure LMainLibName] instance Arbitrary OS where arbitrary = elements knownOSs diff --git a/cabal-testsuite/PackageTests/CaretOperator/setup.test.hs b/cabal-testsuite/PackageTests/CaretOperator/setup.test.hs index b3eee723add..545be48d566 100644 --- a/cabal-testsuite/PackageTests/CaretOperator/setup.test.hs +++ b/cabal-testsuite/PackageTests/CaretOperator/setup.test.hs @@ -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) $ \(Dependency pn vr _) -> when (pn == mkPackageName "pretty") $ assertEqual "targetBuildDepends/pretty" vr (majorBoundVersion (mkVersion [1,1,1,0]))