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 15, 2017
1 parent 929d16a commit c4222ee
Show file tree
Hide file tree
Showing 53 changed files with 762 additions and 527 deletions.
2 changes: 2 additions & 0 deletions Cabal/Cabal.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -216,8 +216,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
122 changes: 53 additions & 69 deletions Cabal/Distribution/Backpack/ConfiguredComponent.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,15 +19,14 @@ import Distribution.Compat.Prelude hiding ((<>))

import Distribution.Backpack.Id

import Distribution.Types.Dependency
import Distribution.Types.ExeDependency
import Distribution.Types.IncludeRenaming
import Distribution.Types.ComponentId
import Distribution.Types.PackageId
import Distribution.Types.PackageName
import Distribution.Types.LibDependency
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 @@ -39,7 +38,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 @@ -85,85 +83,84 @@ 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 (ComponentId, PackageId))

-- 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 keys@(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 (keys, value)
else return old_style_lib_deps

-- 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
(cid, pid) <-
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
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 ]

lib_deps = Map.toList $ reg_lib_map `Map.union` mixin_map

mixin_includes <- forM lib_deps $ \((pname, cname), (rns, implicit)) -> do
(cid, pid) <- 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_id = cid,
ci_pkgid = pid,
ci_compname = cname,
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 (\((_, cn), (cid, pid)) -> ComponentInclude {
ci_id = cid,
ci_pkgid = pid,
ci_compname = cn,
ci_renaming = defaultIncludeRenaming,
ci_implicit = True
})
$ filter (flip Set.notMember used_explicitly . fst . snd) lib_deps

return ConfiguredComponent {
cc_cid = this_cid,
cc_pkgid = package pkg_descr,
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 = [ ((pn, cn), 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 @@ -249,16 +246,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)
3 changes: 3 additions & 0 deletions Cabal/Distribution/Backpack/ReadyComponent.hs
Original file line number Diff line number Diff line change
Expand Up @@ -138,6 +138,9 @@ instance HasMungedPackageId ReadyComponent where
mungedId ReadyComponent { rc_pkgid = pkgid, rc_component = component }
= computeCompatPackageId pkgid (componentName component)

instance HasComponentName ReadyComponent where
sourceCompName = componentName . rc_component

instance HasUnitId ReadyComponent where
installedUnitId = rc_uid

Expand Down
4 changes: 4 additions & 0 deletions Cabal/Distribution/InstalledPackageInfo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -60,6 +60,7 @@ import Distribution.Version
import Distribution.Text
import qualified Distribution.Compat.ReadP as Parse
import Distribution.Compat.Graph
import Distribution.Types.ComponentName
import Distribution.Types.MungedPackageId
import Distribution.Types.MungedPackageName
import Distribution.Types.UnqualComponentName
Expand Down Expand Up @@ -202,6 +203,9 @@ instance Package.Package InstalledPackageInfo where
packageId ipi = PackageIdentifier (sourcePackageName' ipi) ver
where MungedPackageId _ ver = sourceMungedPackageId ipi

instance Package.HasComponentName InstalledPackageInfo where
sourceCompName = libraryComponentName . sourceLibName

instance Package.HasUnitId InstalledPackageInfo where
installedUnitId = installedUnitId

Expand Down
14 changes: 9 additions & 5 deletions Cabal/Distribution/Package.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ module Distribution.Package
, module Distribution.Types.PkgconfigName
, Package(..), packageName, packageVersion
, HasMungedPackageId(..), mungedName', mungedVersion'
, HasUnitId(..)
, HasComponentName(..), HasUnitId(..)
, installedPackageId
, PackageInstalled(..)
) where
Expand All @@ -43,6 +43,7 @@ import Distribution.Types.MungedPackageId
import Distribution.Types.PackageId
import Distribution.Types.UnitId
import Distribution.Types.Module
import Distribution.Types.ComponentName
import Distribution.Types.MungedPackageName
import Distribution.Types.PackageName
import Distribution.Types.PkgconfigName
Expand All @@ -66,12 +67,12 @@ mungedName' = mungedName . mungedId
mungedVersion' :: HasMungedPackageId munged => munged -> Version
mungedVersion' = mungedVersion . mungedId

class HasMungedPackageId pkg where
mungedId :: pkg -> MungedPackageId

instance Package PackageIdentifier where
packageId = id

class HasMungedPackageId pkg where
mungedId :: pkg -> MungedPackageId

packageName :: Package pkg => pkg -> PackageName
packageName = pkgName . packageId

Expand All @@ -81,6 +82,9 @@ packageVersion = pkgVersion . packageId
instance HasMungedPackageId MungedPackageId where
mungedId = id

class Package pkg => HasComponentName pkg where
sourceCompName :: pkg -> ComponentName

-- | Packages that have an installed unit ID
class Package pkg => HasUnitId pkg where
installedUnitId :: pkg -> UnitId
Expand All @@ -96,5 +100,5 @@ installedPackageId = installedUnitId
-- 'InstalledPackageInfo', but when we are doing install plans in Cabal install
-- we may have other, installed package-like things which contain more metadata.
-- Installed packages have exact dependencies 'installedDepends'.
class (HasUnitId pkg) => PackageInstalled pkg where
class (HasComponentName pkg, HasUnitId pkg) => PackageInstalled pkg where
installedDepends :: pkg -> [UnitId]
Loading

0 comments on commit c4222ee

Please sign in to comment.