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.
  • Loading branch information
ezyang authored and Ericson2314 committed Feb 24, 2017
1 parent e84a99a commit 7cc0aed
Show file tree
Hide file tree
Showing 25 changed files with 395 additions and 266 deletions.
1 change: 1 addition & 0 deletions Cabal/Cabal.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -243,6 +243,7 @@ library
Distribution.Types.ComponentRequestedSpec
Distribution.Types.TargetInfo
Distribution.Types.UnqualComponentName
Distribution.Types.LibDependency
Distribution.Utils.Generic
Distribution.Utils.NubList
Distribution.Utils.ShortText
Expand Down
22 changes: 11 additions & 11 deletions Cabal/Distribution/Backpack/ComponentsGraph.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,9 +15,9 @@ import Distribution.Simple.BuildToolDepends
import Distribution.Simple.LocalBuildInfo
import Distribution.Types.ComponentRequestedSpec
import Distribution.Types.Dependency
import Distribution.Types.UnqualComponentName
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,18 @@ 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
++ if null mixin_deps -- the implicit dependency!
then [ CLibName
| Dependency pn _ <- targetBuildDepends bi
, pn == packageName pkg_descr ]
else []
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
2 changes: 1 addition & 1 deletion Cabal/Distribution/Backpack/Configure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -81,7 +81,7 @@ configureComponentLocalBuildInfos
(dispComponentsGraph graph0)

let conf_pkg_map = Map.fromList
[(pc_pkgname pkg, (pc_cid pkg, pc_pkgid pkg))
[((pc_pkgname pkg, CLibName), (pc_cid pkg, pc_pkgid pkg))
| pkg <- prePkgDeps]
graph1 = toConfiguredComponents use_external_internal_deps
flagAssignment
Expand Down
176 changes: 80 additions & 96 deletions Cabal/Distribution/Backpack/ConfiguredComponent.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,10 +19,8 @@ import Distribution.Compat.Prelude hiding ((<>))

import Distribution.Backpack.Id

import Distribution.Types.Dependency
import Distribution.Types.IncludeRenaming
import Distribution.Types.Mixin
import Distribution.Types.UnqualComponentName
import Distribution.Types.ComponentInclude
import Distribution.Package
import Distribution.PackageDescription as PD hiding (Flag)
Expand Down Expand Up @@ -78,104 +76,105 @@ dispConfiguredComponent cc =
| incl <- cc_includes cc
])

-- | Construct a 'ConfiguredComponent', given that the 'ComponentId'
-- and library/executable dependencies are known. The primary
-- work this does is handling implicit @backpack-include@ fields.
mkConfiguredComponent
:: PackageId
-- | 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, 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
-> [(PackageName, (ComponentId, PackageId))]
-> [ComponentId]
-> ConfiguredComponentMap
-> Component
-> ConfiguredComponent
mkConfiguredComponent this_pid this_cid lib_deps exe_deps component =
toConfiguredComponent pkg_descr this_cid deps_map component =
ConfiguredComponent {
cc_cid = this_cid,
cc_pkgid = this_pid,
cc_pkgid = package pkg_descr,
cc_component = component,
cc_public = is_public,
cc_internal_build_tools = exe_deps,
cc_includes = explicit_includes ++ implicit_includes
}
where
bi = componentBuildInfo component
deps_map = Map.fromList lib_deps

-- Resolve each @mixins@ into the actual dependency
-- from @lib_deps@.
explicit_includes
= [ let (cid, pid) =
case Map.lookup name deps_map of
Nothing ->
error $ "Mix-in refers to non-existent package " ++ display name ++
" (did you forget to add the package to build-depends?)"
Just r -> r
= [ let cname = maybe CLibName CSubLibName mb_lib_name
(cid, pid) = case Map.lookup (name, cname) deps_map of
-- TODO: give a better error message here if the *package*
-- exists, but doesn't have this component.
Nothing ->
error $ "Mix-in refers to non-existent component " ++ display cname ++
" in " ++ display name ++
" (did you forget to add the package to build-depends?)"
Just r -> r
in ComponentInclude {
ci_id = cid,
-- TODO: We set pkgName = name here to make error messages
-- look better. But it would be better to properly
-- record component name here.
ci_pkgid = pid { pkgName = name },
ci_pkgid = pid,
ci_renaming = rns,
ci_implicit = False
}
| Mixin name rns <- mixins bi ]
| Mixin name mb_lib_name rns <- mixins bi ]

