diff --git a/cabal-install/Distribution/Client/BuildReports/Storage.hs b/cabal-install/Distribution/Client/BuildReports/Storage.hs
index a64bf9068a5993077ffad9c657a4c355af406219..a4f20de32d50b494953b0a75bff2da5ad749049b 100644
--- a/cabal-install/Distribution/Client/BuildReports/Storage.hs
+++ b/cabal-install/Distribution/Client/BuildReports/Storage.hs
@@ -130,13 +130,13 @@ fromPlanPackage :: Platform -> CompilerId
 fromPlanPackage (Platform arch os) comp planPackage = case planPackage of
   InstallPlan.Installed (ReadyPackage srcPkg flags _ deps) result
     -> Just $ ( BuildReport.new os arch comp
-                                (packageId srcPkg) flags (map packageId (CD.flatDeps deps))
+                                (packageId srcPkg) flags (map packageId (CD.nonSetupDeps deps))
                                 (Right result)
               , extractRepo srcPkg)
 
   InstallPlan.Failed (ConfiguredPackage srcPkg flags _ deps) result
     -> Just $ ( BuildReport.new os arch comp
-                                (packageId srcPkg) flags (map confSrcId (CD.flatDeps deps))
+                                (packageId srcPkg) flags (map confSrcId (CD.nonSetupDeps deps))
                                 (Left result)
               , extractRepo srcPkg )
 
diff --git a/cabal-install/Distribution/Client/ComponentDeps.hs b/cabal-install/Distribution/Client/ComponentDeps.hs
index f6ee4d9a7795630348fa565af256084ac26a63a1..ef38a251483566bd7d39acfb2dd3c52fd8dad048 100644
--- a/cabal-install/Distribution/Client/ComponentDeps.hs
+++ b/cabal-install/Distribution/Client/ComponentDeps.hs
@@ -21,10 +21,15 @@ module Distribution.Client.ComponentDeps (
   , singleton
   , insert
   , fromLibraryDeps
+  , fromSetupDeps
   , fromInstalled
     -- ** Deconstructing ComponentDeps
   , toList
   , flatDeps
+  , nonSetupDeps
+  , libraryDeps
+  , setupDeps
+  , select
   ) where
 
 import Data.Map (Map)
@@ -47,6 +52,7 @@ data Component =
   | ComponentExe   String
   | ComponentTest  String
   | ComponentBench String
+  | ComponentSetup
   deriving (Show, Eq, Ord)
 
 -- | Dependency for a single component
@@ -91,6 +97,10 @@ insert comp a = ComponentDeps . Map.alter aux comp . unComponentDeps
 fromLibraryDeps :: a -> ComponentDeps a
 fromLibraryDeps = singleton ComponentLib
 
+-- | ComponentDeps containing setup dependencies only
+fromSetupDeps :: a -> ComponentDeps a
+fromSetupDeps = singleton ComponentSetup
+
 -- | ComponentDeps for installed packages
 --
 -- We assume that installed packages only record their library dependencies
@@ -111,3 +121,22 @@ toList = Map.toList . unComponentDeps
 -- @#ifdef@s for 7.10 just for the use of 'fold'.
 flatDeps :: Monoid a => ComponentDeps a -> a
 flatDeps = fold
+
+-- | All dependencies except the setup dependencies
+--
+-- Prior to the introduction of setup dependencies (TODO: Version? 1.23) this
+-- would have been _all_ dependencies
+nonSetupDeps :: Monoid a => ComponentDeps a -> a
+nonSetupDeps = select (/= ComponentSetup)
+
+-- | Library dependencies proper only
+libraryDeps :: Monoid a => ComponentDeps a -> a
+libraryDeps = select (== ComponentLib)
+
+-- | Setup dependencies
+setupDeps :: Monoid a => ComponentDeps a -> a
+setupDeps = select (== ComponentSetup)
+
+-- | Select dependencies satisfying a given predicate
+select :: Monoid a => (Component -> Bool) -> ComponentDeps a -> a
+select p = foldMap snd . filter (p . fst) . toList
diff --git a/cabal-install/Distribution/Client/Configure.hs b/cabal-install/Distribution/Client/Configure.hs
index aa0d610d097c2fbb3b6444cbcc3fb588a03c2ec8..aadf36a1318450f81e2418c4a0f03589cc6c73f2 100644
--- a/cabal-install/Distribution/Client/Configure.hs
+++ b/cabal-install/Distribution/Client/Configure.hs
@@ -237,10 +237,10 @@ configurePackage verbosity platform comp scriptOptions configFlags
       -- deps.  In the end only one set gets passed to Setup.hs configure,
       -- depending on the Cabal version we are talking to.
       configConstraints  = [ thisPackageVersion (packageId deppkg)
-                           | deppkg <- CD.flatDeps deps ],
+                           | deppkg <- CD.nonSetupDeps deps ],
       configDependencies = [ (packageName (Installed.sourcePackageId deppkg),
                               Installed.installedPackageId deppkg)
-                           | deppkg <- CD.flatDeps deps ],
+                           | deppkg <- CD.nonSetupDeps deps ],
       -- Use '--exact-configuration' if supported.
       configExactConfiguration = toFlag True,
       configVerbosity          = toFlag verbosity,
