Skip to content

Commit

Permalink
Fix haskell#6083: Treat pkg:sublib dependency syntax as is since 3.4
Browse files Browse the repository at this point in the history
Note: configuredPackageProblems is a mess,
and there might be bugs now.
  • Loading branch information
phadej committed Jun 16, 2020
1 parent 6001bc9 commit 95b9fbc
Show file tree
Hide file tree
Showing 16 changed files with 105 additions and 82 deletions.
28 changes: 20 additions & 8 deletions cabal-install/Distribution/Client/Dependency.hs
Original file line number Diff line number Diff line change
Expand Up @@ -91,8 +91,6 @@ import qualified Distribution.PackageDescription as PD
import qualified Distribution.PackageDescription.Configuration as PD
import Distribution.PackageDescription.Configuration
( finalizePD )
import Distribution.Client.PackageUtils
( externalBuildDepends )
import Distribution.Compiler
( CompilerInfo(..) )
import Distribution.System
Expand Down Expand Up @@ -890,22 +888,27 @@ showPackageProblem (InvalidDep dep pkgid) =
configuredPackageProblems :: Platform -> CompilerInfo
-> SolverPackage UnresolvedPkgLoc -> [PackageProblem]
configuredPackageProblems platform cinfo
(SolverPackage pkg specifiedFlags stanzas specifiedDeps' _specifiedExeDeps') =
(SolverPackage pkg specifiedFlags stanzas specifiedDeps0 _specifiedExeDeps') =
[ DuplicateFlag flag
| flag <- PD.findDuplicateFlagAssignments specifiedFlags ]
++ [ MissingFlag flag | OnlyInLeft flag <- mergedFlags ]
++ [ ExtraFlag flag | OnlyInRight flag <- mergedFlags ]
++ [ DuplicateDeps pkgs
| pkgs <- CD.nonSetupDeps (fmap (duplicatesBy (comparing packageName))
specifiedDeps) ]
specifiedDeps1) ]
++ [ MissingDep dep | OnlyInLeft dep <- mergedDeps ]
++ [ ExtraDep pkgid | OnlyInRight pkgid <- mergedDeps ]
++ [ InvalidDep dep pkgid | InBoth dep pkgid <- mergedDeps
, not (packageSatisfiesDependency pkgid dep) ]
-- TODO: sanity tests on executable deps
where
specifiedDeps :: ComponentDeps [PackageId]
specifiedDeps = fmap (map solverSrcId) specifiedDeps'
thisPkgName = packageName (packageDescription pkg)

specifiedDeps1 :: ComponentDeps [PackageId]
specifiedDeps1 = fmap (map solverSrcId) specifiedDeps0

specifiedDeps :: [PackageId]
specifiedDeps = CD.flatDeps specifiedDeps1

mergedFlags = mergeBy compare
(sort $ map PD.flagName (PD.genPackageFlags (packageDescription pkg)))
Expand All @@ -919,7 +922,7 @@ configuredPackageProblems platform cinfo
dependencyName (Dependency name _ _) = name

mergedDeps :: [MergeResult Dependency PackageId]
mergedDeps = mergeDeps requiredDeps (CD.flatDeps specifiedDeps)
mergedDeps = mergeDeps requiredDeps specifiedDeps

mergeDeps :: [Dependency] -> [PackageId]
-> [MergeResult Dependency PackageId]
Expand All @@ -939,6 +942,15 @@ configuredPackageProblems platform cinfo
-- `mergeDeps`.
requiredDeps :: [Dependency]
requiredDeps =
-- we filter self/internal dependencies. They are still there.
-- This is INCORRECT.
--
-- If we had per-component solver, it would make this unnecessary,
-- but no finalizePDs picks components we are not building, eg. exes.
-- See #3775
--
filter ((/= thisPkgName) . dependencyName) $

--TODO: use something lower level than finalizePD
case finalizePD specifiedFlags
compSpec
Expand All @@ -947,7 +959,7 @@ configuredPackageProblems platform cinfo
[]
(packageDescription pkg) of
Right (resolvedPkg, _) ->
externalBuildDepends resolvedPkg compSpec
PD.enabledBuildDepends resolvedPkg compSpec
++ maybe [] PD.setupDepends (PD.setupBuildInfo resolvedPkg)
Left _ ->
error "configuredPackageInvalidDeps internal error"
Expand Down
41 changes: 0 additions & 41 deletions cabal-install/Distribution/Client/PackageUtils.hs

This file was deleted.

