diff --git a/cabal-install/Distribution/Client/Configure.hs b/cabal-install/Distribution/Client/Configure.hs
index adb283f32d473308907f4a4ad49f13230e664af9..45edd5d8c8490ade9a1292a007b98cfc0d42fe64 100644
--- a/cabal-install/Distribution/Client/Configure.hs
+++ b/cabal-install/Distribution/Client/Configure.hs
@@ -144,7 +144,7 @@ configure verbosity packageDBs repoCtxt comp platform progdb
                                  _ _ _))] -> do
         configurePackage verbosity
           platform (compilerInfo comp)
-          (setupScriptOptions installedPkgIndex (Just pkg))
+          (setupScriptOptions installedPkgIndex pkg)
           configFlags pkg extraArgs
 
       _ -> die' verbosity $ "internal error: configure install plan should have exactly "
diff --git a/cabal-install/Distribution/Client/Dependency.hs b/cabal-install/Distribution/Client/Dependency.hs
index 1b04111ad84694d9f86539faeaae5fbaad2c2279..8dad0748fda363f549d02cb497c794363e419d1b 100644
--- a/cabal-install/Distribution/Client/Dependency.hs
+++ b/cabal-install/Distribution/Client/Dependency.hs
@@ -74,7 +74,7 @@ import qualified Distribution.Client.SolverInstallPlan as SolverInstallPlan
 import Distribution.Client.Types
          ( SourcePackageDb(SourcePackageDb)
          , PackageSpecifier(..), pkgSpecifierTarget, pkgSpecifierConstraints
-         , UnresolvedPkgLoc, UnresolvedSourcePackage
+         , ResolvedPkgLoc, ResolvedSourcePackage
          , AllowNewer(..), AllowOlder(..), RelaxDeps(..), RelaxedDep(..)
          , RelaxDepScope(..), RelaxDepMod(..), RelaxDepSubject(..), isRelaxDeps
          )
