Skip to content

Commit

Permalink
Revert "Merge pull request #4383 from Ericson2314/no-legacy-build-dep…
Browse files Browse the repository at this point in the history
…ends"

This reverts commit ea75854, reversing
changes made to 602dfdc.

See #5119 for the reason for reverting this.
  • Loading branch information
23Skidoo committed Feb 14, 2018
1 parent ccb3350 commit d6831f7
Show file tree
Hide file tree
Showing 33 changed files with 116 additions and 87 deletions.
2 changes: 0 additions & 2 deletions Cabal/Distribution/PackageDescription.hs
Original file line number Diff line number Diff line change
Expand Up @@ -83,8 +83,6 @@ module Distribution.PackageDescription (
hcStaticOptions,

-- ** Supplementary build information
allBuildDepends,
enabledBuildDepends,
ComponentName(..),
defaultLibName,
HookedBuildInfo,
Expand Down
8 changes: 4 additions & 4 deletions Cabal/Distribution/PackageDescription/Check.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1363,7 +1363,7 @@ checkCabalVersion pkg =
_ -> False

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

testedWithVersionRangeExpressions =
Expand Down Expand Up @@ -1391,10 +1391,10 @@ checkCabalVersion pkg =
alg (VersionRangeParensF _) = 3
alg _ = 1 :: Int

depsUsingWildcardSyntax = [ dep | dep@(Dependency _ vr) <- allBuildDepends pkg
depsUsingWildcardSyntax = [ dep | dep@(Dependency _ vr) <- buildDepends pkg
, usesWildcardSyntax vr ]

depsUsingMajorBoundSyntax = [ dep | dep@(Dependency _ vr) <- allBuildDepends pkg
depsUsingMajorBoundSyntax = [ dep | dep@(Dependency _ vr) <- buildDepends pkg
, usesMajorBoundSyntax vr ]

usesBackpackIncludes = any (not . null . mixins) (allBuildInfo pkg)
Expand Down Expand Up @@ -1541,7 +1541,7 @@ checkPackageVersions pkg =
foldr intersectVersionRanges anyVersion baseDeps
where
baseDeps =
[ vr | Dependency pname vr <- allBuildDepends pkg'
[ vr | Dependency pname vr <- buildDepends pkg'
, pname == mkPackageName "base" ]

-- Just in case finalizePD fails for any reason,
Expand Down
78 changes: 46 additions & 32 deletions Cabal/Distribution/PackageDescription/Configuration.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,10 +44,8 @@ import Distribution.Compiler
import Distribution.System
import Distribution.Simple.Utils
import Distribution.Text
import Distribution.Compat.Lens
import Distribution.Compat.ReadP as ReadP hiding ( char )
import qualified Distribution.Compat.ReadP as ReadP ( char )
import qualified Distribution.Types.BuildInfo.Lens as L
import Distribution.Types.ComponentRequestedSpec
import Distribution.Types.ForeignLib
import Distribution.Types.Component
Expand Down Expand Up @@ -353,18 +351,18 @@ overallDependencies enabled (TargetSet targets) = mconcat depss
-- | Collect up the targets in a TargetSet of tagged targets, storing the
-- dependencies as we go.
flattenTaggedTargets :: TargetSet PDTagged -> (Maybe Library, [(UnqualComponentName, Component)])
flattenTaggedTargets (TargetSet targets) = foldr untag (Nothing, []) targets where
untag (depMap, pdTagged) accum = case (pdTagged, accum) of
(Lib _, (Just _, _)) -> userBug "Only one library expected"
(Lib l, (Nothing, comps)) -> (Just $ redoBD l, comps)
(SubComp n c, (mb_lib, comps))
| any ((== n) . fst) comps ->
userBug $ "There exist several components with the same name: '" ++ display n ++ "'"
| otherwise -> (mb_lib, (n, redoBD c) : comps)
(PDNull, x) -> x -- actually this should not happen, but let's be liberal
where
redoBD :: L.HasBuildInfo a => a -> a
redoBD = set L.targetBuildDepends $ fromDepMap depMap
flattenTaggedTargets (TargetSet targets) = foldr untag (Nothing, []) targets
where
untag (_, Lib _) (Just _, _) = userBug "Only one library expected"
untag (_, Lib l) (Nothing, comps) = (Just l, comps)
untag (_, SubComp n c) (mb_lib, comps)
| any ((== n) . fst) comps =
userBug $ "There exist several components with the same name: '" ++ unUnqualComponentName n ++ "'"

| otherwise = (mb_lib, (n, c) : comps)

untag (_, PDNull) x = x -- actually this should not happen, but let's be liberal


------------------------------------------------------------------------------
-- Convert GenericPackageDescription to PackageDescription
Expand Down Expand Up @@ -449,6 +447,7 @@ finalizePD userflags enabled satisfyDep
, executables = exes'
, testSuites = tests'
, benchmarks = bms'
, buildDepends = fromDepMap (overallDependencies enabled targetSet)
}
, flagVals )
where
Expand Down Expand Up @@ -518,25 +517,38 @@ flattenPackageDescription
, executables = reverse exes
, testSuites = reverse tests
, benchmarks = reverse bms
, buildDepends = ldeps
++ reverse sub_ldeps
++ reverse pldeps
++ reverse edeps
++ reverse tdeps
++ reverse bdeps
}
where
mlib = f <$> mlib0
where f lib = (libFillInDefaults . fst . ignoreConditions $ lib) { libName = Nothing }
sub_libs = flattenLib <$> sub_libs0
flibs = flattenFLib <$> flibs0
exes = flattenExe <$> exes0
tests = flattenTst <$> tests0
bms = flattenBm <$> bms0
flattenLib (n, t) = libFillInDefaults $ (fst $ ignoreConditions t)
{ libName = Just n, libExposed = False }
flattenFLib (n, t) = flibFillInDefaults $ (fst $ ignoreConditions t)
{ foreignLibName = n }
flattenExe (n, t) = exeFillInDefaults $ (fst $ ignoreConditions t)
{ exeName = n }
flattenTst (n, t) = testFillInDefaults $ (fst $ ignoreConditions t)
{ testName = n }
flattenBm (n, t) = benchFillInDefaults $ (fst $ ignoreConditions t)
{ benchmarkName = n }
(mlib, ldeps) = case mlib0 of
Just lib -> let (l,ds) = ignoreConditions lib in
(Just ((libFillInDefaults l) { libName = Nothing }), ds)
Nothing -> (Nothing, [])
(sub_libs, sub_ldeps) = foldr flattenLib ([],[]) sub_libs0
(flibs, pldeps) = foldr flattenFLib ([],[]) flibs0
(exes, edeps) = foldr flattenExe ([],[]) exes0
(tests, tdeps) = foldr flattenTst ([],[]) tests0
(bms, bdeps) = foldr flattenBm ([],[]) bms0
flattenLib (n, t) (es, ds) =
let (e, ds') = ignoreConditions t in
( (libFillInDefaults $ e { libName = Just n, libExposed = False }) : es, ds' ++ ds )
flattenFLib (n, t) (es, ds) =
let (e, ds') = ignoreConditions t in
( (flibFillInDefaults $ e { foreignLibName = n }) : es, ds' ++ ds )
flattenExe (n, t) (es, ds) =
let (e, ds') = ignoreConditions t in
( (exeFillInDefaults $ e { exeName = n }) : es, ds' ++ ds )
flattenTst (n, t) (es, ds) =
let (e, ds') = ignoreConditions t in
( (testFillInDefaults $ e { testName = n }) : es, ds' ++ ds )
flattenBm (n, t) (es, ds) =
let (e, ds') = ignoreConditions t in
( (benchFillInDefaults $ e { benchmarkName = n }) : es, ds' ++ ds )

-- This is in fact rather a hack. The original version just overrode the
-- default values, however, when adding conditions we had to switch to a
Expand Down Expand Up @@ -608,10 +620,12 @@ transformAllBuildDepends f gpd = gpd'
where
onBI bi = bi { targetBuildDepends = map f $ targetBuildDepends bi }
onSBI stp = stp { setupDepends = map f $ setupDepends stp }
onPD pd = pd { buildDepends = map f $ buildDepends pd }

pd' = onPD $ packageDescription gpd
gpd' = transformAllCondTrees id id id id (map f)
. transformAllBuildInfos onBI onSBI
$ gpd
$ gpd { packageDescription = pd' }

-- | Walk all 'CondTree's inside a 'GenericPackageDescription' and apply
-- appropriate transformations to all nodes. Helper function used by
Expand Down
1 change: 1 addition & 0 deletions Cabal/Distribution/PackageDescription/FieldGrammar.hs
Original file line number Diff line number Diff line change
Expand Up @@ -87,6 +87,7 @@ packageDescriptionFieldGrammar = PackageDescription
<*> optionalFieldDefAla "description" FreeText L.description ""
<*> optionalFieldDefAla "category" FreeText L.category ""
<*> prefixedFields "x-" L.customFieldsPD
<*> pure [] -- build-depends
<*> optionalField "build-type" L.buildTypeRaw
<*> pure Nothing -- custom-setup
-- components
Expand Down
1 change: 1 addition & 0 deletions Cabal/Distribution/Simple/Build.hs
Original file line number Diff line number Diff line change
Expand Up @@ -481,6 +481,7 @@ testSuiteLibV09AsLibAndExe pkg_descr
}
pkg = pkg_descr {
package = (package pkg_descr) { pkgName = mkPackageName $ unMungedPackageName compat_name }
, buildDepends = targetBuildDepends $ testBuildInfo test
, executables = []
, testSuites = []
, subLibraries = [lib]
Expand Down
15 changes: 11 additions & 4 deletions Cabal/Distribution/Simple/Configure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -474,6 +474,15 @@ configure (pkg_descr0, pbi) cfg = do

debug verbosity $ "Finalized package description:\n"
++ showPackageDescription pkg_descr
-- NB: showPackageDescription does not display the AWFUL HACK GLOBAL
-- buildDepends, so we have to display it separately. See #2066
-- Some day, we should eliminate this, so that
-- configureFinalizedPackage returns the set of overall dependencies
-- separately. Then 'configureDependencies' and
-- 'Distribution.PackageDescription.Check' need to be adjusted
-- accordingly.
debug verbosity $ "Finalized build-depends: "
++ intercalate ", " (map display (buildDepends pkg_descr))

checkCompilerProblems verbosity comp pkg_descr enabled
checkPackageProblems verbosity pkg_descr0
Expand Down Expand Up @@ -508,7 +517,6 @@ configure (pkg_descr0, pbi) cfg = do
installedPackageSet
requiredDepsMap
pkg_descr
enabled

-- Compute installation directory templates, based on user
-- configuration.
Expand Down Expand Up @@ -1014,15 +1022,14 @@ configureDependencies
-> InstalledPackageIndex -- ^ installed packages
-> Map PackageName InstalledPackageInfo -- ^ required deps
-> PackageDescription
-> ComponentRequestedSpec
-> IO [PreExistingComponent]
configureDependencies verbosity use_external_internal_deps
internalPackageSet installedPackageSet requiredDepsMap pkg_descr enableSpec = do
internalPackageSet installedPackageSet requiredDepsMap pkg_descr = do
let failedDeps :: [FailedDependency]
allPkgDeps :: [ResolvedDependency]
(failedDeps, allPkgDeps) = partitionEithers
[ (\s -> (dep, s)) <$> status
| dep <- enabledBuildDepends pkg_descr enableSpec
| dep <- buildDepends pkg_descr
, let status = selectDependency (package pkg_descr)
internalPackageSet installedPackageSet
requiredDepsMap use_external_internal_deps dep ]
Expand Down
4 changes: 2 additions & 2 deletions Cabal/Distribution/Types/BuildInfo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -150,7 +150,7 @@ instance Monoid BuildInfo where
staticOptions = [],
customFieldsBI = [],
targetBuildDepends = [],
mixins = []
mixins = []
}
mappend = (<>)

Expand Down Expand Up @@ -196,7 +196,7 @@ instance Semigroup BuildInfo where
staticOptions = combine staticOptions,
customFieldsBI = combine customFieldsBI,
targetBuildDepends = combineNub targetBuildDepends,
mixins = combine mixins
mixins = combine mixins
}
where
combine field = field a `mappend` field b
Expand Down
27 changes: 13 additions & 14 deletions Cabal/Distribution/Types/PackageDescription.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,8 +49,6 @@ module Distribution.Types.PackageDescription (
withForeignLib,
allBuildInfo,
enabledBuildInfos,
allBuildDepends,
enabledBuildDepends,
updatePackageDescription,
pkgComponents,
pkgBuildableComponents,
Expand All @@ -62,8 +60,6 @@ module Distribution.Types.PackageDescription (
import Prelude ()
import Distribution.Compat.Prelude

import Control.Monad ((<=<))

import Distribution.Types.Library
import Distribution.Types.TestSuite
import Distribution.Types.Executable
Expand Down Expand Up @@ -128,6 +124,18 @@ data PackageDescription
-- with x-, stored in a
-- simple assoc-list.

-- | YOU PROBABLY DON'T WANT TO USE THIS FIELD. This field is
-- special! Depending on how far along processing the
-- PackageDescription we are, the contents of this field are
-- either nonsense, or the collected dependencies of *all* the
-- components in this package. buildDepends is initialized by
-- 'finalizePD' and 'flattenPackageDescription';
-- prior to that, dependency info is stored in the 'CondTree'
-- built around a 'GenericPackageDescription'. When this
-- resolution is done, dependency info is written to the inner
-- 'BuildInfo' and this field. This is all horrible, and #2066
-- tracks progress to get rid of this field.
buildDepends :: [Dependency],
-- | The original @build-type@ value as parsed from the
-- @.cabal@ file without defaulting. See also 'buildType'.
--
Expand Down Expand Up @@ -239,6 +247,7 @@ emptyPackageDescription
author = "",
stability = "",
testedWith = [],
buildDepends = [],
homepage = "",
pkgUrl = "",
bugReports = "",
Expand Down Expand Up @@ -383,16 +392,6 @@ enabledBuildInfos pkg enabled =
-- * Utils
-- ------------------------------------------------------------

-- | Get the combined build-depends entries of all components.
allBuildDepends :: PackageDescription -> [Dependency]
allBuildDepends = targetBuildDepends <=< allBuildInfo

-- | Get the combined build-depends entries of all enabled components, per the
-- given request spec.
enabledBuildDepends :: PackageDescription -> ComponentRequestedSpec -> [Dependency]
enabledBuildDepends spec pd = targetBuildDepends =<< enabledBuildInfos spec pd


updatePackageDescription :: HookedBuildInfo -> PackageDescription -> PackageDescription
updatePackageDescription (mb_lib_bi, exe_bi) p
= p{ executables = updateExecutables exe_bi (executables p)
Expand Down
5 changes: 5 additions & 0 deletions Cabal/Distribution/Types/PackageDescription/Lens.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ import Distribution.Compiler (CompilerFlavor)
import Distribution.License (License)
import Distribution.Types.Benchmark (Benchmark)
import Distribution.Types.BuildType (BuildType)
import Distribution.Types.Dependency (Dependency)
import Distribution.Types.Executable (Executable)
import Distribution.Types.ForeignLib (ForeignLib)
import Distribution.Types.Library (Library)
Expand Down Expand Up @@ -88,6 +89,10 @@ customFieldsPD :: Lens' PackageDescription [(String,String)]
customFieldsPD f s = fmap (\x -> s { T.customFieldsPD = x }) (f (T.customFieldsPD s))
{-# INLINE customFieldsPD #-}

buildDepends :: Lens' PackageDescription [Dependency]
buildDepends f s = fmap (\x -> s { T.buildDepends = x }) (f (T.buildDepends s))
{-# INLINE buildDepends #-}

specVersionRaw :: Lens' PackageDescription (Either Version VersionRange)
specVersionRaw f s = fmap (\x -> s { T.specVersionRaw = x }) (f (T.specVersionRaw s))
{-# INLINE specVersionRaw #-}
Expand Down
4 changes: 0 additions & 4 deletions Cabal/changelog
Original file line number Diff line number Diff line change
Expand Up @@ -52,10 +52,6 @@
* Pretty-printing of .cabal files is slightly different due to
parser changes. For an example, see
https://mail.haskell.org/pipermail/cabal-devel/2017-December/010414.html.
* `buildDepends` is removed from `PackageDescription`. It had long been
uselessly hanging about as top-level build-depends already got put
into per-component condition trees anyway. Now it's finally been put
out of its misery.
* `--hyperlink-source` now uses Haddock's hyperlinker backend when
Haddock is new enough, falling back to HsColour otherwise.
* `D.S.defaultHookedPackageDesc` has been deprecated in favour of
Expand Down
1 change: 1 addition & 0 deletions Cabal/tests/ParserTests/regressions/Octree-0.5.expr
Original file line number Diff line number Diff line change
Expand Up @@ -244,6 +244,7 @@ GenericPackageDescription
{author = "Michal J. Gajda",
benchmarks = [],
bugReports = "mailto:[email protected]",
buildDepends = [],
buildTypeRaw = Just Simple,
category = "Data",
copyright = "Copyright by Michal J. Gajda '2012",
Expand Down
1 change: 1 addition & 0 deletions Cabal/tests/ParserTests/regressions/common.expr
Original file line number Diff line number Diff line change
Expand Up @@ -117,6 +117,7 @@ GenericPackageDescription
{author = "",
benchmarks = [],
bugReports = "",
buildDepends = [],
buildTypeRaw = Just Simple,
category = "",
copyright = "",
Expand Down
1 change: 1 addition & 0 deletions Cabal/tests/ParserTests/regressions/common2.expr
Original file line number Diff line number Diff line change
Expand Up @@ -373,6 +373,7 @@ GenericPackageDescription
{author = "",
benchmarks = [],
bugReports = "",
buildDepends = [],
buildTypeRaw = Just Simple,
category = "",
copyright = "",
Expand Down
1 change: 1 addition & 0 deletions Cabal/tests/ParserTests/regressions/elif.expr
Original file line number Diff line number Diff line change
Expand Up @@ -118,6 +118,7 @@ GenericPackageDescription
{author = "",
benchmarks = [],
bugReports = "",
buildDepends = [],
buildTypeRaw = Just Simple,
category = "",
copyright = "",
Expand Down
1 change: 1 addition & 0 deletions Cabal/tests/ParserTests/regressions/elif2.expr
Original file line number Diff line number Diff line change
Expand Up @@ -277,6 +277,7 @@ GenericPackageDescription
{author = "",
benchmarks = [],
bugReports = "",
buildDepends = [],
buildTypeRaw = Just Simple,
category = "",
copyright = "",
Expand Down
1 change: 1 addition & 0 deletions Cabal/tests/ParserTests/regressions/encoding-0.8.expr
Original file line number Diff line number Diff line change
Expand Up @@ -79,6 +79,7 @@ GenericPackageDescription
{author = "",
benchmarks = [],
bugReports = "",
buildDepends = [],
buildTypeRaw = Nothing,
category = "",
copyright = "",
Expand Down
1 change: 1 addition & 0 deletions Cabal/tests/ParserTests/regressions/generics-sop.expr
Original file line number Diff line number Diff line change
Expand Up @@ -554,6 +554,7 @@ GenericPackageDescription
{author = "Edsko de Vries <[email protected]>, Andres L\246h <[email protected]>",
benchmarks = [],
bugReports = "",
buildDepends = [],
buildTypeRaw = Just Custom,
category = "Generics",
copyright = "",
Expand Down
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
'ghc-options: -O2' is rarely needed. Check that it is giving a real benefit and not just imposing longer compile times on your users.
The package uses major bounded version syntax in the 'build-depends' field: base ^>=4.10.0, Cabal ^>=2.0.0, ghc ^>=8.2, ghc-paths ^>=0.1.0.9, xhtml ^>=3000.2.2, ghc ^>=8.2, hspec ^>=2.4.4, QuickCheck ^>=2.10. To use this new syntax the package need to specify at least 'cabal-version: >= 2.0'. Alternatively, if broader compatibility is important then use: base >=4.10.0 && <4.11, Cabal >=2.0.0 && <2.1, ghc >=8.2 && <8.3, ghc-paths >=0.1.0.9 && <0.2, xhtml >=3000.2.2 && <3000.3, ghc >=8.2 && <8.3, hspec >=2.4.4 && <2.5, QuickCheck >=2.10 && <2.11
The package uses major bounded version syntax in the 'build-depends' field: base ^>=4.10.0, Cabal ^>=2.0.0, ghc ^>=8.2, ghc-paths ^>=0.1.0.9, xhtml ^>=3000.2.2, QuickCheck ^>=2.10, hspec ^>=2.4.4, ghc ^>=8.2. To use this new syntax the package need to specify at least 'cabal-version: >= 2.0'. Alternatively, if broader compatibility is important then use: base >=4.10.0 && <4.11, Cabal >=2.0.0 && <2.1, ghc >=8.2 && <8.3, ghc-paths >=0.1.0.9 && <0.2, xhtml >=3000.2.2 && <3000.3, QuickCheck >=2.10 && <2.11, hspec >=2.4.4 && <2.5, ghc >=8.2 && <8.3
1 change: 1 addition & 0 deletions Cabal/tests/ParserTests/regressions/issue-5055.expr
Original file line number Diff line number Diff line change
Expand Up @@ -183,6 +183,7 @@ GenericPackageDescription
{author = "",
benchmarks = [],
bugReports = "",
buildDepends = [],
buildTypeRaw = Just Simple,
category = "Test",
copyright = "",
Expand Down
Loading

0 comments on commit d6831f7

Please sign in to comment.