diff --git a/Cabal/Distribution/PackageDescription.hs b/Cabal/Distribution/PackageDescription.hs
index bd3f8141f9715e88650c59644f87e14b621f5757..4085278e6c76631914ee9a9cae8ce48612274d35 100644
--- a/Cabal/Distribution/PackageDescription.hs
+++ b/Cabal/Distribution/PackageDescription.hs
@@ -83,8 +83,6 @@ module Distribution.PackageDescription (
         hcStaticOptions,
 
         -- ** Supplementary build information
-        allBuildDepends,
-        enabledBuildDepends,
         ComponentName(..),
         defaultLibName,
         HookedBuildInfo,
diff --git a/Cabal/Distribution/PackageDescription/Check.hs b/Cabal/Distribution/PackageDescription/Check.hs
index e3d27e4acef32ad49a81a680dbfff83ffe8cd26e..25615b274aad28d39a53113885b08b34ea44ad16 100644
--- a/Cabal/Distribution/PackageDescription/Check.hs
+++ b/Cabal/Distribution/PackageDescription/Check.hs
@@ -1363,7 +1363,7 @@ checkCabalVersion pkg =
       _                   -> False
 
     versionRangeExpressions =
-        [ dep | dep@(Dependency _ vr) <- allBuildDepends pkg
+        [ dep | dep@(Dependency _ vr) <- buildDepends pkg
               , usesNewVersionRangeSyntax vr ]
 
     testedWithVersionRangeExpressions =
@@ -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)
@@ -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,
diff --git a/Cabal/Distribution/PackageDescription/Configuration.hs b/Cabal/Distribution/PackageDescription/Configuration.hs
index e97d9dad04f2d10a8b368d899430caf87c164d7e..64771037612042d4eef4303f562165955cfc0516 100644
--- a/Cabal/Distribution/PackageDescription/Configuration.hs
+++ b/Cabal/Distribution/PackageDescription/Configuration.hs
@@ -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
@@ -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
@@ -449,6 +447,7 @@ finalizePD userflags enabled satisfyDep
                , executables = exes'
                , testSuites = tests'
                , benchmarks = bms'
+               , buildDepends = fromDepMap (overallDependencies enabled targetSet)
                }
          , flagVals )
   where
@@ -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
@@ -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
diff --git a/Cabal/Distribution/PackageDescription/FieldGrammar.hs b/Cabal/Distribution/PackageDescription/FieldGrammar.hs
index a6251a114ec688dc5c83e5d06545218fedd1c4bc..0032d59f1b5503693d751d5293bcfdf63b515e3f 100644
--- a/Cabal/Distribution/PackageDescription/FieldGrammar.hs
+++ b/Cabal/Distribution/PackageDescription/FieldGrammar.hs
@@ -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
diff --git a/Cabal/Distribution/Simple/Build.hs b/Cabal/Distribution/Simple/Build.hs
index cbe766d315a9ffb4ac1216253f430a7ef340efbf..2521243551e20d634ec7504b5dd3cddf59df29b1 100644
--- a/Cabal/Distribution/Simple/Build.hs
+++ b/Cabal/Distribution/Simple/Build.hs
@@ -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]
diff --git a/Cabal/Distribution/Simple/Configure.hs b/Cabal/Distribution/Simple/Configure.hs
index 69f8bacbfb4e67bbcfab7c5eb92d0f1adb952422..285bcd5652fdea076ced7215d099e4aaa74dc28b 100644
--- a/Cabal/Distribution/Simple/Configure.hs
+++ b/Cabal/Distribution/Simple/Configure.hs
@@ -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
@@ -508,7 +517,6 @@ configure (pkg_descr0, pbi) cfg = do
                 installedPackageSet
                 requiredDepsMap
                 pkg_descr
-                enabled
 
     -- Compute installation directory templates, based on user
     -- configuration.
