diff --git a/cabal-install/Distribution/Client/BuildReports/Storage.hs b/cabal-install/Distribution/Client/BuildReports/Storage.hs
index 10c7df7e3d1cf45eedd963a1f9003d4a3a6cf41b..20a4cc584711f222d5a87ae99287aabdebe744fe 100644
--- a/cabal-install/Distribution/Client/BuildReports/Storage.hs
+++ b/cabal-install/Distribution/Client/BuildReports/Storage.hs
@@ -135,7 +135,7 @@ fromPlanPackage (Platform arch os) comp planPackage = case planPackage of
 
   InstallPlan.Failed (ConfiguredPackage srcPkg flags _ deps) result
     -> Just $ ( BuildReport.new os arch comp
-                                (packageId srcPkg) flags deps
+                                (packageId srcPkg) flags (map confSrcId deps)
                                 (Left result)
               , extractRepo srcPkg )
 
diff --git a/cabal-install/Distribution/Client/Dependency/Modular/ConfiguredConversion.hs b/cabal-install/Distribution/Client/Dependency/Modular/ConfiguredConversion.hs
index b99f90fce25beffdcf35c85ed79bd58610234197..97d22a52d99385e85c641047fd43fb71830884b3 100644
--- a/cabal-install/Distribution/Client/Dependency/Modular/ConfiguredConversion.hs
+++ b/cabal-install/Distribution/Client/Dependency/Modular/ConfiguredConversion.hs
@@ -25,16 +25,27 @@ convCP iidx sidx (CP qpi fa es ds) =
   case convPI qpi of
     Left  pi -> PreExisting $ InstalledPackage
                   (fromJust $ SI.lookupInstalledPackageId iidx pi)