36 changes: 7 additions & 29 deletions cabal-install/Distribution/Solver/Modular/IndexConversion.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,6 @@ import Distribution.Simple.BuildToolDepends -- from Cabal
import Distribution.Types.ExeDependency -- from Cabal
import Distribution.Types.PkgconfigDependency -- from Cabal
import Distribution.Types.ComponentName -- from Cabal
import Distribution.Types.UnqualComponentName -- from Cabal
import Distribution.Types.CondTree -- from Cabal
import Distribution.Types.MungedPackageId -- from Cabal
import Distribution.Types.MungedPackageName -- from Cabal
Expand Down Expand Up @@ -181,19 +180,11 @@ convGPD os arch cinfo constraints strfl solveExes pn
let
fds = flagInfo strfl flags

-- | We have to be careful to filter out dependencies on
-- internal libraries, since they don't refer to real packages
-- and thus cannot actually be solved over. We'll do this
-- by creating a set of package names which are "internal"
-- and dropping them as we convert.

ipns = S.fromList $ [ unqualComponentNameToPackageName nm
| (nm, _) <- sub_libs ]

conv :: Monoid a => Component -> (a -> BuildInfo) -> DependencyReason PN ->
CondTree ConfVar [Dependency] a -> FlaggedDeps PN
conv comp getInfo dr =
convCondTree M.empty dr pkg os arch cinfo pn fds comp getInfo ipns solveExes .
convCondTree M.empty dr pkg os arch cinfo pn fds comp getInfo solveExes .
addBuildableCondition getInfo

initDR = DependencyReason pn M.empty S.empty
Expand Down Expand Up @@ -331,41 +322,29 @@ flagInfo (StrongFlags strfl) =
weak m = WeakOrTrivial $ not (strfl || m)
flagType m = if m then Manual else Automatic

-- | Internal package names, which should not be interpreted as true
-- dependencies.
type IPNs = S.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 _ _)
| S.notMember pn ipns = Just d
| otherwise = Nothing

