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 8, 2017
1 parent 238c1aa commit b8965f7
Show file tree
Hide file tree
Showing 23 changed files with 332 additions and 210 deletions.
1 change: 1 addition & 0 deletions Cabal/Cabal.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -242,6 +242,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
21 changes: 11 additions & 10 deletions Cabal/Distribution/Backpack/ComponentsGraph.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ 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 +58,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
172 changes: 80 additions & 92 deletions Cabal/Distribution/Backpack/ConfiguredComponent.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,6 @@ 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
Expand Down Expand Up @@ -77,100 +76,104 @@ 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 snd lib_deps
deps_map = Map.fromList lib_deps

-- Resolve each @backpack-include@ 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: Check what breaks if you remove this edit
ci_pkgid = pid { pkgName = name },
ci_pkgid = pid,
ci_renaming = rns
}
| 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 (\(cid, pid) -> ComponentInclude {
ci_id = cid,
ci_pkgid = pid,
ci_renaming = defaultIncludeRenaming
})
$ filter (flip Set.notMember used_explicitly . fst) 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
}) 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 @@ -180,45 +183,30 @@ toConfiguredComponent'
-> PackageDescription
-> 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 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 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 @@ -230,18 +218,18 @@ toConfiguredComponents
-> Flag String -- configIPID
-> Flag ComponentId -- configCID
-> PackageDescription
-> Map PackageName (ComponentId, PackageId)
-> ConfiguredComponentMap
-> [Component]
-> [ConfiguredComponent]
toConfiguredComponents
use_external_internal_deps flags 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 ipid_flag cid_flag
external_lib_map m component
m component


newPackageDepsBehaviourMinVersion :: Version
Expand Down
11 changes: 7 additions & 4 deletions Cabal/Distribution/PackageDescription/Parse.hs
Original file line number Diff line number Diff line change
Expand Up @@ -53,11 +53,12 @@ module Distribution.PackageDescription.Parse (
import Prelude ()
import Distribution.Compat.Prelude

import Distribution.Types.BuildInfo
import Distribution.Types.Dependency
import Distribution.Types.ForeignLib
import Distribution.Types.ForeignLibType
import Distribution.Types.UnqualComponentName
import Distribution.Types.CondTree
import Distribution.Types.LibDependency
import Distribution.ParseUtils hiding (parseFields)
import Distribution.PackageDescription
import Distribution.PackageDescription.Utils
Expand Down Expand Up @@ -427,7 +428,9 @@ binfoFieldDescrs =
toolDepends (\xs binfo -> binfo{toolDepends=xs})
, commaListFieldWithSep vcat "build-depends"
disp parse
targetBuildDepends (\xs binfo -> binfo{targetBuildDepends=xs})
buildDependencies
(\xs binfo -> binfo{targetBuildDepends=map buildDependencyToDependency xs,
implicitMixins=map buildDependencyToMixin xs})
, commaListFieldWithSep vcat "mixins"
disp parse
mixins (\xs binfo -> binfo{mixins=xs})
Expand Down Expand Up @@ -643,7 +646,7 @@ constraintFieldNames = ["build-depends"]
-- they add and define an accessor that specifies what the dependencies
-- are. This way we would completely reuse the parsing knowledge from the
-- field descriptor.
parseConstraint :: Field -> ParseResult [Dependency]
parseConstraint :: Field -> ParseResult [LibDependency]
parseConstraint (F l n v)
| n `elem` constraintFieldNames = runP l n (parseCommaList parse) v
parseConstraint f = userBug $ "Constraint was expected (got: " ++ show f ++ ")"
Expand Down Expand Up @@ -1115,7 +1118,7 @@ parseGenericPackageDescription file = do
-- to check the CondTree, rather than grovel everywhere
-- inside the conditional bits).
deps <- liftM concat
. traverse (lift . parseConstraint)
. traverse (lift . fmap (map buildDependencyToDependency) . parseConstraint)
. filter isConstraint
$ simplFlds

Expand Down
6 changes: 5 additions & 1 deletion Cabal/Distribution/PackageDescription/Parsec/FieldDescr.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,6 +43,8 @@ import Distribution.ModuleName (ModuleName)
import Distribution.Package
import Distribution.PackageDescription
import Distribution.Types.ForeignLib
import Distribution.Types.BuildInfo
import Distribution.Types.LibDependency
import Distribution.Parsec.Class
import Distribution.Parsec.Types.Common
import Distribution.Parsec.Types.FieldDescr
Expand Down Expand Up @@ -428,7 +430,9 @@ binfoFieldDescrs =
toolDepends (\xs binfo -> binfo{toolDepends=xs})
, commaListFieldWithSep vcat "build-depends"
disp parsec
targetBuildDepends (\xs binfo -> binfo{targetBuildDepends=xs})
buildDependencies
(\xs binfo -> binfo{targetBuildDepends=map buildDependencyToDependency xs,
implicitMixins=map buildDependencyToMixin xs})
, commaListFieldWithSep vcat "mixins"
disp parsec
mixins (\xs binfo -> binfo{mixins=xs})
Expand Down
Loading

0 comments on commit b8965f7

Please sign in to comment.