-                  (map convPI' ds)
+                  (map confSrcId ds')
     Right pi -> Configured $ ConfiguredPackage
                   (fromJust $ CI.lookupPackageId sidx pi)
                   fa
                   es
-                  (map convPI' ds)
+                  ds'
+  where
+    ds' :: [ConfiguredId]
+    ds' = map convConfId ds
 
 convPI :: PI QPN -> Either InstalledPackageId PackageId
 convPI (PI _ (I _ (Inst pi))) = Left pi
-convPI qpi                    = Right $ convPI' qpi
+convPI qpi                    = Right $ confSrcId $ convConfId qpi
 
-convPI' :: PI QPN -> PackageId
-convPI' (PI (Q _ pn) (I v _))  = PackageIdentifier pn v
+convConfId :: PI QPN -> ConfiguredId
+convConfId (PI (Q _ pn) (I v loc)) = ConfiguredId {
+      confSrcId  = sourceId
+    , confInstId = installedId
+    }
+  where
+    sourceId    = PackageIdentifier pn v
+    installedId = case loc of
+                    Inst pi    -> pi
+                    _otherwise -> fakeInstalledPackageId sourceId
diff --git a/cabal-install/Distribution/Client/Dependency/TopDown.hs b/cabal-install/Distribution/Client/Dependency/TopDown.hs
index a4a083473e3f7acf17151059ff573ffb65b23e23..a6f75e6090e1be49998e4ddb9a34b19a119fe599 100644
--- a/cabal-install/Distribution/Client/Dependency/TopDown.hs
+++ b/cabal-install/Distribution/Client/Dependency/TopDown.hs
@@ -26,7 +26,7 @@ import Distribution.Client.InstallPlan
          ( PlanPackage(..) )
 import Distribution.Client.Types
          ( SourcePackage(..), ConfiguredPackage(..), InstalledPackage(..)
-         , enableStanzas )
+         , enableStanzas, ConfiguredId(..), fakeInstalledPackageId )
 import Distribution.Client.Dependency.Types
          ( DependencyResolver, PackageConstraint(..)
          , PackagePreferences(..), InstalledPreference(..)
@@ -562,7 +562,38 @@ finaliseSelectedPackages pref selected constraints =
     finaliseSource mipkg (SemiConfiguredPackage pkg flags stanzas deps) =
       InstallPlan.Configured (ConfiguredPackage pkg flags stanzas deps')
       where
-        deps' = map (packageId . pickRemaining mipkg) deps
+        deps' = map (confId . pickRemaining mipkg) deps
+
+    -- InstalledOrSource indicates that we either have a source package
+    -- available, or an installed one, or both. In the case that we have both
+    -- available, we don't yet know if we can pick the installed one (the
+    -- dependencies may not match up, for instance); this is verified in
+    -- `improvePlan`.
+    --
+    -- This means that at this point we cannot construct a valid installed
+    -- package ID yet for the dependencies. We therefore have two options:
+    --
+    -- * We could leave the installed package ID undefined here, and have a
+    --   separate pass over the output of the top-down solver, fixing all
+    --   dependencies so that if we depend on an already installed package we
+    --   use the proper installed package ID.
+    --
+    -- * We can _always_ use fake installed IDs, irrespective of whether we the
+    --   dependency is on an already installed package or not. This is okay
+    --   because (i) the top-down solver does not (and never will) support
+    --   multiple package instances, and (ii) we initialize the FakeMap with
+    --   fake IDs for already installed packages.
+    --
+    -- For now we use the second option; if however we change the implementation
+    -- of these fake IDs so that we do away with the FakeMap and update a
+    -- package reverse dependencies as we execute the install plan and discover
+    -- real package IDs, then this is no longer possible and we have to
+    -- implement the first option (see also Note [FakeMap] in Cabal).
+    confId :: InstalledOrSource InstalledPackageEx UnconfiguredPackage -> ConfiguredId
+    confId pkg = ConfiguredId {
+        confSrcId  = packageId pkg
+      , confInstId = fakeInstalledPackageId (packageId pkg)
+      }
 
     pickRemaining mipkg dep@(Dependency _name versionRange) =
           case PackageIndex.lookupDependency remainingChoices dep of
diff --git a/cabal-install/Distribution/Client/Dependency/TopDown/Types.hs b/cabal-install/Distribution/Client/Dependency/TopDown/Types.hs
index 29632b67af65230628afe8f5587ec1434f538f73..c6cc5baa73b660362cd0bfc05c58634eaabe7f74 100644
--- a/cabal-install/Distribution/Client/Dependency/TopDown/Types.hs
+++ b/cabal-install/Distribution/Client/Dependency/TopDown/Types.hs
@@ -14,7 +14,7 @@ module Distribution.Client.Dependency.TopDown.Types where
 
 import Distribution.Client.Types
          ( SourcePackage(..), ReadyPackage(..), InstalledPackage(..)
-         , OptionalStanza )
+         , OptionalStanza, ConfiguredId(..) )
 import Distribution.Client.InstallPlan
          ( ConfiguredPackage(..), PlanPackage(..) )
 
@@ -113,7 +113,7 @@ instance PackageSourceDeps InstalledPackageEx where
   sourceDeps (InstalledPackageEx _ _ deps) = deps
 
 instance PackageSourceDeps ConfiguredPackage where
-  sourceDeps (ConfiguredPackage _ _ _ deps) = deps
+  sourceDeps (ConfiguredPackage _ _ _ deps) = map confSrcId deps
 
 instance PackageSourceDeps ReadyPackage where
   sourceDeps (ReadyPackage _ _ _ deps) = map packageId deps
diff --git a/cabal-install/Distribution/Client/InstallPlan.hs b/cabal-install/Distribution/Client/InstallPlan.hs
index da9d841a6ad3b39ead774531ca512a6e70cb49f5..84735ff41e11a5961d9915a694a5c2a44a36faa7 100644
--- a/cabal-install/Distribution/Client/InstallPlan.hs
+++ b/cabal-install/Distribution/Client/InstallPlan.hs
@@ -54,10 +54,12 @@ import Distribution.Client.Types
          ( SourcePackage(packageDescription), ConfiguredPackage(..)
          , ReadyPackage(..), readyPackageToConfiguredPackage
          , InstalledPackage, BuildFailure, BuildSuccess(..), enableStanzas
-         , InstalledPackage(..), fakeInstalledPackageId )
+         , InstalledPackage(..), fakeInstalledPackageId
+         , ConfiguredId(..)
+         )
 import Distribution.Package
          ( PackageIdentifier(..), PackageName(..), Package(..), packageName
-         , Dependency(..), InstalledPackageId
+         , Dependency(..), PackageId, InstalledPackageId
          , HasInstalledPackageId(..), PackageInstalled(..) )
 import Distribution.Version
          ( Version, withinRange )
@@ -594,7 +596,7 @@ showPackageProblem (InvalidDep dep pkgid) =
 configuredPackageProblems :: Platform -> CompilerInfo
                           -> ConfiguredPackage -> [PackageProblem]
 configuredPackageProblems platform cinfo
-  (ConfiguredPackage pkg specifiedFlags stanzas specifiedDeps) =
+  (ConfiguredPackage pkg specifiedFlags stanzas specifiedDeps') =
      [ DuplicateFlag flag | ((flag,_):_) <- duplicates specifiedFlags ]
   ++ [ MissingFlag flag | OnlyInLeft  flag <- mergedFlags ]
   ++ [ ExtraFlag   flag | OnlyInRight flag <- mergedFlags ]
@@ -605,6 +607,9 @@ configuredPackageProblems platform cinfo
   ++ [ InvalidDep dep pkgid | InBoth      dep pkgid <- mergedDeps
                             , not (packageSatisfiesDependency pkgid dep) ]
   where
+    specifiedDeps :: [PackageId]
+    specifiedDeps = map confSrcId specifiedDeps'
+
     mergedFlags = mergeBy compare
       (sort $ map flagName (genPackageFlags (packageDescription pkg)))
       (sort $ map fst specifiedFlags)
diff --git a/cabal-install/Distribution/Client/Types.hs b/cabal-install/Distribution/Client/Types.hs
index 10f0cca3f9ca3874c1144e19fec90c4a31061d45..fb9a693c59717209177fc7d3d657181e240f7f2b 100644
--- a/cabal-install/Distribution/Client/Types.hs
+++ b/cabal-install/Distribution/Client/Types.hs
@@ -19,7 +19,7 @@ import Distribution.Package
          , mkPackageKey, PackageKey, InstalledPackageId(..)
          , HasInstalledPackageId(..), PackageInstalled(..) )
 import Distribution.InstalledPackageInfo
-         ( InstalledPackageInfo, packageKey )
+         ( InstalledPackageInfo )
 import Distribution.PackageDescription
          ( Benchmark(..), GenericPackageDescription(..), FlagAssignment
          , TestSuite(..) )
@@ -32,6 +32,7 @@ import Distribution.Version
 import Distribution.Simple.Compiler
          ( Compiler, packageKeySupported )
 import Distribution.Text (display)
+import qualified Distribution.InstalledPackageInfo as Info
 
 import Data.Map (Map)
 import Network.URI (URI)
@@ -102,17 +103,37 @@ data ConfiguredPackage = ConfiguredPackage
        SourcePackage       -- package info, including repo
        FlagAssignment      -- complete flag assignment for the package
        [OptionalStanza]    -- list of enabled optional stanzas for the package
-       [PackageId]         -- set of exact dependencies. These must be
-                           -- consistent with the 'buildDepends' in the
-                           -- 'PackageDescription' that you'd get by applying
-                           -- the flag assignment and optional stanzas.
+       [ConfiguredId]      -- set of exact dependencies (installed or source).
+                           -- These must be consistent with the 'buildDepends'
+                           -- in the 'PackageDescription' that you'd get by
+                           -- applying the flag assignment and optional stanzas.
   deriving Show
 
+-- | A ConfiguredId is a package ID for a configured package.
+--
+-- Once we configure a source package we know it's InstalledPackageId
+-- (at least, in principle, even if we have to fake it currently). It is still
+-- however useful in lots of places to also know the source ID for the package.
+-- We therefore bundle the two.
+--
+-- An already installed package of course is also "configured" (all it's
+-- configuration parameters and dependencies have been specified).
+--
+-- TODO: I wonder if it would make sense to promote this datatype to Cabal
+-- and use it consistently instead of InstalledPackageIds?
+data ConfiguredId = ConfiguredId {
+    confSrcId  :: PackageId
+  , confInstId :: InstalledPackageId
+  }
+
+instance Show ConfiguredId where
+  show = show . confSrcId
+
 instance Package ConfiguredPackage where
   packageId (ConfiguredPackage pkg _ _ _) = packageId pkg
 
 instance PackageFixedDeps ConfiguredPackage where
-  depends (ConfiguredPackage _ _ _ deps) = deps
+  depends (ConfiguredPackage _ _ _ deps) = map confSrcId deps
 
 instance HasInstalledPackageId ConfiguredPackage where
   installedPackageId = fakeInstalledPackageId . packageId
@@ -144,7 +165,7 @@ instance PackageInstalled ReadyPackage where
 readyPackageKey :: Compiler -> ReadyPackage -> PackageKey
 readyPackageKey comp (ReadyPackage pkg _ _ deps) =
     mkPackageKey (packageKeySupported comp) (packageId pkg)
-                 (map packageKey deps) []
+                 (map Info.packageKey deps) []
 
 
 -- | Sometimes we need to convert a 'ReadyPackage' back to a
@@ -152,7 +173,14 @@ readyPackageKey comp (ReadyPackage pkg _ _ deps) =
 -- Ready or Configured.
 readyPackageToConfiguredPackage :: ReadyPackage -> ConfiguredPackage
 readyPackageToConfiguredPackage (ReadyPackage srcpkg flags stanzas deps) =
-  ConfiguredPackage srcpkg flags stanzas (map packageId deps)
+    ConfiguredPackage srcpkg flags stanzas (map aux deps)
+  where
+    aux :: InstalledPackageInfo -> ConfiguredId
+    aux info = ConfiguredId {
+        confSrcId  = Info.sourcePackageId info
+      , confInstId = installedPackageId info
+      }
+
 
 -- | A package description along with the location of the package sources.
 --