diff --git a/cabal-install/Distribution/Client/Dependency/Modular/ConfiguredConversion.hs b/cabal-install/Distribution/Client/Dependency/Modular/ConfiguredConversion.hs
index 8a5d4b60602e6a185d4bd41b4fae5583c233aecc..47968d19ec2ba06cca2c760df581b3ff3666e98b 100644
--- a/cabal-install/Distribution/Client/Dependency/Modular/ConfiguredConversion.hs
+++ b/cabal-install/Distribution/Client/Dependency/Modular/ConfiguredConversion.hs
@@ -28,7 +28,7 @@ convCP iidx sidx (CP qpi fa es ds) =
   case convPI qpi of
     Left  pi -> PreExisting $ InstalledPackage
                   (fromJust $ SI.lookupInstalledPackageId iidx pi)
-                  (map confSrcId $ CD.flatDeps ds')
+                  (map confSrcId $ CD.nonSetupDeps ds')
     Right pi -> Configured $ ConfiguredPackage
                   (fromJust $ CI.lookupPackageId sidx pi)
                   fa
diff --git a/cabal-install/Distribution/Client/Dependency/TopDown/Types.hs b/cabal-install/Distribution/Client/Dependency/TopDown/Types.hs
index 6f31385994a2a20771b6c745017754c5f5138ad6..73c1a27327326279290b9c705dd32842f0f23ecd 100644
--- a/cabal-install/Distribution/Client/Dependency/TopDown/Types.hs
+++ b/cabal-install/Distribution/Client/Dependency/TopDown/Types.hs
@@ -115,10 +115,10 @@ instance PackageSourceDeps InstalledPackageEx where
   sourceDeps (InstalledPackageEx _ _ deps) = deps
 
 instance PackageSourceDeps ConfiguredPackage where
-  sourceDeps (ConfiguredPackage _ _ _ deps) = map confSrcId $ CD.flatDeps deps
+  sourceDeps (ConfiguredPackage _ _ _ deps) = map confSrcId $ CD.nonSetupDeps deps
 
 instance PackageSourceDeps ReadyPackage where
-  sourceDeps (ReadyPackage _ _ _ deps) = map packageId $ CD.flatDeps deps
+  sourceDeps (ReadyPackage _ _ _ deps) = map packageId $ CD.nonSetupDeps deps
 
 instance PackageSourceDeps InstalledPackage where
   sourceDeps (InstalledPackage _ deps) = deps
diff --git a/cabal-install/Distribution/Client/Install.hs b/cabal-install/Distribution/Client/Install.hs
index 568d722c26947dbcaeee2238f436b4f7e31a20b6..81a990cb40de3ffbbf4f321d757eac7c707626b7 100644
--- a/cabal-install/Distribution/Client/Install.hs
+++ b/cabal-install/Distribution/Client/Install.hs
@@ -564,8 +564,8 @@ packageStatus _comp installedPkgIndex cpkg =
             -> [MergeResult PackageIdentifier PackageIdentifier]
     changes pkg pkg' = filter changed $
       mergeBy (comparing packageName)
-        (resolveInstalledIds $ Installed.depends pkg)      -- deps of installed pkg
-        (resolveInstalledIds $ CD.flatDeps (depends pkg')) -- deps of configured pkg
+        (resolveInstalledIds $ Installed.depends pkg)          -- deps of installed pkg
+        (resolveInstalledIds $ CD.nonSetupDeps (depends pkg')) -- deps of configured pkg
 
     -- convert to source pkg ids via index
     resolveInstalledIds :: [InstalledPackageId] -> [PackageIdentifier]
@@ -1192,10 +1192,10 @@ installReadyPackage platform cinfo configFlags
     -- In the end only one set gets passed to Setup.hs configure, depending on
     -- the Cabal version we are talking to.
     configConstraints  = [ thisPackageVersion (packageId deppkg)
-                         | deppkg <- CD.flatDeps deps ],
+                         | deppkg <- CD.nonSetupDeps deps ],
     configDependencies = [ (packageName (Installed.sourcePackageId deppkg),
                             Installed.installedPackageId deppkg)
-                         | deppkg <- CD.flatDeps deps ],
+                         | deppkg <- CD.nonSetupDeps deps ],
     -- Use '--exact-configuration' if supported.
     configExactConfiguration = toFlag True,
     configBenchmarks         = toFlag False,
diff --git a/cabal-install/Distribution/Client/InstallPlan.hs b/cabal-install/Distribution/Client/InstallPlan.hs
index 50e593e9559a0bcfcc5a45bf890ad7fd82a26afc..d345b011a9383556f4a9da9d365ec114c4801d30 100644
--- a/cabal-install/Distribution/Client/InstallPlan.hs
+++ b/cabal-install/Distribution/Client/InstallPlan.hs
@@ -495,7 +495,7 @@ problems platform cinfo fakeMap indepGoals index =
 
   ++ [ PackageStateInvalid pkg pkg'
      | pkg <- PackageIndex.allPackages index
-     , Just pkg' <- map (PlanIndex.fakeLookupInstalledPackageId fakeMap index) (CD.flatDeps (depends pkg))
+     , Just pkg' <- map (PlanIndex.fakeLookupInstalledPackageId fakeMap index) (CD.nonSetupDeps (depends pkg))
      , not (stateDependencyRelation pkg pkg') ]
 
 -- | The graph of packages (nodes) and dependencies (edges) must be acyclic.
@@ -616,7 +616,7 @@ configuredPackageProblems platform cinfo
   ++ [ MissingFlag flag | OnlyInLeft  flag <- mergedFlags ]
   ++ [ ExtraFlag   flag | OnlyInRight flag <- mergedFlags ]
   ++ [ DuplicateDeps pkgs
-     | pkgs <- CD.flatDeps (fmap (duplicatesBy (comparing packageName)) specifiedDeps) ]
+     | pkgs <- CD.nonSetupDeps (fmap (duplicatesBy (comparing packageName)) specifiedDeps) ]
   ++ [ MissingDep dep       | OnlyInLeft  dep       <- mergedDeps ]
   ++ [ ExtraDep       pkgid | OnlyInRight     pkgid <- mergedDeps ]
   ++ [ InvalidDep dep pkgid | InBoth      dep pkgid <- mergedDeps
@@ -637,7 +637,7 @@ configuredPackageProblems platform cinfo
     dependencyName (Dependency name _) = name
 
     mergedDeps :: [MergeResult Dependency PackageId]
-    mergedDeps = mergeDeps requiredDeps (CD.flatDeps specifiedDeps)
+    mergedDeps = mergeDeps requiredDeps (CD.nonSetupDeps specifiedDeps)
 
     mergeDeps :: [Dependency] -> [PackageId] -> [MergeResult Dependency PackageId]
     mergeDeps required specified =
diff --git a/cabal-install/Distribution/Client/InstallSymlink.hs b/cabal-install/Distribution/Client/InstallSymlink.hs
index dffc8321cac38240039cfe0c4015c625b8be413f..0ea1921688de2a85164c54fa91c791bf8340beeb 100644
--- a/cabal-install/Distribution/Client/InstallSymlink.hs
+++ b/cabal-install/Distribution/Client/InstallSymlink.hs
@@ -123,7 +123,7 @@ symlinkBinaries comp configFlags installFlags plan =
         | (ReadyPackage _ _flags _ deps, pkg, exe) <- exes
         , let pkgid  = packageId pkg
               pkg_key = mkPackageKey (packageKeySupported comp) pkgid
-                                     (map Installed.packageKey (CD.flatDeps deps)) []
+                                     (map Installed.packageKey (CD.nonSetupDeps deps)) []
               publicExeName  = PackageDescription.exeName exe
               privateExeName = prefix ++ publicExeName ++ suffix
               prefix = substTemplate pkgid pkg_key prefixTemplate
diff --git a/cabal-install/Distribution/Client/PlanIndex.hs b/cabal-install/Distribution/Client/PlanIndex.hs
index 16813b484947d0bffbc939f30ac1667d7570c8b8..d98d3b9963953353a9ff37e19e9f1de19c6143a5 100644
--- a/cabal-install/Distribution/Client/PlanIndex.hs
+++ b/cabal-install/Distribution/Client/PlanIndex.hs
@@ -111,7 +111,7 @@ brokenPackages fakeMap index =
   [ (pkg, missing)
   | pkg  <- allPackages index
   , let missing =
-          [ pkg' | pkg' <- CD.flatDeps (depends pkg)
+          [ pkg' | pkg' <- CD.nonSetupDeps (depends pkg)
                  , isNothing (fakeLookupInstalledPackageId fakeMap index pkg') ]
   , not (null missing) ]
 
@@ -188,7 +188,7 @@ dependencyInconsistencies' fakeMap index =
       | -- For each package @pkg@
         pkg <- allPackages index
         -- Find out which @ipid@ @pkg@ depends on
-      , ipid <- CD.flatDeps (fakeDepends fakeMap pkg)
+      , ipid <- CD.nonSetupDeps (fakeDepends fakeMap pkg)
         -- And look up those @ipid@ (i.e., @ipid@ is the ID of @dep@)
       , Just dep <- [fakeLookupInstalledPackageId fakeMap index ipid]
       ]
@@ -204,8 +204,8 @@ dependencyInconsistencies' fakeMap index =
     reallyIsInconsistent [p1, p2] =
       let pid1 = installedPackageId p1
           pid2 = installedPackageId p2
-      in Map.findWithDefault pid1 pid1 fakeMap `notElem` CD.flatDeps (fakeDepends fakeMap p2)
-      && Map.findWithDefault pid2 pid2 fakeMap `notElem` CD.flatDeps (fakeDepends fakeMap p1)
+      in Map.findWithDefault pid1 pid1 fakeMap `notElem` CD.nonSetupDeps (fakeDepends fakeMap p2)
+      && Map.findWithDefault pid2 pid2 fakeMap `notElem` CD.nonSetupDeps (fakeDepends fakeMap p1)
     reallyIsInconsistent _ = True
 
 
@@ -225,7 +225,7 @@ dependencyCycles :: (PackageFixedDeps pkg, HasInstalledPackageId pkg)
 dependencyCycles fakeMap index =
   [ vs | Graph.CyclicSCC vs <- Graph.stronglyConnComp adjacencyList ]
   where
-    adjacencyList = [ (pkg, installedPackageId pkg, CD.flatDeps (fakeDepends fakeMap pkg))
+    adjacencyList = [ (pkg, installedPackageId pkg, CD.nonSetupDeps (fakeDepends fakeMap pkg))
                     | pkg <- allPackages index ]
 
 
@@ -256,7 +256,7 @@ dependencyClosure fakeMap index pkgids0 = case closure mempty [] pkgids0 of
             Just _  -> closure completed  failed pkgids
             Nothing -> closure completed' failed pkgids'
               where completed' = insert pkg completed
-                    pkgids'    = CD.flatDeps (depends pkg) ++ pkgids
+                    pkgids'    = CD.nonSetupDeps (depends pkg) ++ pkgids
 
 
 topologicalOrder :: (PackageFixedDeps pkg, HasInstalledPackageId pkg)
@@ -322,5 +322,5 @@ dependencyGraph fakeMap index = (graph, vertexToPkg, idToVertex)
     resolve   pid = Map.findWithDefault pid pid fakeMap
     edgesFrom pkg = ( ()
                     , resolve (installedPackageId pkg)
-                    , CD.flatDeps (fakeDepends fakeMap pkg)
+                    , CD.nonSetupDeps (fakeDepends fakeMap pkg)
                     )
diff --git a/cabal-install/Distribution/Client/Types.hs b/cabal-install/Distribution/Client/Types.hs
index 1c349b84ce9bce911a687aa5f240ae368bbee6ce..cf9802610791dfd9b0bcde390d9c15530672152d 100644
--- a/cabal-install/Distribution/Client/Types.hs
+++ b/cabal-install/Distribution/Client/Types.hs
@@ -154,7 +154,7 @@ instance HasInstalledPackageId ReadyPackage where
 readyPackageKey :: Compiler -> ReadyPackage -> PackageKey
 readyPackageKey comp (ReadyPackage pkg _ _ deps) =
     mkPackageKey (packageKeySupported comp) (packageId pkg)
-                 (map Info.packageKey (CD.flatDeps deps)) []
+                 (map Info.packageKey (CD.nonSetupDeps deps)) []
 
 
 -- | Sometimes we need to convert a 'ReadyPackage' back to a