-- Any @build-depends@ which is not explicitly mentioned in
-- @backpack-include@ is converted into an "implicit" include.
used_explicitly = Set.fromList (map ci_id explicit_includes)
implicit_includes
= map (\(pn, (cid, pid)) -> ComponentInclude {
ci_id = cid,
-- See above ci_pkgid
ci_pkgid = pid { pkgName = pn },
ci_renaming = defaultIncludeRenaming,
ci_implicit = True
})
$ filter (flip Set.notMember used_explicitly . fst . snd) lib_deps

is_public = componentName component == CLibName

type ConfiguredComponentMap =
(Map PackageName (ComponentId, PackageId), -- libraries
Map UnqualComponentName ComponentId) -- executables

-- 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
-> Map PackageName (ComponentId, PackageId) -- external
-> ConfiguredComponentMap
-> Component
-> ConfiguredComponent
toConfiguredComponent pkg_descr this_cid
external_lib_map (lib_map, exe_map) component =
mkConfiguredComponent
(package pkg_descr) this_cid
lib_deps exe_deps component
where
bi = componentBuildInfo component
find_it :: PackageName -> (ComponentId, PackageId)
find_it name =
fromMaybe (error ("toConfiguredComponent: " ++ display (packageName pkg_descr) ++
" " ++ display name)) $
Map.lookup name lib_map <|>
Map.lookup name external_lib_map
-- NB: This INCLUDES if you depend pkg:sublib (because other way
-- there's no way to depend on a sublib without depending on the
-- main library as well).
used_explicitly = Set.fromList (map (\m -> (mixinPackageName m, mixinLibraryName m))
(mixins bi))
lib_deps
| newPackageDepsBehaviour pkg_descr
= [ (name, find_it name)
| Dependency name _ <- targetBuildDepends bi ]
= [ case Map.lookup (pn, maybe CLibName CSubLibName mb_cn) deps_map of
Nothing ->
error ("toConfiguredComponent: " ++ display (packageName pkg_descr) ++
" " ++ display pn)
Just r -> r
| Mixin pn mb_cn _ <- implicitMixins bi
, Set.notMember (pn,mb_cn) used_explicitly ]
| otherwise
= Map.toList external_lib_map
-- deps_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.
= [ r
| ((pn,cn), r) <- Map.toList deps_map
, pn /= packageName pkg_descr
, cn == CLibName
, Set.notMember (pn, Nothing) used_explicitly ]
implicit_includes
= map (\(cid, pid) ->
ComponentInclude {
ci_id = cid,
ci_pkgid = pid,
ci_renaming = defaultIncludeRenaming,
ci_implicit = True
}) lib_deps

exe_deps = [ cid
| toolName <- getAllInternalToolDependencies pkg_descr bi
, Just cid <- [ Map.lookup toolName exe_map ] ]
, let cn = CExeName toolName
-- NB: we silently swallow non-existent build-tools,
-- because historically they did not have to correspond
-- to Haskell executables.
, Just (cid, _) <- [ Map.lookup (packageName pkg_descr, cn) deps_map ] ]

is_public = componentName component == CLibName

-- | Also computes the 'ComponentId', and sets cc_public if necessary.
-- This is Cabal-only; cabal-install won't use this.
Expand All @@ -186,45 +185,30 @@ toConfiguredComponent'
-> Bool -- deterministic
-> Flag String -- configIPID (todo: remove me)
-> Flag ComponentId -- configCID
-> Map PackageName (ComponentId, PackageId) -- external
-> ConfiguredComponentMap
-> Component
-> ConfiguredComponent
toConfiguredComponent' use_external_internal_deps flags
pkg_descr deterministic ipid_flag cid_flag
external_lib_map (lib_map, exe_map) component =
deps_map component =
let cc = toConfiguredComponent
pkg_descr this_cid
external_lib_map (lib_map, exe_map) component
deps_map component
in if use_external_internal_deps
then cc { cc_public = True }
else cc
where
this_cid = computeComponentId deterministic ipid_flag cid_flag (package pkg_descr)
(componentName component) (Just (deps, flags))
deps = [ cid | (cid, _) <- Map.elems external_lib_map ]
deps = [ cid | ((dep_pn, _), (cid, _)) <- Map.toList deps_map
, dep_pn /= packageName pkg_descr ]

