diff --git a/Cabal/doc/developing-packages.rst b/Cabal/doc/developing-packages.rst
index 018da13df2607377de8442a6cca9bbc525bcb07e..73b26108b8d38188e528246c2f57db4abd5ead75 100644
--- a/Cabal/doc/developing-packages.rst
+++ b/Cabal/doc/developing-packages.rst
@@ -1336,6 +1336,10 @@ The following flags are supported by the ``outdated`` command:
 ``--new-freeze-file``
     Read dependency version bounds from the new-style freeze file
     (``cabal.project.freeze``) instead of the package description file.
+``--project-file`` *PROJECTFILE*
+    Read dependendency version bounds from the new-style freeze file
+    related to the named project file (i.e., ``$PROJECTFILE.freeze``)
+    instead of the package desctription file.
 ``--simple-output``
     Print only the names of outdated dependencies, one per line.
 ``--exit-code``
diff --git a/cabal-install/Distribution/Client/Outdated.hs b/cabal-install/Distribution/Client/Outdated.hs
index 8ec0d63bea98800b554add6fe932f88f98d197b6..ea17496cfaf854f54e160d45f3a195693ca2e17a 100644
--- a/cabal-install/Distribution/Client/Outdated.hs
+++ b/cabal-install/Distribution/Client/Outdated.hs
@@ -31,7 +31,8 @@ import Distribution.Package                          (PackageName, packageVersio
 import Distribution.PackageDescription               (allBuildDepends)
 import Distribution.PackageDescription.Configuration (finalizePD)
 import Distribution.Simple.Compiler                  (Compiler, compilerInfo)
-import Distribution.Simple.Setup                     (fromFlagOrDefault)
+import Distribution.Simple.Setup
+       (fromFlagOrDefault, flagToMaybe)
 import Distribution.Simple.Utils
        (die', notice, debug, tryFindPackageDesc)
 import Distribution.System                           (Platform)
@@ -58,8 +59,8 @@ outdated :: Verbosity -> OutdatedFlags -> RepoContext
          -> IO ()
 outdated verbosity0 outdatedFlags repoContext comp platform = do
   let freezeFile    = fromFlagOrDefault False (outdatedFreezeFile outdatedFlags)
-      newFreezeFile = fromFlagOrDefault False
-                      (outdatedNewFreezeFile outdatedFlags)
+      mprojectFile  = flagToMaybe
+                      (outdatedProjectFile outdatedFlags)
       simpleOutput  = fromFlagOrDefault False
                       (outdatedSimpleOutput outdatedFlags)
       quiet         = fromFlagOrDefault False (outdatedQuiet outdatedFlags)
@@ -79,9 +80,11 @@ outdated verbosity0 outdatedFlags repoContext comp platform = do
   let pkgIndex = packageIndex sourcePkgDb
   deps <- if freezeFile
           then depsFromFreezeFile verbosity
-          else if newFreezeFile
-               then depsFromNewFreezeFile verbosity
-               else depsFromPkgDesc       verbosity comp platform
+          else case mprojectFile of
+            Just projectFile
+              -> depsFromNewFreezeFile verbosity projectFile
+            Nothing
+              -> depsFromPkgDesc verbosity comp platform
   debug verbosity $ "Dependencies loaded: "
     ++ (intercalate ", " $ map display deps)
   let outdatedDeps = listOutdated deps pkgIndex
@@ -123,11 +126,10 @@ depsFromFreezeFile verbosity = do
   return deps
 
 -- | Read the list of dependencies from the new-style freeze file.
-depsFromNewFreezeFile :: Verbosity -> IO [Dependency]
-depsFromNewFreezeFile verbosity = do
+depsFromNewFreezeFile :: Verbosity -> FilePath -> IO [Dependency]
+depsFromNewFreezeFile verbosity projectFile = do
   projectRoot <- either throwIO return =<<
-                 findProjectRoot Nothing
-                 {- TODO: Support '--project-file': -} Nothing
+                 findProjectRoot Nothing (Just projectFile)
   let distDirLayout = defaultDistDirLayout projectRoot
                       {- TODO: Support dist dir override -} Nothing
   projectConfig  <- runRebuild (distProjectRootDirectory distDirLayout) $
@@ -135,8 +137,8 @@ depsFromNewFreezeFile verbosity = do
   let ucnstrs = map fst . projectConfigConstraints . projectConfigShared
                 $ projectConfig
       deps    = userConstraintsToDependencies ucnstrs
-  debug verbosity
-    "Reading the list of dependencies from the new-style freeze file"
+  debug verbosity $
+    "Reading the list of dependencies from the new-style freeze file " ++ projectFile ++ ".freeze"
   return deps
 
 -- | Read the list of dependencies from the package description.
diff --git a/cabal-install/Distribution/Client/Setup.hs b/cabal-install/Distribution/Client/Setup.hs
index 305fd553a53b521fe6368d55bb24b438dc856d42..697389ea4af491e4ab7f43c78b0ba785d6f765eb 100644
--- a/cabal-install/Distribution/Client/Setup.hs
+++ b/cabal-install/Distribution/Client/Setup.hs
@@ -1100,7 +1100,7 @@ instance Semigroup IgnoreMajorVersionBumps where
 data OutdatedFlags = OutdatedFlags {
   outdatedVerbosity     :: Flag Verbosity,
   outdatedFreezeFile    :: Flag Bool,
-  outdatedNewFreezeFile :: Flag Bool,
+  outdatedProjectFile   :: Flag FilePath,
   outdatedSimpleOutput  :: Flag Bool,
   outdatedExitCode      :: Flag Bool,
   outdatedQuiet         :: Flag Bool,
@@ -1112,7 +1112,7 @@ defaultOutdatedFlags :: OutdatedFlags
 defaultOutdatedFlags = OutdatedFlags {
   outdatedVerbosity     = toFlag normal,
   outdatedFreezeFile    = mempty,
-  outdatedNewFreezeFile = mempty,
+  outdatedProjectFile   = mempty,
   outdatedSimpleOutput  = mempty,
   outdatedExitCode      = mempty,
   outdatedQuiet         = mempty,
@@ -1140,9 +1140,14 @@ outdatedCommand = CommandUI {
      trueArg
 
     ,option [] ["new-freeze-file"]
-     "Act on the new-style freeze file"
-     outdatedNewFreezeFile (\v flags -> flags { outdatedNewFreezeFile = v })
-     trueArg
+     "Act on the new-style freeze file named cabal.project.freeze"
+     outdatedProjectFile (\_ flags -> flags { outdatedProjectFile = pure "cabal.project" })
+     (noArg mempty)
+
+    ,option [] ["project-file"]
+     "Act on the new-style freeze file named PROJECTFILE.freeze"
+     outdatedProjectFile (\v flags -> flags { outdatedProjectFile = v })
+     (reqArgFlag "PROJECTFILE")
 
     ,option [] ["simple-output"]
      "Only print names of outdated dependencies, one per line"
diff --git a/cabal-install/changelog b/cabal-install/changelog
index 5adc2f0e8e318e267b18f29c6040e476a1c3c9e9..f1e49704f5bd650d2d060fb661e824b31e5f65ee 100644
--- a/cabal-install/changelog
+++ b/cabal-install/changelog
@@ -1,6 +1,8 @@
 -*-change-log-*-
 
 2.4.0.0 (current development version)
+        * 'outdated' now accepts '--project-file FILE', which will look for bounds
+          from the new-style freeze file named FILE.freeze.
 	* 'new-repl' now accepts a '--build-depends' flag which accepts the
 	  same syntax as is used in .cabal files to add additional dependencies
 	  to the environment when developing in the REPL. It is now usable outside
diff --git a/cabal-testsuite/PackageTests/Outdated/outdated-project-file.out b/cabal-testsuite/PackageTests/Outdated/outdated-project-file.out
new file mode 100644
index 0000000000000000000000000000000000000000..af5a361229388d8f0f9a5b277fc553cad2627fb7
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Outdated/outdated-project-file.out
@@ -0,0 +1,5 @@
+# cabal v1-update
+Downloading the latest package list from test-local-repo
+# cabal outdated
+Outdated dependencies:
+base ==3.0.3.2 (latest: 4.0.0.0)
diff --git a/cabal-testsuite/PackageTests/Outdated/outdated-project-file.test.hs b/cabal-testsuite/PackageTests/Outdated/outdated-project-file.test.hs
new file mode 100644
index 0000000000000000000000000000000000000000..96327309f5e6128be4634a716ee88d6656ac9a33
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Outdated/outdated-project-file.test.hs
@@ -0,0 +1,6 @@
+import Test.Cabal.Prelude
+main = cabalTest $ withRepo "repo" $ do
+  res <- cabal' "outdated" ["--project-file", "variant.project"]
+  assertOutputContains "base" res
+  assertOutputDoesNotContain "template-haskell" res
+
diff --git a/cabal-testsuite/PackageTests/Outdated/variant.project b/cabal-testsuite/PackageTests/Outdated/variant.project
new file mode 100644
index 0000000000000000000000000000000000000000..e6fdbadb4398bc0e333947b5fb8021778310d943
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Outdated/variant.project
@@ -0,0 +1 @@
+packages: .
diff --git a/cabal-testsuite/PackageTests/Outdated/variant.project.freeze b/cabal-testsuite/PackageTests/Outdated/variant.project.freeze
new file mode 100644
index 0000000000000000000000000000000000000000..0cc3a7252537b14c826fa4d92bea30c053a2494a
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Outdated/variant.project.freeze
@@ -0,0 +1 @@
+constraints: base == 3.0.3.2