diff --git a/cabal-install-solver/src/Distribution/Solver/Modular/Message.hs b/cabal-install-solver/src/Distribution/Solver/Modular/Message.hs
index d802079d04cd7950458cd880e770652bf91353b9..73580aff3e65de27113731b052c7979e37379298 100644
--- a/cabal-install-solver/src/Distribution/Solver/Modular/Message.hs
+++ b/cabal-install-solver/src/Distribution/Solver/Modular/Message.hs
@@ -228,7 +228,6 @@ showFR _ (NewPackageHasUnbuildableRequiredComponent comp dr) = " (" ++ showExpos
 showFR _ (PackageRequiresMissingComponent qpn comp) = " (requires " ++ showExposedComponent comp ++ " from " ++ showQPN qpn ++ ", but the component does not exist)"
 showFR _ (PackageRequiresPrivateComponent qpn comp) = " (requires " ++ showExposedComponent comp ++ " from " ++ showQPN qpn ++ ", but the component is private)"
 showFR _ (PackageRequiresUnbuildableComponent qpn comp) = " (requires " ++ showExposedComponent comp ++ " from " ++ showQPN qpn ++ ", but the component is not buildable in the current environment)"
-showFR _ CannotInstall                    = " (only already installed instances can be used)"
 showFR _ CannotReinstall                  = " (avoiding to reinstall a package with same version but new dependencies)"
 showFR _ NotExplicit                      = " (not a user-provided goal nor mentioned as a constraint, but reject-unconstrained-dependencies was set)"
 showFR _ Shadowed                         = " (shadowed by another installed package with same version)"
diff --git a/cabal-install-solver/src/Distribution/Solver/Modular/Preference.hs b/cabal-install-solver/src/Distribution/Solver/Modular/Preference.hs
index 3c5b6c5f9847353649723e3d8d75f1274110e375..9e0d5fb4d2208ea2ac132049ef235cfbfde5da93 100644
--- a/cabal-install-solver/src/Distribution/Solver/Modular/Preference.hs
+++ b/cabal-install-solver/src/Distribution/Solver/Modular/Preference.hs
@@ -12,7 +12,6 @@ module Distribution.Solver.Modular.Preference
     , preferLinked
     , preferPackagePreferences
     , preferReallyEasyGoalChoices
-    , requireInstalled
     , onlyConstrained
     , sortGoals
     , pruneAfterFirstSuccess
@@ -318,18 +317,6 @@ enforceManualFlags pcs = go
       in W.mapWithKey (restrictToggling d flagConstraintValues) ts
     go x                                                            = x
 
--- | Require installed packages.
-requireInstalled :: (PN -> Bool) -> EndoTreeTrav d c
-requireInstalled p = go
-  where
-    go (PChoiceF v@(Q _ pn) rdm gr cs)
-      | p pn      = PChoiceF v rdm gr (W.mapWithKey installed cs)
-      | otherwise = PChoiceF v rdm gr                         cs
-      where
-        installed (POption (I _ (Inst _)) _) x = x
-        installed _ _ = Fail (varToConflictSet (P v)) CannotInstall
-    go x          = x
-
 -- | Avoid reinstalls.
 --
 -- This is a tricky strategy. If a package version is installed already and the
