Skip to content

Commit

Permalink
Distinguish between internal and external libraries in build-depends
Browse files Browse the repository at this point in the history
Fixes haskell#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.
  • Loading branch information
ezyang authored and Ericson2314 committed Mar 18, 2017
1 parent 4458a02 commit 2dc6210
Show file tree
Hide file tree
Showing 45 changed files with 729 additions and 567 deletions.
2 changes: 2 additions & 0 deletions Cabal/Cabal.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
22 changes: 10 additions & 12 deletions Cabal/Distribution/Backpack/ComponentsGraph.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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) )
Expand Down Expand Up @@ -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
Expand Down
118 changes: 52 additions & 66 deletions Cabal/Distribution/Backpack/ConfiguredComponent.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,15 +22,14 @@ 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
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)
Expand All @@ -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
Expand Down Expand Up @@ -95,59 +93,72 @@ 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
-> ConfiguredComponentMap
-> 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,
Expand All @@ -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
Expand Down Expand Up @@ -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)
53 changes: 35 additions & 18 deletions Cabal/Distribution/PackageDescription/Check.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -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 "
Expand Down Expand Up @@ -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 =
Expand All @@ -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
Expand Down Expand Up @@ -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 "
Expand All @@ -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)) $
Expand All @@ -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)) $
Expand Down Expand Up @@ -1292,7 +1301,7 @@ checkCabalVersion pkg =
_ -> False

versionRangeExpressions =
[ dep | dep@(Dependency _ vr) <- allBuildDepends pkg
[ dep | dep@(LibDependency _ _ vr) <- allBuildDepends pkg
, usesNewVersionRangeSyntax vr ]

testedWithVersionRangeExpressions =
Expand Down Expand Up @@ -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)

Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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,
Expand Down
Loading

0 comments on commit 2dc6210

Please sign in to comment.