extendConfiguredComponentMap
:: ConfiguredComponent
-> ConfiguredComponentMap
-> ConfiguredComponentMap
extendConfiguredComponentMap cc (lib_map, exe_map) =
(lib_map', exe_map')
where
lib_map'
= case cc_name cc of
CLibName ->
Map.insert (pkgName (cc_pkgid cc))
(cc_cid cc, cc_pkgid cc) lib_map
CSubLibName str ->
Map.insert (unqualComponentNameToPackageName str)
(cc_cid cc, cc_pkgid cc) lib_map
_ -> lib_map
exe_map'
= case cc_name cc of
CExeName str ->
Map.insert str (cc_cid cc) exe_map
_ -> exe_map
extendConfiguredComponentMap cc deps_map =
Map.insert (pkgName (cc_pkgid cc), cc_name cc) (cc_cid cc, cc_pkgid cc) deps_map

-- Compute the 'ComponentId's for a graph of 'Component's. The
-- list of internal components must be topologically sorted
Expand All @@ -237,19 +221,19 @@ toConfiguredComponents
-> Flag String -- configIPID
-> Flag ComponentId -- configCID
-> PackageDescription
-> Map PackageName (ComponentId, PackageId)
-> ConfiguredComponentMap
-> [Component]
-> [ConfiguredComponent]
toConfiguredComponents
use_external_internal_deps flags deterministic ipid_flag cid_flag pkg_descr
external_lib_map comps
= snd (mapAccumL go (Map.empty, Map.empty) comps)
deps_map comps
= snd (mapAccumL go deps_map comps)
where
go m component = (extendConfiguredComponentMap cc m, cc)
where cc = toConfiguredComponent'
use_external_internal_deps flags pkg_descr
deterministic ipid_flag cid_flag
external_lib_map m component
m component


newPackageDepsBehaviourMinVersion :: Version
Expand Down
13 changes: 5 additions & 8 deletions Cabal/Distribution/Backpack/PreExistingComponent.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@ import Prelude ()

import Distribution.Backpack.ModuleShape
import Distribution.Backpack
import Distribution.Types.ComponentName

import qualified Data.Map as Map
import Distribution.Package
Expand All @@ -18,12 +19,8 @@ import Distribution.InstalledPackageInfo (InstalledPackageInfo)
-- we don't need to know how to build.
data PreExistingComponent
= PreExistingComponent {
-- | The 'PackageName' that, when we see it in 'PackageDescription',
-- we should map this to. This may DISAGREE with 'pc_pkgid' for
-- internal dependencies: e.g., an internal component @lib@
-- may be munged to @z-pkg-z-lib@, but we still want to use
-- it when we see @lib@ in @build-depends@
pc_pkgname :: PackageName,
pc_compname :: ComponentName,
pc_pkgid :: PackageId,
pc_uid :: UnitId,
pc_cid :: ComponentId,
Expand All @@ -34,10 +31,11 @@ data PreExistingComponent
-- | Convert an 'InstalledPackageInfo' into a 'PreExistingComponent',
-- which was brought into scope under the 'PackageName' (important for
-- a package qualified reference.)
ipiToPreExistingComponent :: (PackageName, InstalledPackageInfo) -> PreExistingComponent
ipiToPreExistingComponent (pn, ipi) =
ipiToPreExistingComponent :: (PackageName, ComponentName, InstalledPackageInfo) -> PreExistingComponent
ipiToPreExistingComponent (pn, cn, ipi) =
PreExistingComponent {
pc_pkgname = pn,
pc_compname = cn,
pc_pkgid = Installed.sourcePackageId ipi,
pc_uid = Installed.installedUnitId ipi,
pc_cid = Installed.installedComponentId ipi,
Expand All @@ -46,4 +44,3 @@ ipiToPreExistingComponent (pn, ipi) =
(Map.fromList (Installed.instantiatedWith ipi)),
pc_shape = shapeInstalledPackage ipi
}

Loading

0 comments on commit 7cc0aed

Please sign in to comment.