diff --git a/cabal-install-solver/src/Distribution/Solver/Modular/Solver.hs b/cabal-install-solver/src/Distribution/Solver/Modular/Solver.hs
index 87ce414059f8e55dc95bc21aaccadd8cc1d05feb..39bd7bf4690abb3d4bbadae4bf6eefd2ddb7d46f 100644
--- a/cabal-install-solver/src/Distribution/Solver/Modular/Solver.hs
+++ b/cabal-install-solver/src/Distribution/Solver/Modular/Solver.hs
@@ -66,8 +66,6 @@ data SolverConfig = SolverConfig {
   avoidReinstalls        :: AvoidReinstalls,
   shadowPkgs             :: ShadowPkgs,
   strongFlags            :: StrongFlags,
-  allowBootLibInstalls   :: AllowBootLibInstalls,
-  nonInstallablePackages :: [PackageName],
   onlyConstrained        :: OnlyConstrained,
   maxBackjumps           :: Maybe Int,
   enableBackjumping      :: EnableBackjumping,
@@ -141,9 +139,6 @@ solve sc cinfo idx pkgConfigDB userPrefs userConstraints userGoals =
                        validateLinking idx .
                        validateTree cinfo idx pkgConfigDB
     prunePhase       = (if asBool (avoidReinstalls sc) then P.avoidReinstalls (const True) else id) .
-                       (if asBool (allowBootLibInstalls sc)
-                        then id
-                        else P.requireInstalled (`elem` nonInstallablePackages sc)) .
                        (case onlyConstrained sc of
                           OnlyConstrainedAll ->
                             P.onlyConstrained pkgIsExplicit
diff --git a/cabal-install-solver/src/Distribution/Solver/Modular/Tree.hs b/cabal-install-solver/src/Distribution/Solver/Modular/Tree.hs
index 039da4b41b0ed0d92aea2b3c1b7a35cf96a077a9..10d372525b1cf38b92653d9e63863b10e2716eb1 100644
--- a/cabal-install-solver/src/Distribution/Solver/Modular/Tree.hs
+++ b/cabal-install-solver/src/Distribution/Solver/Modular/Tree.hs
@@ -110,7 +110,6 @@ data FailReason = UnsupportedExtension Extension
                 | PackageRequiresMissingComponent QPN ExposedComponent
                 | PackageRequiresPrivateComponent QPN ExposedComponent
                 | PackageRequiresUnbuildableComponent QPN ExposedComponent
-                | CannotInstall
                 | CannotReinstall
                 | NotExplicit
                 | Shadowed
diff --git a/cabal-install-solver/src/Distribution/Solver/Types/ConstraintSource.hs b/cabal-install-solver/src/Distribution/Solver/Types/ConstraintSource.hs
index 7d82125723480a82183bfe8f5a9ef7e485965ce0..dadf8bf08b1bdb6b156415641029a7e3a9461097 100644
--- a/cabal-install-solver/src/Distribution/Solver/Types/ConstraintSource.hs
+++ b/cabal-install-solver/src/Distribution/Solver/Types/ConstraintSource.hs
@@ -27,7 +27,7 @@ data ConstraintSource =
   | ConstraintSourceUserTarget
 
   -- | Internal requirement to use installed versions of packages like ghc-prim.
-  | ConstraintSourceNonUpgradeablePackage
+  | ConstraintSourceNonReinstallablePackage
 
   -- | Internal constraint used by @cabal freeze@.
   | ConstraintSourceFreeze
@@ -64,8 +64,8 @@ showConstraintSource (ConstraintSourceProjectConfig path) =
 showConstraintSource (ConstraintSourceUserConfig path)= "user config " ++ path
 showConstraintSource ConstraintSourceCommandlineFlag = "command line flag"
 showConstraintSource ConstraintSourceUserTarget = "user target"
-showConstraintSource ConstraintSourceNonUpgradeablePackage =
-    "non-upgradeable package"
+showConstraintSource ConstraintSourceNonReinstallablePackage =
+    "non-reinstallable package"
 showConstraintSource ConstraintSourceFreeze = "cabal freeze"
 showConstraintSource ConstraintSourceConfigFlagOrTarget =
     "config file, command line flag, or user target"
diff --git a/cabal-install/src/Distribution/Client/Dependency.hs b/cabal-install/src/Distribution/Client/Dependency.hs
index 056d0ffed057d39013c7afb802eed8188776eb29..749ae0df6d61f787216d2b3b07c4f63c407a1a43 100644
--- a/cabal-install/src/Distribution/Client/Dependency.hs
+++ b/cabal-install/src/Distribution/Client/Dependency.hs
@@ -436,26 +436,18 @@ setSolverVerbosity verbosity params =
     }
 
 -- | Some packages are specific to a given compiler version and should never be
--- upgraded.
-dontUpgradeNonUpgradeablePackages :: DepResolverParams -> DepResolverParams
-dontUpgradeNonUpgradeablePackages params =
+-- reinstalled.
+dontInstallNonReinstallablePackages :: DepResolverParams -> DepResolverParams
+dontInstallNonReinstallablePackages params =
   addConstraints extraConstraints params
   where
     extraConstraints =
       [ LabeledPackageConstraint
         (PackageConstraint (ScopeAnyQualifier pkgname) PackagePropertyInstalled)
-        ConstraintSourceNonUpgradeablePackage
-      | Set.notMember (mkPackageName "base") (depResolverTargets params)
-      , pkgname <- nonUpgradeablePackages
-      , isInstalled pkgname
+        ConstraintSourceNonReinstallablePackage
+      | pkgname <- nonReinstallablePackages
       ]
 
-    isInstalled =
-      not
-        . null
-        . InstalledPackageIndex.lookupPackageName
-          (depResolverInstalledPkgIndex params)
-
 -- | The set of non-reinstallable packages includes those which cannot be
 -- rebuilt using a GHC installation and Hackage-published source distribution.
 -- There are a few reasons why this might be true:
@@ -471,15 +463,8 @@ dontUpgradeNonUpgradeablePackages params =
 --  * the package does not have a complete (that is, buildable) source distribution.
 --    For instance, some packages provided by GHC rely on files outside of the
 --    source tree generated by GHC's build system.
---
--- Note: the list of non-upgradable/non-installable packages used to be
--- respectively in this module and in `Distribution.Solver.Modular.Solver`.
--- Since they were kept synced, they are now combined in the following list.
---
--- See: https://github.com/haskell/cabal/issues/8581 and
--- https://github.com/haskell/cabal/issues/9064.
-nonUpgradeablePackages :: [PackageName]
-nonUpgradeablePackages =
+nonReinstallablePackages :: [PackageName]
+nonReinstallablePackages =
   [ mkPackageName "base"
   , mkPackageName "ghc-bignum"
   , mkPackageName "ghc-prim"
@@ -792,12 +777,6 @@ resolveDependencies
   -> Solver
   -> DepResolverParams
   -> Progress String String SolverInstallPlan
--- TODO: is this needed here? see dontUpgradeNonUpgradeablePackages
-resolveDependencies platform comp _pkgConfigDB _solver params
-  | Set.null (depResolverTargets params) =
-      return (validateSolverResult platform comp indGoals [])
-  where
-    indGoals = depResolverIndependentGoals params
 resolveDependencies platform comp pkgConfigDB solver params =
   Step (showDepResolverParams finalparams) $
     fmap (validateSolverResult platform comp indGoals) $
@@ -812,10 +791,6 @@ resolveDependencies platform comp pkgConfigDB solver params =
             noReinstalls
             shadowing
             strFlags
-            allowBootLibs
-            -- See comment of nonUpgradeablePackages about
-            -- non-installable and non-upgradable packages.
-            nonUpgradeablePackages
             onlyConstrained_
             maxBkjumps
             enableBj
@@ -848,7 +823,7 @@ resolveDependencies platform comp pkgConfigDB solver params =
                     noReinstalls
                     shadowing
                     strFlags
-                    allowBootLibs
+                    _allowBootLibs
                     onlyConstrained_
                     maxBkjumps
                     enableBj
@@ -858,7 +833,7 @@ resolveDependencies platform comp pkgConfigDB solver params =
                   ) =
         if asBool (depResolverAllowBootLibInstalls params)
           then params
-          else dontUpgradeNonUpgradeablePackages params
+          else dontInstallNonReinstallablePackages params
 
     preferences :: PackageName -> PackagePreferences
     preferences = interpretPackagesPreference targets defpref prefs
diff --git a/cabal-install/tests/UnitTests/Distribution/Solver/Modular/Solver.hs b/cabal-install/tests/UnitTests/Distribution/Solver/Modular/Solver.hs
index d5973598fa9a5a726c3a5cfe4bfa35fce3dbc062..123979921b15cfd97cd2349ab9dd4ebd777f4046 100644
--- a/cabal-install/tests/UnitTests/Distribution/Solver/Modular/Solver.hs
+++ b/cabal-install/tests/UnitTests/Distribution/Solver/Modular/Solver.hs
@@ -192,17 +192,17 @@ tests =
       , runTest $ mkTest db12 "baseShim6" ["E"] (solverSuccess [("E", 1), ("syb", 2)])
       ]
   , testGroup
-      "Base and Nonupgradable"
+      "Base and non-reinstallable"
       [ runTest $
           mkTest dbBase "Refuse to install base without --allow-boot-library-installs" ["base"] $
-            solverFailure (isInfixOf "only already installed instances can be used")
+            solverFailure (isInfixOf "rejecting: base-1.0.0 (constraint from non-reinstallable package requires installed instance)")
       , runTest $
           allowBootLibInstalls $
             mkTest dbBase "Install base with --allow-boot-library-installs" ["base"] $
               solverSuccess [("base", 1), ("ghc-prim", 1), ("integer-gmp", 1), ("integer-simple", 1)]
       , runTest $
           mkTest dbNonupgrade "Refuse to install newer ghc requested by another library" ["A"] $
-            solverFailure (isInfixOf "rejecting: ghc-2.0.0 (constraint from non-upgradeable package requires installed instance)")
+            solverFailure (isInfixOf "rejecting: ghc-2.0.0 (constraint from non-reinstallable package requires installed instance)")
       ]
   , testGroup
       "reject-unconstrained"