@@ -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 ]
diff --git a/Cabal/Distribution/Types/BuildInfo.hs b/Cabal/Distribution/Types/BuildInfo.hs
index 7685270d77f0c4a52cd6a31616b733fcd09218cc..92d2021f7cc3197c14e1985cef95ce7efac57427 100644
--- a/Cabal/Distribution/Types/BuildInfo.hs
+++ b/Cabal/Distribution/Types/BuildInfo.hs
@@ -150,7 +150,7 @@ instance Monoid BuildInfo where
     staticOptions       = [],
     customFieldsBI      = [],
     targetBuildDepends  = [],
-    mixins              = []
+    mixins    = []
   }
   mappend = (<>)
 
@@ -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
diff --git a/Cabal/Distribution/Types/PackageDescription.hs b/Cabal/Distribution/Types/PackageDescription.hs
index 482093bfdbacdb729a2d47d37496254a694d180c..b9dd51735c6f54a23e0c7bdbdae3ca42d46e5dcd 100644
--- a/Cabal/Distribution/Types/PackageDescription.hs
+++ b/Cabal/Distribution/Types/PackageDescription.hs
@@ -49,8 +49,6 @@ module Distribution.Types.PackageDescription (
     withForeignLib,
     allBuildInfo,
     enabledBuildInfos,
-    allBuildDepends,
-    enabledBuildDepends,
     updatePackageDescription,
     pkgComponents,
     pkgBuildableComponents,
@@ -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
@@ -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'.
         --
@@ -239,6 +247,7 @@ emptyPackageDescription
                       author       = "",
                       stability    = "",
                       testedWith   = [],
+                      buildDepends = [],
                       homepage     = "",
                       pkgUrl       = "",
                       bugReports   = "",
@@ -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)
diff --git a/Cabal/Distribution/Types/PackageDescription/Lens.hs b/Cabal/Distribution/Types/PackageDescription/Lens.hs
index e08dbc4584856675dc8e5c70d5c13baebe577c83..6594b9953377397e71eb37e96d66d5e2df88d796 100644
--- a/Cabal/Distribution/Types/PackageDescription/Lens.hs
+++ b/Cabal/Distribution/Types/PackageDescription/Lens.hs
@@ -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)
@@ -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 #-}
diff --git a/Cabal/changelog b/Cabal/changelog
index e74bbab5f552722e2ec76217a4824c443329a5ee..13a4916bbcfddb6a972636d9b09ef676a3281f7a 100644
--- a/Cabal/changelog
+++ b/Cabal/changelog
@@ -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
diff --git a/Cabal/tests/ParserTests/regressions/Octree-0.5.expr b/Cabal/tests/ParserTests/regressions/Octree-0.5.expr
index 7c3b45ceb6d87610a42f224561b779408596285f..1591c75da33865b9be478c8499bee2636f4107ad 100644
--- a/Cabal/tests/ParserTests/regressions/Octree-0.5.expr
+++ b/Cabal/tests/ParserTests/regressions/Octree-0.5.expr
@@ -244,6 +244,7 @@ GenericPackageDescription
                           {author = "Michal J. Gajda",
                            benchmarks = [],
                            bugReports = "mailto:mjgajda@googlemail.com",
+                           buildDepends = [],
                            buildTypeRaw = Just Simple,
                            category = "Data",
                            copyright = "Copyright by Michal J. Gajda '2012",
diff --git a/Cabal/tests/ParserTests/regressions/common.expr b/Cabal/tests/ParserTests/regressions/common.expr
index 01b7ad3662d05a54fd07728e03b1163a3a05875b..9341df23fd1fbaff848bdf919b51587ebec2ee26 100644
--- a/Cabal/tests/ParserTests/regressions/common.expr
+++ b/Cabal/tests/ParserTests/regressions/common.expr
@@ -117,6 +117,7 @@ GenericPackageDescription
                           {author = "",
                            benchmarks = [],
                            bugReports = "",
+                           buildDepends = [],
                            buildTypeRaw = Just Simple,
                            category = "",
                            copyright = "",
diff --git a/Cabal/tests/ParserTests/regressions/common2.expr b/Cabal/tests/ParserTests/regressions/common2.expr
index d8fe2546acda02765fac456323f4caf9a02952d8..bb88b42870488c56649960d5b9c5cb372c400bba 100644
--- a/Cabal/tests/ParserTests/regressions/common2.expr
+++ b/Cabal/tests/ParserTests/regressions/common2.expr
@@ -373,6 +373,7 @@ GenericPackageDescription
                           {author = "",
                            benchmarks = [],
                            bugReports = "",
+                           buildDepends = [],
                            buildTypeRaw = Just Simple,
                            category = "",
                            copyright = "",
diff --git a/Cabal/tests/ParserTests/regressions/elif.expr b/Cabal/tests/ParserTests/regressions/elif.expr
index ae39c7d3e0ddc2dbbac07e10b64d1b9cefbab0e7..09e8d6f7049f100ec60a47a789c784dd424c4e14 100644
--- a/Cabal/tests/ParserTests/regressions/elif.expr
+++ b/Cabal/tests/ParserTests/regressions/elif.expr
@@ -118,6 +118,7 @@ GenericPackageDescription
                           {author = "",
                            benchmarks = [],
                            bugReports = "",
+                           buildDepends = [],
                            buildTypeRaw = Just Simple,
                            category = "",
                            copyright = "",
diff --git a/Cabal/tests/ParserTests/regressions/elif2.expr b/Cabal/tests/ParserTests/regressions/elif2.expr
index 19511897387d11cf7512e720c82cd359c4f00680..a76f5cf3d6b2093090884a6c290e1b9f2418a880 100644
--- a/Cabal/tests/ParserTests/regressions/elif2.expr
+++ b/Cabal/tests/ParserTests/regressions/elif2.expr
@@ -277,6 +277,7 @@ GenericPackageDescription
                           {author = "",
                            benchmarks = [],
                            bugReports = "",
+                           buildDepends = [],
                            buildTypeRaw = Just Simple,
                            category = "",
                            copyright = "",
diff --git a/Cabal/tests/ParserTests/regressions/encoding-0.8.expr b/Cabal/tests/ParserTests/regressions/encoding-0.8.expr
index 889650974a31269db99af7d69781992cd7a0c67c..76fe659803af2554898034a754d1bba197481762 100644
--- a/Cabal/tests/ParserTests/regressions/encoding-0.8.expr
+++ b/Cabal/tests/ParserTests/regressions/encoding-0.8.expr
@@ -79,6 +79,7 @@ GenericPackageDescription
                           {author = "",
                            benchmarks = [],
                            bugReports = "",
+                           buildDepends = [],
                            buildTypeRaw = Nothing,
                            category = "",
                            copyright = "",
diff --git a/Cabal/tests/ParserTests/regressions/generics-sop.expr b/Cabal/tests/ParserTests/regressions/generics-sop.expr
index f99eaedd49778d715f487e143a47dd44e21089d0..a26d2bfbe5ceffad124e467ffbf82c58f887ba1e 100644
--- a/Cabal/tests/ParserTests/regressions/generics-sop.expr
+++ b/Cabal/tests/ParserTests/regressions/generics-sop.expr
@@ -554,6 +554,7 @@ GenericPackageDescription
                           {author = "Edsko de Vries <edsko@well-typed.com>, Andres L\246h <andres@well-typed.com>",
                            benchmarks = [],
                            bugReports = "",
+                           buildDepends = [],
                            buildTypeRaw = Just Custom,
                            category = "Generics",
                            copyright = "",
diff --git a/Cabal/tests/ParserTests/regressions/haddock-api-2.18.1-check.check b/Cabal/tests/ParserTests/regressions/haddock-api-2.18.1-check.check
index c95a5ebc74a5edbaa2b0a18ca18387e919c59927..b9d2e11cbcbf41b68398522a3130c7926e4fed23 100644
--- a/Cabal/tests/ParserTests/regressions/haddock-api-2.18.1-check.check
+++ b/Cabal/tests/ParserTests/regressions/haddock-api-2.18.1-check.check
@@ -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
diff --git a/Cabal/tests/ParserTests/regressions/issue-5055.expr b/Cabal/tests/ParserTests/regressions/issue-5055.expr
index c7ce614e3905223a70f33d6d25ff8cf327d9b523..a1e234adc4eab59851db19f83d912df958da4cd6 100644
--- a/Cabal/tests/ParserTests/regressions/issue-5055.expr
+++ b/Cabal/tests/ParserTests/regressions/issue-5055.expr
@@ -183,6 +183,7 @@ GenericPackageDescription
                           {author = "",
                            benchmarks = [],
                            bugReports = "",
+                           buildDepends = [],
                            buildTypeRaw = Just Simple,
                            category = "Test",
                            copyright = "",
diff --git a/Cabal/tests/ParserTests/regressions/issue-774.expr b/Cabal/tests/ParserTests/regressions/issue-774.expr
index 5cda458c27cb152e546fa7e4fe9f348202c6ec0d..29380faadb40224e599851b0d9e7472745f590c0 100644
--- a/Cabal/tests/ParserTests/regressions/issue-774.expr
+++ b/Cabal/tests/ParserTests/regressions/issue-774.expr
@@ -66,6 +66,7 @@ GenericPackageDescription
                           {author = "",
                            benchmarks = [],
                            bugReports = "",
+                           buildDepends = [],
                            buildTypeRaw = Just Simple,
                            category = "",
                            copyright = "",
diff --git a/Cabal/tests/ParserTests/regressions/leading-comma.expr b/Cabal/tests/ParserTests/regressions/leading-comma.expr
index 4b9b892a42021da5962ff19eea8cafaaa8ed0e85..71644e8cd67aa4533d2abff4904d0ab4dc1c96c0 100644
--- a/Cabal/tests/ParserTests/regressions/leading-comma.expr
+++ b/Cabal/tests/ParserTests/regressions/leading-comma.expr
@@ -83,6 +83,7 @@ GenericPackageDescription
                           {author = "",
                            benchmarks = [],
                            bugReports = "",
+                           buildDepends = [],
                            buildTypeRaw = Just Simple,
                            category = "",
                            copyright = "",
diff --git a/Cabal/tests/ParserTests/regressions/nothing-unicode.expr b/Cabal/tests/ParserTests/regressions/nothing-unicode.expr
index 3fd9b4820df2c29ddd5f4ae6685f81f950a174fc..6a544a5dcf8ff9c92c34eacf73911a8a1b99d656 100644
--- a/Cabal/tests/ParserTests/regressions/nothing-unicode.expr
+++ b/Cabal/tests/ParserTests/regressions/nothing-unicode.expr
@@ -118,6 +118,7 @@ GenericPackageDescription
                           {author = "",
                            benchmarks = [],
                            bugReports = "",
+                           buildDepends = [],
                            buildTypeRaw = Just Simple,
                            category = "",
                            copyright = "",
diff --git a/Cabal/tests/ParserTests/regressions/shake.expr b/Cabal/tests/ParserTests/regressions/shake.expr
index a3efa683b6e708d968f05503b3f7a68ab6b2b2dd..b0927b700256418194097df8c792c14f449ff046 100644
--- a/Cabal/tests/ParserTests/regressions/shake.expr
+++ b/Cabal/tests/ParserTests/regressions/shake.expr
@@ -1630,6 +1630,7 @@ GenericPackageDescription
                           {author = "Neil Mitchell <ndmitchell@gmail.com>",
                            benchmarks = [],
                            bugReports = "https://github.com/ndmitchell/shake/issues",
+                           buildDepends = [],
                            buildTypeRaw = Just Simple,
                            category = "Development, Shake",
                            copyright = "Neil Mitchell 2011-2017",
diff --git a/Cabal/tests/ParserTests/regressions/th-lift-instances.expr b/Cabal/tests/ParserTests/regressions/th-lift-instances.expr
index 0621e9c3ef07909a4c2c2e7c5b759f5311af554a..273ad24bea84e5003082226e55ffeb77b7933556 100644
--- a/Cabal/tests/ParserTests/regressions/th-lift-instances.expr
+++ b/Cabal/tests/ParserTests/regressions/th-lift-instances.expr
@@ -386,6 +386,7 @@ GenericPackageDescription
                           {author = "Benno F\252nfst\252ck",
                            benchmarks = [],
                            bugReports = "http://github.com/bennofs/th-lift-instances/issues",
+                           buildDepends = [],
                            buildTypeRaw = Just Custom,
                            category = "Template Haskell",
                            copyright = "Copyright (C) 2013-2014 Benno F\252nfst\252ck",
diff --git a/Cabal/tests/ParserTests/regressions/wl-pprint-indef.expr b/Cabal/tests/ParserTests/regressions/wl-pprint-indef.expr
index 021191dcc385bd12e13eb791590cb21ef08d33af..371992839595c60a4f5ddda9d5cf5695df7c25d9 100644
--- a/Cabal/tests/ParserTests/regressions/wl-pprint-indef.expr
+++ b/Cabal/tests/ParserTests/regressions/wl-pprint-indef.expr
@@ -140,6 +140,7 @@ GenericPackageDescription
                           {author = "Daan Leijen",
                            benchmarks = [],
                            bugReports = "",
+                           buildDepends = [],
                            buildTypeRaw = Just Simple,
                            category = "Text",
                            copyright = "",
diff --git a/cabal-install/Distribution/Client/Dependency.hs b/cabal-install/Distribution/Client/Dependency.hs
index f13777ab0b5f11c4ae8228c1ccc28d535616eff7..e3eff39577998ee307bd16d088a4ef6581fde7cf 100644
--- a/cabal-install/Distribution/Client/Dependency.hs
+++ b/cabal-install/Distribution/Client/Dependency.hs
@@ -930,24 +930,24 @@ configuredPackageProblems platform cinfo
         (sortNubOn dependencyName required)
         (sortNubOn packageName    specified)
 
-    compSpec = enableStanzas stanzas
     -- TODO: It would be nicer to use ComponentDeps here so we can be more
-    -- precise in our checks. In fact, this no longer relies on buildDepends and
-    -- thus should be easier to fix. As long as we _do_ use a flat list here, we
-    -- have to allow for duplicates when we fold specifiedDeps; once we have
-    -- proper ComponentDeps here we should get rid of the `nubOn` in
-    -- `mergeDeps`.
+    -- precise in our checks. That's a bit tricky though, as this currently
+    -- relies on the 'buildDepends' field of 'PackageDescription'. (OTOH, that
+    -- field is deprecated and should be removed anyway.)  As long as we _do_
+    -- use a flat list here, we have to allow for duplicates when we fold
+    -- specifiedDeps; once we have proper ComponentDeps here we should get rid
+    -- of the `nubOn` in `mergeDeps`.
     requiredDeps :: [Dependency]
     requiredDeps =
       --TODO: use something lower level than finalizePD
       case finalizePD specifiedFlags
-         compSpec
+         (enableStanzas stanzas)
          (const True)
          platform cinfo
          []
          (packageDescription pkg) of
         Right (resolvedPkg, _) ->
-             externalBuildDepends resolvedPkg compSpec
+             externalBuildDepends resolvedPkg
           ++ maybe [] PD.setupDepends (PD.setupBuildInfo resolvedPkg)
         Left  _ ->
           error "configuredPackageInvalidDeps internal error"
diff --git a/cabal-install/Distribution/Client/GenBounds.hs b/cabal-install/Distribution/Client/GenBounds.hs
index 0f2727ad2fcecb6b43985729934d4de9e8390170..139e05b9dae521b91e69e7a572a97ad919ccd979 100644
--- a/cabal-install/Distribution/Client/GenBounds.hs
+++ b/cabal-install/Distribution/Client/GenBounds.hs
@@ -29,7 +29,7 @@ import Distribution.Client.Setup
 import Distribution.Package
          ( Package(..), unPackageName, packageName, packageVersion )
 import Distribution.PackageDescription
-         ( enabledBuildDepends )
+         ( buildDepends )
 import Distribution.PackageDescription.Configuration
          ( finalizePD )
 import Distribution.PackageDescription.Parsec
@@ -122,7 +122,7 @@ genBounds verbosity packageDBs repoCtxt comp platform progdb mSandboxPkgInfo
       Left _ -> putStrLn "finalizePD failed"
       Right (pd,_) -> do
         let needBounds = filter (not . hasUpperBound . depVersion) $
-                         enabledBuildDepends pd defaultComponentRequestedSpec
+                         buildDepends pd
 
         if (null needBounds)
           then putStrLn
diff --git a/cabal-install/Distribution/Client/List.hs b/cabal-install/Distribution/Client/List.hs
index 5a72ce7a709557573bd8e3c742ac5d56cffb36d7..65d43b6522c68a9407a4512fc080027986af1b8b 100644
--- a/cabal-install/Distribution/Client/List.hs
+++ b/cabal-install/Distribution/Client/List.hs
@@ -470,7 +470,7 @@ mergePackageInfo versionPref installedPkgs sourcePkgs selectedPkg showVer =
                            source,
     dependencies =
       combine (map (SourceDependency . simplifyDependency)
-               . Source.allBuildDepends) source
+               . Source.buildDepends) source
       (map InstalledDependency . Installed.depends) installed,
     haddockHtml  = fromMaybe "" . join
                  . fmap (listToMaybe . Installed.haddockHTMLs)
diff --git a/cabal-install/Distribution/Client/Outdated.hs b/cabal-install/Distribution/Client/Outdated.hs
index 8ec0d63bea98800b554add6fe932f88f98d197b6..9f0bcc0f2ff4e02d9385b23a751a1e7ab23051a5 100644
--- a/cabal-install/Distribution/Client/Outdated.hs
+++ b/cabal-install/Distribution/Client/Outdated.hs
@@ -27,8 +27,9 @@ import Distribution.Solver.Types.PackageConstraint
 import Distribution.Solver.Types.PackageIndex
 import Distribution.Client.Sandbox.PackageEnvironment
 
-import Distribution.Package                          (PackageName, packageVersion)
-import Distribution.PackageDescription               (allBuildDepends)
+import Distribution.Package                          (PackageName
+                                                     ,packageVersion)
+import Distribution.PackageDescription               (buildDepends)
 import Distribution.PackageDescription.Configuration (finalizePD)
 import Distribution.Simple.Compiler                  (Compiler, compilerInfo)
 import Distribution.Simple.Setup                     (fromFlagOrDefault)
@@ -151,7 +152,7 @@ depsFromPkgDesc verbosity comp platform = do
   case epd of
     Left _        -> die' verbosity "finalizePD failed"
     Right (pd, _) -> do
-      let bd = allBuildDepends pd
+      let bd = buildDepends pd
       debug verbosity
         "Reading the list of dependencies from the package description"
       return bd
diff --git a/cabal-install/Distribution/Client/PackageUtils.hs b/cabal-install/Distribution/Client/PackageUtils.hs
index b1236fb38b11430a7e638aaf224fbd617c1634ce..4f4609973869106b7a8887cd860f459aaa8c808b 100644
--- a/cabal-install/Distribution/Client/PackageUtils.hs
+++ b/cabal-install/Distribution/Client/PackageUtils.hs
@@ -16,20 +16,18 @@ module Distribution.Client.PackageUtils (
 
 import Distribution.Package
          ( packageVersion, packageName )
-import Distribution.Types.ComponentRequestedSpec
-         ( ComponentRequestedSpec )
 import Distribution.Types.Dependency
 import Distribution.Types.UnqualComponentName
 import Distribution.PackageDescription
-         ( PackageDescription(..), libName, enabledBuildDepends )
+         ( PackageDescription(..), libName )
 import Distribution.Version
          ( withinRange, isAnyVersion )
 
 -- | The list of dependencies that refer to external packages
 -- rather than internal package components.
 --
-externalBuildDepends :: PackageDescription -> ComponentRequestedSpec -> [Dependency]
-externalBuildDepends pkg spec = filter (not . internal) (enabledBuildDepends pkg spec)
+externalBuildDepends :: PackageDescription -> [Dependency]
+externalBuildDepends pkg = filter (not . internal) (buildDepends pkg)
   where
     -- True if this dependency is an internal one (depends on a library
     -- defined in the same package).
diff --git a/cabal-testsuite/PackageTests/Backpack/Includes2/cabal-internal.out b/cabal-testsuite/PackageTests/Backpack/Includes2/cabal-internal.out
index 36f513582b22e78f5fcffe3925fa325365d7764b..412950ed677a5306be6cb0fac6ac6977388ba9a6 100644
--- a/cabal-testsuite/PackageTests/Backpack/Includes2/cabal-internal.out
+++ b/cabal-testsuite/PackageTests/Backpack/Includes2/cabal-internal.out
@@ -34,11 +34,9 @@ Building library 'mylib' instantiated with
   Database = Includes2-0.1.0.0-inplace-postgresql:Database.PostgreSQL
 for Includes2-0.1.0.0..
 Configuring library for Includes2-0.1.0.0..
-Warning: The package has an extraneous version range for a dependency on an internal library: Includes2 -any && ==0.1.0.0 && ==0.1.0.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 library for Includes2-0.1.0.0..
 Building library for Includes2-0.1.0.0..
 Configuring executable 'exe' for Includes2-0.1.0.0..
-Warning: The package has an extraneous version range for a dependency on an internal library: Includes2 -any && ==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 'exe' for Includes2-0.1.0.0..
 Building executable 'exe' for Includes2-0.1.0.0..
 # Includes2 exe
diff --git a/cabal-testsuite/PackageTests/BuildTools/Internal/cabal.out b/cabal-testsuite/PackageTests/BuildTools/Internal/cabal.out
index 90464eb31d80fba1bd914992305f3ca55014b230..4486c7aab9b66b2c757360f14b4a81358e9bbd8b 100644
--- a/cabal-testsuite/PackageTests/BuildTools/Internal/cabal.out
+++ b/cabal-testsuite/PackageTests/BuildTools/Internal/cabal.out
@@ -12,6 +12,5 @@ Configuring library for foo-0.1.0.0..
 Preprocessing library for foo-0.1.0.0..
 Building library for foo-0.1.0.0..
 Configuring executable 'hello-world' for foo-0.1.0.0..
-Warning: The package has an extraneous version range for a dependency on an internal library: foo -any && ==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 'hello-world' for foo-0.1.0.0..
 Building executable 'hello-world' for foo-0.1.0.0..
diff --git a/cabal-testsuite/PackageTests/TestSuiteTests/ExeV10/cabal.out b/cabal-testsuite/PackageTests/TestSuiteTests/ExeV10/cabal.out
index b1ccd8f66fc2f9c321f4054fa9ceca40266c217a..a8318f25d5356343a5024f58b1f4ee5d316b10da 100644
--- a/cabal-testsuite/PackageTests/TestSuiteTests/ExeV10/cabal.out
+++ b/cabal-testsuite/PackageTests/TestSuiteTests/ExeV10/cabal.out
@@ -9,7 +9,6 @@ Configuring library for my-0.1..
 Preprocessing library for my-0.1..
 Building library for my-0.1..
 Configuring test suite 'test-Short' for my-0.1..
-Warning: The package has an extraneous version range for a dependency on an internal library: my -any && ==0.1, my -any && ==0.1. This version range includes the current package but isn't needed as the current package's library will always be used.
 Preprocessing test suite 'test-Short' for my-0.1..
 Building test suite 'test-Short' for my-0.1..
 Running 1 test suites...
@@ -18,7 +17,6 @@ Test suite test-Short: PASS
 Test suite logged to: <ROOT>/cabal.dist/work/./dist/build/<ARCH>/ghc-<GHCVER>/my-0.1/t/test-Short/test/my-0.1-test-Short.log
 1 of 1 test suites (1 of 1 test cases) passed.
 Configuring test suite 'test-Foo' for my-0.1..
-Warning: The package has an extraneous version range for a dependency on an internal library: my -any && ==0.1, my -any && ==0.1. This version range includes the current package but isn't needed as the current package's library will always be used.
 Preprocessing test suite 'test-Foo' for my-0.1..
 Building test suite 'test-Foo' for my-0.1..
 Running 1 test suites...