diff --git a/cabal-install/Distribution/Client/InstallPlan.hs b/cabal-install/Distribution/Client/InstallPlan.hs
index d345b011a9383556f4a9da9d365ec114c4801d30..6e9afb8006079cfa858505384af054bb55047b35 100644
--- a/cabal-install/Distribution/Client/InstallPlan.hs
+++ b/cabal-install/Distribution/Client/InstallPlan.hs
@@ -65,7 +65,9 @@ import Distribution.Version
          ( Version, withinRange )
 import Distribution.PackageDescription
          ( GenericPackageDescription(genPackageFlags)
-         , Flag(flagName), FlagName(..) )
+         , Flag(flagName), FlagName(..)
+         , SetupBuildInfo(..), setupBuildInfo
+         )
 import Distribution.Client.PackageUtils
          ( externalBuildDepends )
 import Distribution.Client.PackageIndex
@@ -637,7 +639,7 @@ configuredPackageProblems platform cinfo
     dependencyName (Dependency name _) = name
 
     mergedDeps :: [MergeResult Dependency PackageId]
-    mergedDeps = mergeDeps requiredDeps (CD.nonSetupDeps specifiedDeps)
+    mergedDeps = mergeDeps requiredDeps (CD.flatDeps specifiedDeps)
 
     mergeDeps :: [Dependency] -> [PackageId] -> [MergeResult Dependency PackageId]
     mergeDeps required specified =
@@ -662,8 +664,11 @@ configuredPackageProblems platform cinfo
          platform cinfo
          []
          (enableStanzas stanzas $ packageDescription pkg) of
-        Right (resolvedPkg, _) -> externalBuildDepends resolvedPkg
-        Left  _ -> error "configuredPackageInvalidDeps internal error"
+        Right (resolvedPkg, _) ->
+             externalBuildDepends resolvedPkg
+          ++ maybe [] setupDepends (setupBuildInfo resolvedPkg)
+        Left  _ ->
+          error "configuredPackageInvalidDeps internal error"
 
 -- | Compute the dependency closure of a _source_ package in a install plan
 --
diff --git a/cabal-install/Distribution/Client/PlanIndex.hs b/cabal-install/Distribution/Client/PlanIndex.hs
index d98d3b9963953353a9ff37e19e9f1de19c6143a5..bc89f7eecc05e024c8c208482f00f06b2f5ac82f 100644
--- a/cabal-install/Distribution/Client/PlanIndex.hs
+++ b/cabal-install/Distribution/Client/PlanIndex.hs
@@ -139,6 +139,7 @@ rootSets :: (PackageFixedDeps pkg, HasInstalledPackageId pkg)
          => FakeMap -> Bool -> PackageIndex pkg -> [[InstalledPackageId]]
 rootSets fakeMap indepGoals index =
        if indepGoals then map (:[]) libRoots else [libRoots]
+    ++ setupRoots index
   where
     libRoots = libraryRoots fakeMap index
 
@@ -156,6 +157,12 @@ libraryRoots fakeMap index =
     roots    = filter isRoot (Graph.vertices graph)
     isRoot v = indegree ! v == 0
 
+-- | The setup dependencies of each package in the plan
+setupRoots :: PackageFixedDeps pkg => PackageIndex pkg -> [[InstalledPackageId]]
+setupRoots = filter (not . null)
+           . map (CD.setupDeps . depends)
+           . allPackages
+
 -- | Given a package index where we assume we want to use all the packages
 -- (use 'dependencyClosure' if you need to get such a index subset) find out
 -- if the dependencies within it use consistent versions of each package.