-- | Convert condition trees to flagged dependencies. Mutually
-- recursive with 'convBranch'. See 'convBranch' for an explanation
-- of all arguments preceding the input 'CondTree'.
convCondTree :: Map FlagName Bool -> DependencyReason PN -> PackageDescription -> OS -> Arch -> CompilerInfo -> PN -> FlagInfo ->
Component ->
(a -> BuildInfo) ->
IPNs ->
SolveExecutables ->
CondTree ConfVar [Dependency] a -> FlaggedDeps PN
convCondTree flags dr pkg os arch cinfo pn fds comp getInfo ipns solveExes@(SolveExecutables solveExes') (CondNode info ds branches) =
convCondTree flags dr pkg os arch cinfo pn fds comp getInfo solveExes@(SolveExecutables solveExes') (CondNode info ds branches) =
-- Merge all library and build-tool dependencies at every level in
-- the tree of flagged dependencies. Otherwise 'extractCommon'
-- could create duplicate dependencies, and the number of
-- duplicates could grow exponentially from the leaves to the root
-- of the tree.
mergeSimpleDeps $
[ D.Simple singleDep comp
| dep <- mapMaybe (filterIPNs ipns) ds
| dep <- ds
, singleDep <- convLibDeps dr dep ] -- unconditional package dependencies

++ L.map (\e -> D.Simple (LDep dr (Ext e)) comp) (allExtensions bi) -- unconditional extension dependencies
++ L.map (\l -> D.Simple (LDep dr (Lang l)) comp) (allLanguages bi) -- unconditional language dependencies
++ L.map (\(PkgconfigDependency pkn vr) -> D.Simple (LDep dr (Pkg pkn vr)) comp) (pkgconfigDepends bi) -- unconditional pkg-config dependencies
++ concatMap (convBranch flags dr pkg os arch cinfo pn fds comp getInfo ipns solveExes) branches
++ concatMap (convBranch flags dr pkg os arch cinfo pn fds comp getInfo solveExes) branches
-- build-tools dependencies
-- NB: Only include these dependencies if SolveExecutables
-- is True. It might be false in the legacy solver
Expand Down Expand Up @@ -481,14 +460,13 @@ convBranch :: Map FlagName Bool
-> FlagInfo
-> Component
-> (a -> BuildInfo)
-> IPNs
-> SolveExecutables
-> CondBranch ConfVar [Dependency] a
-> FlaggedDeps PN
convBranch flags dr pkg os arch cinfo pn fds comp getInfo ipns solveExes (CondBranch c' t' mf') =
convBranch flags dr pkg os arch cinfo pn fds comp getInfo solveExes (CondBranch c' t' mf') =
go c'
(\flags' dr' -> convCondTree flags' dr' pkg os arch cinfo pn fds comp getInfo ipns solveExes t')
(\flags' dr' -> maybe [] (convCondTree flags' dr' pkg os arch cinfo pn fds comp getInfo ipns solveExes) mf')
(\flags' dr' -> convCondTree flags' dr' pkg os arch cinfo pn fds comp getInfo solveExes t')
(\flags' dr' -> maybe [] (convCondTree flags' dr' pkg os arch cinfo pn fds comp getInfo solveExes) mf')
flags dr
where
go :: Condition ConfVar
Expand Down
1 change: 0 additions & 1 deletion cabal-install/cabal-install.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -225,7 +225,6 @@ executable cabal
Distribution.Client.NixStyleOptions
Distribution.Client.Outdated
Distribution.Client.PackageHash
Distribution.Client.PackageUtils
Distribution.Client.ParseUtils
Distribution.Client.ProjectBuilding
Distribution.Client.ProjectBuilding.Types
Expand Down
1 change: 0 additions & 1 deletion cabal-install/cabal-install.cabal.dev
Original file line number Diff line number Diff line change
Expand Up @@ -217,7 +217,6 @@ library cabal-lib-client
Distribution.Client.NixStyleOptions
Distribution.Client.Outdated
Distribution.Client.PackageHash
Distribution.Client.PackageUtils
Distribution.Client.ParseUtils
Distribution.Client.ProjectBuilding
Distribution.Client.ProjectBuilding.Types
Expand Down
1 change: 0 additions & 1 deletion cabal-install/cabal-install.cabal.prod
Original file line number Diff line number Diff line change
Expand Up @@ -225,7 +225,6 @@ executable cabal
Distribution.Client.NixStyleOptions
Distribution.Client.Outdated
Distribution.Client.PackageHash
Distribution.Client.PackageUtils
Distribution.Client.ParseUtils
Distribution.Client.ProjectBuilding
Distribution.Client.ProjectBuilding.Types
Expand Down
1 change: 0 additions & 1 deletion cabal-install/cabal-install.cabal.zinza
Original file line number Diff line number Diff line change
Expand Up @@ -161,7 +161,6 @@ Version: 3.3.0.0
Distribution.Client.NixStyleOptions
Distribution.Client.Outdated
Distribution.Client.PackageHash
Distribution.Client.PackageUtils
Distribution.Client.ParseUtils
Distribution.Client.ProjectBuilding
Distribution.Client.ProjectBuilding.Types
Expand Down
15 changes: 15 additions & 0 deletions cabal-testsuite/PackageTests/MultipleLibraries/T6083Post/cabal.out
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
# cabal v2-run
Resolving dependencies...
Build profile: -w ghc-<GHCVER> -O1
In order, the following will be built:
- pkg-def-0.1.0.0 (lib) (first run)
- pkg-abc-0.1.0.0 (exe:program) (first run)
Warning: pkg-def.cabal:13:27: visibility is experimental feature (issue #5660)
Configuring library for pkg-def-0.1.0.0..
Preprocessing library for pkg-def-0.1.0.0..
Building library for pkg-def-0.1.0.0..
Warning: pkg-abc.cabal:19:15: colon specifier is experimental feature (issue #5660)
Configuring executable 'program' for pkg-abc-0.1.0.0..
Warning: The package has an extraneous version range for a dependency on an internal library: pkg-def >=0 && ==0.1.0.0. This version range includes the current package but isn't needed as the current package's library will always be used.
Preprocessing executable 'program' for pkg-abc-0.1.0.0..
Building executable 'program' for pkg-abc-0.1.0.0..
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
packages:
pkg-abc
pkg-def

Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
import Test.Cabal.Prelude

-- https://github.com/haskell/cabal/issues/6083
-- see pkg-abc.cabal
main = cabalTest $
cabal' "v2-run" ["pkg-abc:program"] >>= assertOutputContains "pkg-def:pkg-def"
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
module Main (main) where
import PkgDef (defValue)

main :: IO ()
main = print defValue
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
cabal-version: 3.4
name: pkg-abc
version: 0.1.0.0

library pkg-def
default-language: Haskell2010
hs-source-dirs: pkg-def
build-depends: base
exposed-modules: PkgDef

executable program
default-language: Haskell2010
hs-source-dirs: exe
main-is: Main.hs

-- we want that to resolve to pkg-def main library.
build-depends:
, base
, pkg-def:pkg-def
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
module PkgDef (defValue) where

defValue :: String
defValue = "pkg-abc:pkg-def"
Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@
cabal-version: 3.0
name: pkg-def
version: 0.1.0.0

library
default-language: Haskell2010
hs-source-dirs: src
build-depends: base
exposed-modules: PkgDef

library publib
default-language: Haskell2010
visibility: public
hs-source-dirs: publib
build-depends: base
exposed-modules: PkgDef

Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
module PkgDef (defValue) where

defValue :: String
defValue = "pkg-def:publib"
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
module PkgDef (defValue) where

defValue :: String
defValue = "pkg-def:pkg-def"

0 comments on commit 95b9fbc

Please sign in to comment.