@@ -155,7 +155,7 @@ data DepResolverParams = DepResolverParams {
        depResolverPreferences       :: [PackagePreference],
        depResolverPreferenceDefault :: PackagesPreferenceDefault,
        depResolverInstalledPkgIndex :: InstalledPackageIndex,
-       depResolverSourcePkgIndex    :: PackageIndex.PackageIndex UnresolvedSourcePackage,
+       depResolverSourcePkgIndex    :: PackageIndex.PackageIndex ResolvedSourcePackage,
        depResolverReorderGoals      :: ReorderGoals,
        depResolverCountConflicts    :: CountConflicts,
        depResolverIndependentGoals  :: IndependentGoals,
@@ -239,7 +239,7 @@ showPackagePreference (PackageStanzasPreference pn st) =
   display pn ++ " " ++ show st
 
 basicDepResolverParams :: InstalledPackageIndex
-                       -> PackageIndex.PackageIndex UnresolvedSourcePackage
+                       -> PackageIndex.PackageIndex ResolvedSourcePackage
                        -> DepResolverParams
 basicDepResolverParams installedPkgIndex sourcePkgIndex =
     DepResolverParams {
@@ -399,7 +399,7 @@ dontUpgradeNonUpgradeablePackages params =
                 . InstalledPackageIndex.lookupPackageName
                                  (depResolverInstalledPkgIndex params)
 
-addSourcePackages :: [UnresolvedSourcePackage]
+addSourcePackages :: [ResolvedSourcePackage]
                   -> DepResolverParams -> DepResolverParams
 addSourcePackages pkgs params =
     params {
@@ -456,7 +456,7 @@ removeBounds  relKind relDeps            params =
   where
     sourcePkgIndex' = fmap relaxDeps $ depResolverSourcePkgIndex params
 
-    relaxDeps :: UnresolvedSourcePackage -> UnresolvedSourcePackage
+    relaxDeps :: ResolvedSourcePackage -> ResolvedSourcePackage
     relaxDeps srcPkg = srcPkg {
       packageDescription = relaxPackageDeps relKind relDeps
                            (packageDescription srcPkg)
@@ -523,7 +523,7 @@ removeBound relKind RelaxDepModCaret = hyloVersionRange embed projectVersionRang
 -- 'addSourcePackages'. Otherwise, the packages inserted by
 -- 'addSourcePackages' won't have upper bounds in dependencies relaxed.
 --
-addDefaultSetupDependencies :: (UnresolvedSourcePackage -> Maybe [Dependency])
+addDefaultSetupDependencies :: (ResolvedSourcePackage -> Maybe [Dependency])
                             -> DepResolverParams -> DepResolverParams
 addDefaultSetupDependencies defaultSetupDeps params =
     params {
@@ -531,7 +531,7 @@ addDefaultSetupDependencies defaultSetupDeps params =
         fmap applyDefaultSetupDeps (depResolverSourcePkgIndex params)
     }
   where
-    applyDefaultSetupDeps :: UnresolvedSourcePackage -> UnresolvedSourcePackage
+    applyDefaultSetupDeps :: ResolvedSourcePackage -> ResolvedSourcePackage
     applyDefaultSetupDeps srcpkg =
         srcpkg {
           packageDescription = gpkgdesc {
@@ -598,7 +598,7 @@ reinstallTargets params =
 --
 basicInstallPolicy :: InstalledPackageIndex
                    -> SourcePackageDb
-                   -> [PackageSpecifier UnresolvedSourcePackage]
+                   -> [PackageSpecifier ResolvedSourcePackage]
                    -> DepResolverParams
 basicInstallPolicy
     installedPkgIndex (SourcePackageDb sourcePkgIndex sourcePkgPrefs)
@@ -631,7 +631,7 @@ basicInstallPolicy
 --
 standardInstallPolicy :: InstalledPackageIndex
                       -> SourcePackageDb
-                      -> [PackageSpecifier UnresolvedSourcePackage]
+                      -> [PackageSpecifier ResolvedSourcePackage]
                       -> DepResolverParams
 standardInstallPolicy installedPkgIndex sourcePkgDb pkgSpecifiers
 
@@ -642,7 +642,7 @@ standardInstallPolicy installedPkgIndex sourcePkgDb pkgSpecifiers
 
     where
       -- Force Cabal >= 1.24 dep when the package is affected by #3199.
-      mkDefaultSetupDeps :: UnresolvedSourcePackage -> Maybe [Dependency]
+      mkDefaultSetupDeps :: ResolvedSourcePackage -> Maybe [Dependency]
       mkDefaultSetupDeps srcpkg | affected        =
         Just [Dependency (mkPackageName "Cabal")
               (orLaterVersion $ mkVersion [1,24])]
@@ -718,7 +718,7 @@ chooseSolver _verbosity preSolver _cinfo =
       AlwaysModular -> do
         return Modular
 
-runSolver :: Solver -> SolverConfig -> DependencyResolver UnresolvedPkgLoc
+runSolver :: Solver -> SolverConfig -> DependencyResolver ResolvedPkgLoc
 runSolver Modular = modularResolver
 
 -- | Run the dependency solver.
@@ -827,7 +827,7 @@ interpretPackagesPreference selected defaultPref prefs =
 validateSolverResult :: Platform
                      -> CompilerInfo
                      -> IndependentGoals
-                     -> [ResolverPackage UnresolvedPkgLoc]
+                     -> [ResolverPackage ResolvedPkgLoc]
                      -> SolverInstallPlan
 validateSolverResult platform comp indepGoals pkgs =
     case planPackagesProblems platform comp pkgs of
@@ -852,9 +852,9 @@ validateSolverResult platform comp indepGoals pkgs =
 
 
 data PlanPackageProblem =
-       InvalidConfiguredPackage (SolverPackage UnresolvedPkgLoc)
+       InvalidConfiguredPackage (SolverPackage ResolvedPkgLoc)
                                 [PackageProblem]
-     | DuplicatePackageSolverId SolverId [ResolverPackage UnresolvedPkgLoc]
+     | DuplicatePackageSolverId SolverId [ResolverPackage ResolvedPkgLoc]
 
 showPlanPackageProblem :: PlanPackageProblem -> String
 showPlanPackageProblem (InvalidConfiguredPackage pkg packageProblems) =
@@ -867,7 +867,7 @@ showPlanPackageProblem (DuplicatePackageSolverId pid dups) =
   ++ show (length dups) ++ " duplicate instances."
 
 planPackagesProblems :: Platform -> CompilerInfo
-                     -> [ResolverPackage UnresolvedPkgLoc]
+                     -> [ResolverPackage ResolvedPkgLoc]
                      -> [PlanPackageProblem]
 planPackagesProblems platform cinfo pkgs =
      [ InvalidConfiguredPackage pkg packageProblems
@@ -918,7 +918,7 @@ showPackageProblem (InvalidDep dep pkgid) =
 -- dependencies are satisfied by the specified packages.
 --
 configuredPackageProblems :: Platform -> CompilerInfo
-                          -> SolverPackage UnresolvedPkgLoc -> [PackageProblem]
+                          -> SolverPackage ResolvedPkgLoc -> [PackageProblem]
 configuredPackageProblems platform cinfo
   (SolverPackage pkg specifiedFlags stanzas specifiedDeps' _specifiedExeDeps') =
      [ DuplicateFlag flag
@@ -1002,7 +1002,7 @@ configuredPackageProblems platform cinfo
 -- It simply means preferences for installed packages will be ignored.
 --
 resolveWithoutDependencies :: DepResolverParams
-                           -> Either [ResolveNoDepsError] [UnresolvedSourcePackage]
+                           -> Either [ResolveNoDepsError] [ResolvedSourcePackage]
 resolveWithoutDependencies (DepResolverParams targets constraints
                               prefs defpref installedPkgIndex sourcePkgIndex
                               _reorderGoals _countConflicts _indGoals _avoidReinstalls
@@ -1010,7 +1010,7 @@ resolveWithoutDependencies (DepResolverParams targets constraints
                               _solveExes _allowBootLibInstalls _onlyConstrained _order _verbosity) =
     collectEithers $ map selectPackage (Set.toList targets)
   where
-    selectPackage :: PackageName -> Either ResolveNoDepsError UnresolvedSourcePackage
+    selectPackage :: PackageName -> Either ResolveNoDepsError ResolvedSourcePackage
     selectPackage pkgname
       | null choices = Left  $! ResolveUnsatisfiable pkgname requiredVersions
       | otherwise    = Right $! maximumBy bestByPrefs choices
diff --git a/cabal-install/Distribution/Client/Fetch.hs b/cabal-install/Distribution/Client/Fetch.hs
index ecad9a98ce1f09ef86b15ad764fd688da828e544..55123fe7f907757b35e699cfbf29e004b1055256 100644
--- a/cabal-install/Distribution/Client/Fetch.hs
+++ b/cabal-install/Distribution/Client/Fetch.hs
@@ -99,7 +99,7 @@ fetch verbosity packageDBs repoCtxt comp platform progdb
                verbosity comp platform fetchFlags
                installedPkgIndex sourcePkgDb pkgConfigDb pkgSpecifiers
 
-    pkgs' <- filterM (fmap not . isFetched . packageSource) pkgs
+    pkgs' <- filterM (fmap not . isFetchedResolved . packageSource) pkgs
     if null pkgs'
       --TODO: when we add support for remote tarballs then this message
       -- will need to be changed because for remote tarballs we fetch them
@@ -124,8 +124,8 @@ planPackages :: Verbosity
              -> InstalledPackageIndex
              -> SourcePackageDb
              -> PkgConfigDb
-             -> [PackageSpecifier UnresolvedSourcePackage]
-             -> IO [UnresolvedSourcePackage]
+             -> [PackageSpecifier ResolvedSourcePackage]
+             -> IO [ResolvedSourcePackage]
 planPackages verbosity comp platform fetchFlags
              installedPkgIndex sourcePkgDb pkgConfigDb pkgSpecifiers
 
diff --git a/cabal-install/Distribution/Client/FetchUtils.hs b/cabal-install/Distribution/Client/FetchUtils.hs
index 401bd1513a3f86fe4e979ca058f4823f0c949e74..bdebaeaf7139e7ff8f936976e32e98b0cbcd6a2a 100644
--- a/cabal-install/Distribution/Client/FetchUtils.hs
+++ b/cabal-install/Distribution/Client/FetchUtils.hs
@@ -17,6 +17,7 @@ module Distribution.Client.FetchUtils (
     -- * fetching packages
     fetchPackage,
     isFetched,
+    isFetchedResolved,
     checkFetched,
 
     -- ** specifically for repo packages
@@ -84,6 +85,17 @@ isFetched loc = case loc of
     RemoteTarballPackage _uri local -> return (isJust local)
     RepoTarballPackage repo pkgid _ -> doesFileExist (packageFile repo pkgid)
     RemoteSourceRepoPackage _ local -> return (isJust local)
+
+-- | Returns @True@ if the package has already been fetched
+-- or does not need fetching.
+--
+isFetchedResolved :: ResolvedPkgLoc -> IO Bool
+isFetchedResolved loc = case loc of
+    LocalUnpackedPackage _dir       -> return True
+    LocalTarballPackage  _file      -> return True
+    RemoteTarballPackage _uri _local -> return True
+    RepoTarballPackage repo pkgid _ -> doesFileExist (packageFile repo pkgid)
+    RemoteSourceRepoPackage _ _local -> return True
     
 
 -- | Checks if the package has already been fetched (or does not need
diff --git a/cabal-install/Distribution/Client/Freeze.hs b/cabal-install/Distribution/Client/Freeze.hs
index 7b7c98a80a65b73186bf324bfaff2bec47e86825..72448330c970917df1123f6ab3f5831fa19bc97a 100644
--- a/cabal-install/Distribution/Client/Freeze.hs
+++ b/cabal-install/Distribution/Client/Freeze.hs
@@ -146,7 +146,7 @@ planPackages :: Verbosity
              -> InstalledPackageIndex
              -> SourcePackageDb
              -> PkgConfigDb
-             -> [PackageSpecifier UnresolvedSourcePackage]
+             -> [PackageSpecifier ResolvedSourcePackage]
              -> IO [SolverPlanPackage]
 planPackages verbosity comp platform mSandboxPkgInfo freezeFlags
              installedPkgIndex sourcePkgDb pkgConfigDb pkgSpecifiers = do
@@ -226,7 +226,7 @@ planPackages verbosity comp platform mSandboxPkgInfo freezeFlags
 -- Invariant: @pkgSpecifiers@ must refer to packages which are not
 -- 'PreExisting' in the 'SolverInstallPlan'.
 pruneInstallPlan :: SolverInstallPlan
-                 -> [PackageSpecifier UnresolvedSourcePackage]
+                 -> [PackageSpecifier ResolvedSourcePackage]
                  -> [SolverPlanPackage]
 pruneInstallPlan installPlan pkgSpecifiers =
     removeSelf pkgIds $
diff --git a/cabal-install/Distribution/Client/Get.hs b/cabal-install/Distribution/Client/Get.hs
index 34b713bfc2cdbdb340a307a2eb80a085d0ac3e98..c3306980ca15c93c776766696410698198da07b2 100644
--- a/cabal-install/Distribution/Client/Get.hs
+++ b/cabal-install/Distribution/Client/Get.hs
@@ -108,7 +108,7 @@ get verbosity repoCtxt globalFlags getFlags userTargets = do
 
     prefix = fromFlagOrDefault "" (getDestDir getFlags)
 
-    clone :: [UnresolvedSourcePackage] -> IO ()
+    clone :: [ResolvedSourcePackage] -> IO ()
     clone = clonePackagesFromSourceRepo verbosity prefix kind
           . map (\pkg -> (packageId pkg, packageSourceRepos pkg))
       where
@@ -118,11 +118,11 @@ get verbosity repoCtxt globalFlags getFlags userTargets = do
                            . PD.packageDescription
                            . packageDescription
 
-    unpack :: [UnresolvedSourcePackage] -> IO ()
+    unpack :: [ResolvedSourcePackage] -> IO ()
     unpack pkgs = do
       forM_ pkgs $ \pkg -> do
-        location <- fetchPackage verbosity repoCtxt (packageSource pkg)
-        let pkgid = packageId pkg
+        let location = packageSource pkg
+            pkgid = packageId pkg
             descOverride | usePristine = Nothing
                          | otherwise   = packageDescrOverride pkg
         case location of
diff --git a/cabal-install/Distribution/Client/IndexUtils.hs b/cabal-install/Distribution/Client/IndexUtils.hs
index ffa2b4b0539c64c173c78ab0bd6ec4bbc148bea5..1b290696a55a5c50826deb1cfb839e01a333cc2e 100644
--- a/cabal-install/Distribution/Client/IndexUtils.hs
+++ b/cabal-install/Distribution/Client/IndexUtils.hs
@@ -298,7 +298,7 @@ readCacheStrict verbosity index mkPkg = do
 -- This is a higher level wrapper used internally in cabal-install.
 --
 readRepoIndex :: Verbosity -> RepoContext -> Repo -> IndexState
-              -> IO (PackageIndex UnresolvedSourcePackage, [Dependency], IndexStateInfo)
+              -> IO (PackageIndex ResolvedSourcePackage, [Dependency], IndexStateInfo)
 readRepoIndex verbosity repoCtxt repo idxState =
   handleNotFound $ do
     warnIfIndexIsOld =<< getIndexFileAge repo
@@ -313,7 +313,7 @@ readRepoIndex verbosity repoCtxt repo idxState =
         packageInfoId      = pkgid,
         packageDescription = packageDesc pkgEntry,
         packageSource      = case pkgEntry of
-          NormalPackage _ _ _ _       -> RepoTarballPackage repo pkgid Nothing
+          NormalPackage _ _ _ _       -> RepoTarballPackage repo pkgid undefined
           BuildTreeRef  _  _ _ path _ -> LocalUnpackedPackage path,
         packageDescrOverride = case pkgEntry of
           NormalPackage _ _ pkgtxt _ -> Just pkgtxt
diff --git a/cabal-install/Distribution/Client/InstallPlan.hs b/cabal-install/Distribution/Client/InstallPlan.hs
index e6df0246956c973964f37fcdcae01de52fe21e06..ba97c8d4cd900c5cb01154f91187257fe10bd1e5 100644
--- a/cabal-install/Distribution/Client/InstallPlan.hs
+++ b/cabal-install/Distribution/Client/InstallPlan.hs
@@ -207,7 +207,7 @@ instance (Binary ipkg, Binary srcpkg)
       => Binary (GenericPlanPackage ipkg srcpkg)
 
 type PlanPackage = GenericPlanPackage
-                   InstalledPackageInfo (ConfiguredPackage UnresolvedPkgLoc)
+                   InstalledPackageInfo (ConfiguredPackage ResolvedPkgLoc)
 
 instance (Package ipkg, Package srcpkg) =>
          Package (GenericPlanPackage ipkg srcpkg) where
@@ -242,7 +242,7 @@ data GenericInstallPlan ipkg srcpkg = GenericInstallPlan {
 
 -- | 'GenericInstallPlan' specialised to most commonly used types.
 type InstallPlan = GenericInstallPlan
-                   InstalledPackageInfo (ConfiguredPackage UnresolvedPkgLoc)
+                   InstalledPackageInfo (ConfiguredPackage ResolvedPkgLoc)
 
 -- | Smart constructor that deals with caching the 'Graph' representation.
 --
@@ -517,8 +517,8 @@ configureInstallPlan configFlags solverPlan =
       ]
   where
     configureSolverPackage :: (SolverId -> [PlanPackage])
-                           -> SolverPackage UnresolvedPkgLoc
-                           -> ConfiguredPackage UnresolvedPkgLoc
+                           -> SolverPackage ResolvedPkgLoc
+                           -> ConfiguredPackage ResolvedPkgLoc
     configureSolverPackage mapDep spkg =
       ConfiguredPackage {
         confPkgId = Configure.computeComponentId
diff --git a/cabal-install/Distribution/Client/List.hs b/cabal-install/Distribution/Client/List.hs
index 5a72ce7a709557573bd8e3c742ac5d56cffb36d7..fdd9cf923c252b6aac5f981d35bdf7dd55ef9d12 100644
--- a/cabal-install/Distribution/Client/List.hs
+++ b/cabal-install/Distribution/Client/List.hs
@@ -50,7 +50,7 @@ import qualified Distribution.Solver.Types.PackageIndex as PackageIndex
 import           Distribution.Solver.Types.SourcePackage
 
 import Distribution.Client.Types
-         ( SourcePackageDb(..), PackageSpecifier(..), UnresolvedSourcePackage )
+         ( SourcePackageDb(..), PackageSpecifier(..), ResolvedSourcePackage )
 import Distribution.Client.Targets
          ( UserTarget, resolveUserTargets )
 import Distribution.Client.Setup
@@ -61,7 +61,7 @@ import Distribution.Client.Utils
 import Distribution.Client.IndexUtils as IndexUtils
          ( getSourcePackages, getInstalledPackages )
 import Distribution.Client.FetchUtils
-         ( isFetched )
+         ( isFetchedResolved )
 
 import Data.List
          ( sortBy, groupBy, sort, nub, intersperse, maximumBy, partition )
@@ -95,7 +95,7 @@ getPkgList verbosity packageDBs repoCtxt comp progdb listFlags pats = do
                        (Map.lookup name (packagePreferences sourcePkgDb))
 
         pkgsInfo ::
-          [(PackageName, [Installed.InstalledPackageInfo], [UnresolvedSourcePackage])]
+          [(PackageName, [Installed.InstalledPackageInfo], [ResolvedSourcePackage])]
         pkgsInfo
             -- gather info for all packages
           | null pats = mergePackages
@@ -106,7 +106,7 @@ getPkgList verbosity packageDBs repoCtxt comp progdb listFlags pats = do
           | otherwise = pkgsInfoMatching
 
         pkgsInfoMatching ::
-          [(PackageName, [Installed.InstalledPackageInfo], [UnresolvedSourcePackage])]
+          [(PackageName, [Installed.InstalledPackageInfo], [ResolvedSourcePackage])]
         pkgsInfoMatching =
           let matchingInstalled = matchingPackages
                                   InstalledPackageIndex.searchByNameSubstring
@@ -211,8 +211,8 @@ info verbosity packageDBs repoCtxt comp progdb
   where
     gatherPkgInfo :: (PackageName -> VersionRange) ->
                      InstalledPackageIndex ->
-                     PackageIndex.PackageIndex UnresolvedSourcePackage ->
-                     PackageSpecifier UnresolvedSourcePackage ->
+                     PackageIndex.PackageIndex ResolvedSourcePackage ->
+                     PackageSpecifier ResolvedSourcePackage ->
                      Either String PackageDisplayInfo
     gatherPkgInfo prefs installedPkgIndex sourcePkgIndex
       (NamedPackage name props)
@@ -256,8 +256,8 @@ sourcePkgsInfo ::
   (PackageName -> VersionRange)
   -> PackageName
   -> InstalledPackageIndex
-  -> PackageIndex.PackageIndex UnresolvedSourcePackage
-  -> (VersionRange, [Installed.InstalledPackageInfo], [UnresolvedSourcePackage])
+  -> PackageIndex.PackageIndex ResolvedSourcePackage
+  -> (VersionRange, [Installed.InstalledPackageInfo], [ResolvedSourcePackage])
 sourcePkgsInfo prefs name installedPkgIndex sourcePkgIndex =
   (pref, installedPkgs, sourcePkgs)
   where
@@ -273,7 +273,7 @@ sourcePkgsInfo prefs name installedPkgIndex sourcePkgIndex =
 data PackageDisplayInfo = PackageDisplayInfo {
     pkgName           :: PackageName,
     selectedVersion   :: Maybe Version,
-    selectedSourcePkg :: Maybe UnresolvedSourcePackage,
+    selectedSourcePkg :: Maybe ResolvedSourcePackage,
     installedVersions :: [Version],
     sourceVersions    :: [Version],
     preferredVersions :: VersionRange,
@@ -422,8 +422,8 @@ reflowLines = vcat . map text . lines
 --
 mergePackageInfo :: VersionRange
                  -> [Installed.InstalledPackageInfo]
-                 -> [UnresolvedSourcePackage]
-                 -> Maybe UnresolvedSourcePackage
+                 -> [ResolvedSourcePackage]
+                 -> Maybe ResolvedSourcePackage
                  -> Bool
                  -> PackageDisplayInfo
 mergePackageInfo versionPref installedPkgs sourcePkgs selectedPkg showVer =
@@ -503,7 +503,7 @@ mergePackageInfo versionPref installedPkgs sourcePkgs selectedPkg showVer =
 --
 updateFileSystemPackageDetails :: PackageDisplayInfo -> IO PackageDisplayInfo
 updateFileSystemPackageDetails pkginfo = do
-  fetched   <- maybe (return False) (isFetched . packageSource)
+  fetched   <- maybe (return False) (isFetchedResolved . packageSource)
                      (selectedSourcePkg pkginfo)
   docsExist <- doesDirectoryExist (haddockHtml pkginfo)
   return pkginfo {
@@ -524,10 +524,10 @@ latestWithPref pref pkgs = Just (maximumBy (comparing prefThenVersion) pkgs)
 -- both be empty.
 --
 mergePackages :: [Installed.InstalledPackageInfo]
-              -> [UnresolvedSourcePackage]
+              -> [ResolvedSourcePackage]
               -> [( PackageName
                   , [Installed.InstalledPackageInfo]
-                  , [UnresolvedSourcePackage] )]
+                  , [ResolvedSourcePackage] )]
 mergePackages installedPkgs sourcePkgs =
     map collect
   $ mergeBy (\i a -> fst i `compare` fst a)
diff --git a/cabal-install/Distribution/Client/Outdated.hs b/cabal-install/Distribution/Client/Outdated.hs
index 017aae4212364d2d037f72f5e7bb2779dc806f4e..6af2fe6d1eca4c5c1983b4fcfb474c3620e64f8e 100644
--- a/cabal-install/Distribution/Client/Outdated.hs
+++ b/cabal-install/Distribution/Client/Outdated.hs
@@ -172,7 +172,7 @@ data ListOutdatedSettings = ListOutdatedSettings {
 
 -- | Find all outdated dependencies.
 listOutdated :: [Dependency]
-             -> PackageIndex UnresolvedSourcePackage
+             -> PackageIndex ResolvedSourcePackage
              -> ListOutdatedSettings
              -> [(Dependency, Version)]
 listOutdated deps pkgIndex (ListOutdatedSettings ignorePred minorPred) =
diff --git a/cabal-install/Distribution/Client/ProjectConfig.hs b/cabal-install/Distribution/Client/ProjectConfig.hs
index 9243f79334b765019578cd367e223b78261aa71e..1762e46169e00fe02470314710c8714e86630602 100644
--- a/cabal-install/Distribution/Client/ProjectConfig.hs
+++ b/cabal-install/Distribution/Client/ProjectConfig.hs
@@ -958,7 +958,7 @@ fetchAndReadSourcePackages
   -> ProjectConfigShared
   -> ProjectConfigBuildOnly
   -> [ProjectPackageLocation]
-  -> Rebuild [PackageSpecifier (SourcePackage UnresolvedPkgLoc)]
+  -> Rebuild [PackageSpecifier (SourcePackage ResolvedPkgLoc)]
 fetchAndReadSourcePackages verbosity distDirLayout
                            projectConfigShared
                            projectConfigBuildOnly
@@ -1019,7 +1019,7 @@ readSourcePackageLocalDirectory
   :: Verbosity
   -> FilePath  -- ^ The package directory
   -> FilePath  -- ^ The package @.cabal@ file
-  -> Rebuild (PackageSpecifier (SourcePackage UnresolvedPkgLoc))
+  -> Rebuild (PackageSpecifier (SourcePackage ResolvedPkgLoc))
 readSourcePackageLocalDirectory verbosity dir cabalFile = do
     monitorFiles [monitorFileHashed cabalFile]
     root <- askRoot
@@ -1036,7 +1036,7 @@ readSourcePackageLocalDirectory verbosity dir cabalFile = do
 readSourcePackageLocalTarball
   :: Verbosity
   -> FilePath
-  -> Rebuild (PackageSpecifier (SourcePackage UnresolvedPkgLoc))
+  -> Rebuild (PackageSpecifier (SourcePackage ResolvedPkgLoc))
 readSourcePackageLocalTarball verbosity tarballFile = do
     monitorFiles [monitorFile tarballFile]
     root <- askRoot
@@ -1055,7 +1055,7 @@ fetchAndReadSourcePackageRemoteTarball
   -> DistDirLayout
   -> Rebuild HttpTransport
   -> URI
-  -> Rebuild (PackageSpecifier (SourcePackage UnresolvedPkgLoc))
+  -> Rebuild (PackageSpecifier (SourcePackage ResolvedPkgLoc))
 fetchAndReadSourcePackageRemoteTarball verbosity
                                        DistDirLayout {
                                          distDownloadSrcDirectory
@@ -1087,7 +1087,7 @@ fetchAndReadSourcePackageRemoteTarball verbosity
               </> localFileNameForRemoteTarball tarballUri
     tarballFile = tarballStem <.> "tar.gz"
 
-    monitor :: FileMonitor URI (PackageSpecifier (SourcePackage UnresolvedPkgLoc))
+    monitor :: FileMonitor URI (PackageSpecifier (SourcePackage ResolvedPkgLoc))
     monitor = newFileMonitor (tarballStem <.> "cache")
 
 
@@ -1099,7 +1099,7 @@ syncAndReadSourcePackagesRemoteRepos
   -> DistDirLayout
   -> ProjectConfigShared
   -> [SourceRepo]
-  -> Rebuild [PackageSpecifier (SourcePackage UnresolvedPkgLoc)]
+  -> Rebuild [PackageSpecifier (SourcePackage ResolvedPkgLoc)]
 syncAndReadSourcePackagesRemoteRepos verbosity
                                      DistDirLayout{distDownloadSrcDirectory}
                                      ProjectConfigShared {
@@ -1134,7 +1134,7 @@ syncAndReadSourcePackagesRemoteRepos verbosity
                    </> localFileNameForRemoteRepo primaryRepo
             monitor :: FileMonitor
                          [SourceRepo]
-                         [PackageSpecifier (SourcePackage UnresolvedPkgLoc)]
+                         [PackageSpecifier (SourcePackage ResolvedPkgLoc)]
             monitor  = newFileMonitor (pathStem <.> "cache")
       ]
   where
@@ -1142,7 +1142,7 @@ syncAndReadSourcePackagesRemoteRepos verbosity
       :: VCS ConfiguredProgram
       -> FilePath
       -> [SourceRepo]
-      -> Rebuild [PackageSpecifier (SourcePackage UnresolvedPkgLoc)]
+      -> Rebuild [PackageSpecifier (SourcePackage ResolvedPkgLoc)]
     syncRepoGroupAndReadSourcePackages vcs pathStem repoGroup = do
         liftIO $ createDirectoryIfMissingVerbose verbosity False
                                                  distDownloadSrcDirectory
@@ -1205,13 +1205,12 @@ syncAndReadSourcePackagesRemoteRepos verbosity
 mkSpecificSourcePackage :: PackageLocation FilePath
                         -> GenericPackageDescription
                         -> PackageSpecifier
-                             (SourcePackage (PackageLocation (Maybe FilePath)))
+                             (SourcePackage (PackageLocation FilePath))
 mkSpecificSourcePackage location pkg =
     SpecificSourcePackage SourcePackage {
       packageInfoId        = packageId pkg,
       packageDescription   = pkg,
-      --TODO: it is silly that we still have to use a Maybe FilePath here
-      packageSource        = fmap Just location,
+      packageSource        = location,
       packageDescrOverride = Nothing
     }
 
diff --git a/cabal-install/Distribution/Client/ProjectOrchestration.hs b/cabal-install/Distribution/Client/ProjectOrchestration.hs
index 195d043bd23f07f9c701ce1a38d12964a3c90897..8f5bf2b50dadf839b93fcdd089dfeffde2081c31 100644
--- a/cabal-install/Distribution/Client/ProjectOrchestration.hs
+++ b/cabal-install/Distribution/Client/ProjectOrchestration.hs
@@ -109,7 +109,7 @@ import           Distribution.Client.ProjectBuilding
 import           Distribution.Client.ProjectPlanOutput
 
 import           Distribution.Client.Types
-                   ( GenericReadyPackage(..), UnresolvedSourcePackage
+                   ( GenericReadyPackage(..), ResolvedSourcePackage
                    , PackageSpecifier(..)
                    , SourcePackageDb(..) )
 import           Distribution.Solver.Types.PackageIndex
@@ -166,7 +166,7 @@ data ProjectBaseContext = ProjectBaseContext {
        distDirLayout  :: DistDirLayout,
        cabalDirLayout :: CabalDirLayout,
        projectConfig  :: ProjectConfig,
-       localPackages  :: [PackageSpecifier UnresolvedSourcePackage],
+       localPackages  :: [PackageSpecifier ResolvedSourcePackage],
        buildSettings  :: BuildTimeSettings
      }
 
diff --git a/cabal-install/Distribution/Client/ProjectPlanOutput.hs b/cabal-install/Distribution/Client/ProjectPlanOutput.hs
index 1e0eb7641482a06e0fea4c788a1c0fe05cfc9f4c..5746cbc05334e6ddbdc1a66dc489cbfcfb0fa94b 100644
--- a/cabal-install/Distribution/Client/ProjectPlanOutput.hs
+++ b/cabal-install/Distribution/Client/ProjectPlanOutput.hs
@@ -169,7 +169,7 @@ encodePlanAsJson distDirLayout elaboratedInstallPlan elaboratedSharedConfig =
             ] ++
             bin_file (compSolverName comp)
      where
-      packageLocationToJ :: PackageLocation (Maybe FilePath) -> J.Value
+      packageLocationToJ :: PackageLocation FilePath -> J.Value
       packageLocationToJ pkgloc =
         case pkgloc of
           LocalUnpackedPackage local ->
diff --git a/cabal-install/Distribution/Client/ProjectPlanning.hs b/cabal-install/Distribution/Client/ProjectPlanning.hs
index 2f85dca3cdc21c7a5dc2d1b6d4ad0ba925525ffa..597f9f205709e661a0c65ce97e6e99d7c52a85c3 100644
--- a/cabal-install/Distribution/Client/ProjectPlanning.hs
+++ b/cabal-install/Distribution/Client/ProjectPlanning.hs
@@ -297,7 +297,7 @@ rebuildProjectConfig :: Verbosity
                      -> DistDirLayout
                      -> ProjectConfig
                      -> IO ( ProjectConfig
-                           , [PackageSpecifier UnresolvedSourcePackage] )
+                           , [PackageSpecifier ResolvedSourcePackage] )
 rebuildProjectConfig verbosity
                      distDirLayout@DistDirLayout {
                        distProjectRootDirectory,
@@ -340,7 +340,7 @@ rebuildProjectConfig verbosity
     fileMonitorProjectConfig =
       newFileMonitor (distProjectCacheFile "config") :: FileMonitor
           (FilePath, FilePath)
-          (ProjectConfig, [PackageSpecifier UnresolvedSourcePackage])
+          (ProjectConfig, [PackageSpecifier ResolvedSourcePackage])
 
     -- Read the cabal.project (or implicit config) and combine it with
     -- arguments from the command line
@@ -353,7 +353,7 @@ rebuildProjectConfig verbosity
     -- some of which may be local src dirs, tarballs etc
     --
     phaseReadLocalPackages :: ProjectConfig
-                           -> Rebuild [PackageSpecifier UnresolvedSourcePackage]
+                           -> Rebuild [PackageSpecifier ResolvedSourcePackage]
     phaseReadLocalPackages projectConfig@ProjectConfig {
                                projectConfigShared,
                                projectConfigBuildOnly
@@ -1281,7 +1281,7 @@ elaborateInstallPlan verbosity platform compiler compilerprogdb pkgConfigDB
     -- a post-pass.  This makes it simpler to compute dependencies.
     elaborateSolverToComponents
         :: (SolverId -> [ElaboratedPlanPackage])
-        -> SolverPackage UnresolvedPkgLoc
+        -> SolverPackage ResolvedPkgLoc
         -> LogProgress [ElaboratedConfiguredPackage]
     elaborateSolverToComponents mapDep spkg@(SolverPackage _ _ _ deps0 exe_deps0)
         = case mkComponentsGraph (elabEnabledSpec elab0) pd of
@@ -1712,7 +1712,7 @@ elaborateInstallPlan verbosity platform compiler compilerprogdb pkgConfigDB
               (compilerId compiler)
               pkgInstalledId
 
-    elaborateSolverToCommon :: SolverPackage UnresolvedPkgLoc
+    elaborateSolverToCommon :: SolverPackage ResolvedPkgLoc
                             -> ElaboratedConfiguredPackage
     elaborateSolverToCommon
         pkg@(SolverPackage (SourcePackage pkgid gdesc srcloc descOverride)
diff --git a/cabal-install/Distribution/Client/ProjectPlanning/Types.hs b/cabal-install/Distribution/Client/ProjectPlanning/Types.hs
index 382fb1304dfb3562bf1c2fba0caa4c24e9bbd931..6d63eeaa07ab00539ce4454814ac1180fe701f33 100644
--- a/cabal-install/Distribution/Client/ProjectPlanning/Types.hs
+++ b/cabal-install/Distribution/Client/ProjectPlanning/Types.hs
@@ -191,7 +191,7 @@ data ElaboratedConfiguredPackage
 
        -- | Where the package comes from, e.g. tarball, local dir etc. This
        --   is not the same as where it may be unpacked to for the build.
-       elabPkgSourceLocation :: PackageLocation (Maybe FilePath),
+       elabPkgSourceLocation :: ResolvedPkgLoc,
 
        -- | The hash of the source, e.g. the tarball. We don't have this for
        -- local source dir packages.
@@ -409,9 +409,7 @@ dataDirEnvVarForPackage distDirLayout pkg =
     srcPath (LocalTarballPackage _path) = unpackedPath
     srcPath (RemoteTarballPackage _uri _localTar) = unpackedPath
     srcPath (RepoTarballPackage _repo _packageId _localTar) = unpackedPath
-    srcPath (RemoteSourceRepoPackage _sourceRepo (Just localCheckout)) = localCheckout
-    srcPath (RemoteSourceRepoPackage _sourceRepo Nothing) = error
-      "calling dataDirEnvVarForPackage on a not-downloaded repo is an error"
+    srcPath (RemoteSourceRepoPackage _sourceRepo localCheckout) = localCheckout
     unpackedPath =
       distUnpackedSrcDirectory distDirLayout $ elabPkgSourceId pkg
 
diff --git a/cabal-install/Distribution/Client/SolverInstallPlan.hs b/cabal-install/Distribution/Client/SolverInstallPlan.hs
index 222b4d4ff0ebc000f9e48df27e5332396cc34fb9..35fc7dcef3c20880b4df992a1e0fac5adf8126bc 100644
--- a/cabal-install/Distribution/Client/SolverInstallPlan.hs
+++ b/cabal-install/Distribution/Client/SolverInstallPlan.hs
@@ -59,7 +59,7 @@ import Distribution.Text
          ( display )
 
 import Distribution.Client.Types
-         ( UnresolvedPkgLoc )
+         ( ResolvedPkgLoc )
 import Distribution.Version
          ( Version )
 
@@ -80,7 +80,7 @@ import Data.Map (Map)
 import Data.Array ((!))
 import Data.Typeable
 
-type SolverPlanPackage = ResolverPackage UnresolvedPkgLoc
+type SolverPlanPackage = ResolverPackage ResolvedPkgLoc
 
 type SolverPlanIndex = Graph SolverPlanPackage
 
diff --git a/cabal-install/Distribution/Client/Targets.hs b/cabal-install/Distribution/Client/Targets.hs
index 69ca5dec0d99788162fa592dad441d4a11e0a00a..5a959fc048352213d37de0426681f6db456bfe80 100644
--- a/cabal-install/Distribution/Client/Targets.hs
+++ b/cabal-install/Distribution/Client/Targets.hs
@@ -55,7 +55,7 @@ import Distribution.Package
          , PackageIdentifier(..), packageName, packageVersion )
 import Distribution.Types.Dependency
 import Distribution.Client.Types
-         ( PackageLocation(..), ResolvedPkgLoc, UnresolvedSourcePackage
+         ( PackageLocation(..), ResolvedPkgLoc, ResolvedSourcePackage
          , PackageSpecifier(..) )
 
 import           Distribution.Solver.Types.OptionalStanza
@@ -323,7 +323,7 @@ resolveUserTargets :: Package pkg
                    -> FilePath
                    -> PackageIndex pkg
                    -> [UserTarget]
-                   -> IO [PackageSpecifier UnresolvedSourcePackage]
+                   -> IO [PackageSpecifier ResolvedSourcePackage]
 resolveUserTargets verbosity repoCtxt worldFile available userTargets = do
 
     -- given the user targets, get a list of fully or partially resolved
@@ -430,7 +430,7 @@ fetchPackageTarget verbosity repoCtxt = traverse $
 --
 readPackageTarget :: Verbosity
                   -> PackageTarget ResolvedPkgLoc
-                  -> IO (PackageTarget UnresolvedSourcePackage)
+                  -> IO (PackageTarget ResolvedSourcePackage)
 readPackageTarget verbosity = traverse modifyLocation
   where
     modifyLocation location = case location of
@@ -441,7 +441,7 @@ readPackageTarget verbosity = traverse modifyLocation
         return $ SourcePackage {
                    packageInfoId        = packageId pkg,
                    packageDescription   = pkg,
-                   packageSource        = fmap Just location,
+                   packageSource        = location,
                    packageDescrOverride = Nothing
                  }
 
@@ -473,7 +473,7 @@ readPackageTarget verbosity = traverse modifyLocation
           return $ SourcePackage {
                      packageInfoId        = packageId pkg,
                      packageDescription   = pkg,
-                     packageSource        = fmap Just location,
+                     packageSource        = location,
                      packageDescrOverride = Nothing
                    }
 
diff --git a/cabal-install/Distribution/Client/Types.hs b/cabal-install/Distribution/Client/Types.hs
index b87597d63b13f01d5db2ee32014bc2140a927f20..a0a02f35595d898f9a82e09c37ff9bed8eb0434c 100644
--- a/cabal-install/Distribution/Client/Types.hs
+++ b/cabal-install/Distribution/Client/Types.hs
@@ -78,7 +78,7 @@ newtype Password = Password { unPassword :: String }
 -- | This is the information we get from a @00-index.tar.gz@ hackage index.
 --
 data SourcePackageDb = SourcePackageDb {
-  packageIndex       :: PackageIndex UnresolvedSourcePackage,
+  packageIndex       :: PackageIndex ResolvedSourcePackage,
   packagePreferences :: Map PackageName VersionRange
 }
   deriving (Eq, Generic)
@@ -212,10 +212,12 @@ instance IsNode srcpkg => IsNode (GenericReadyPackage srcpkg) where
     nodeKey (ReadyPackage spkg) = nodeKey spkg
     nodeNeighbors (ReadyPackage spkg) = nodeNeighbors spkg
 
-type ReadyPackage = GenericReadyPackage (ConfiguredPackage UnresolvedPkgLoc)
+type ReadyPackage = GenericReadyPackage (ConfiguredPackage ResolvedPkgLoc)
 
 -- | Convenience alias for 'SourcePackage UnresolvedPkgLoc'.
 type UnresolvedSourcePackage = SourcePackage UnresolvedPkgLoc
+-- | Convenience alias for 'SourcePackage ResolvedPkgLoc'.
+type ResolvedSourcePackage = SourcePackage ResolvedPkgLoc
 
 
 -- ------------------------------------------------------------