diff --git a/cabal-install/cabal-install.cabal b/cabal-install/cabal-install.cabal
index cef5fbd8277b571aa9065c53a4fbf2dd1d96161e..94080878afaf58c7cb67add8282e48b3bcb5ff69 100644
--- a/cabal-install/cabal-install.cabal
+++ b/cabal-install/cabal-install.cabal
@@ -110,6 +110,7 @@ library
         Distribution.Client.CmdRepl
         Distribution.Client.CmdRun
         Distribution.Client.CmdSdist
+        Distribution.Client.CmdTarget
         Distribution.Client.CmdTest
         Distribution.Client.CmdUpdate
         Distribution.Client.Compat.Directory
diff --git a/cabal-install/src/Distribution/Client/CmdTarget.hs b/cabal-install/src/Distribution/Client/CmdTarget.hs
new file mode 100644
index 0000000000000000000000000000000000000000..c2edeeec89cda317613d40986b3f84cdeffd02bf
--- /dev/null
+++ b/cabal-install/src/Distribution/Client/CmdTarget.hs
@@ -0,0 +1,224 @@
+{-# LANGUAGE NamedFieldPuns #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE RecordWildCards #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+
+module Distribution.Client.CmdTarget
+  ( targetCommand
+  , targetAction
+  ) where
+
+import Distribution.Client.Compat.Prelude
+import Prelude ()
+
+import qualified Data.Map as Map
+import Distribution.Client.CmdBuild (selectComponentTarget, selectPackageTargets)
+import Distribution.Client.CmdErrorMessages
+import Distribution.Client.InstallPlan
+import qualified Distribution.Client.InstallPlan as InstallPlan
+import Distribution.Client.NixStyleOptions
+  ( NixStyleFlags (..)
+  , defaultNixStyleFlags
+  , nixStyleOptions
+  )
+import Distribution.Client.ProjectOrchestration
+import Distribution.Client.ProjectPlanning
+import Distribution.Client.Setup
+  ( ConfigFlags (..)
+  , GlobalFlags
+  )
+import Distribution.Client.TargetProblem
+  ( TargetProblem'
+  )
+import Distribution.Package
+import Distribution.Simple.Command
+  ( CommandUI (..)
+  , usageAlternatives
+  )
+import Distribution.Simple.Flag (fromFlagOrDefault)
+import Distribution.Simple.Utils
+  ( noticeDoc
+  , safeHead
+  , wrapText
+  )
+import Distribution.Verbosity
+  ( normal
+  )
+import Text.PrettyPrint
+import qualified Text.PrettyPrint as Pretty
+
+-------------------------------------------------------------------------------
+-- Command
+-------------------------------------------------------------------------------
+
+targetCommand :: CommandUI (NixStyleFlags ())
+targetCommand =
+  CommandUI
+    { commandName = "v2-target"
+    , commandSynopsis = "Target a subset of all targets."
+    , commandUsage = usageAlternatives "v2-target" ["[TARGETS]"]
+    , commandDescription =
+        Just . const . render $
+          vcat
+            [ intro
+            , vcat $ punctuate (text "\n") [targetForms, ctypes, Pretty.empty]
+            , caution
+            , unique
+            ]
+    , commandNotes = Just $ \pname -> render $ examples pname
+    , commandDefaultFlags = defaultNixStyleFlags ()
+    , commandOptions = nixStyleOptions (const [])
+    }
+  where
+    intro =
+      text . wrapText $
+        "Discover targets in a project for use with other commands taking [TARGETS].\n\n"
+          ++ "This command, like many others, takes [TARGETS]. Taken together, these will"
+          ++ " select for a set of targets in the project. When none are supplied, the"
+          ++ " command acts as if 'all' was supplied."
+          ++ " Targets in the returned subset are shown sorted and fully-qualified."
+
+    targetForms =
+      vcat
+        [ text "A [TARGETS] item can be one of these target forms:"
+        , nest 1 . vcat $
+            (char '-' <+>)
+              <$> [ text "a package target (e.g. [pkg:]package)"
+                  , text "a component target (e.g. [package:][ctype:]component)"
+                  , text "all packages (e.g. all)"
+                  , text "components of a particular type (e.g. package:ctypes or all:ctypes)"
+                  , text "a module target: (e.g. [package:][ctype:]module)"
+                  , text "a filepath target: (e.g. [package:][ctype:]filepath)"
+                  ]
+        ]
+
+    ctypes =
+      vcat
+        [ text "The ctypes, in short form and (long form), can be one of:"
+        , nest 1 . vcat $
+            (char '-' <+>)
+              <$> [ "libs" <+> parens "libraries"
+                  , "exes" <+> parens "executables"
+                  , "tests"
+                  , "benches" <+> parens "benchmarks"
+                  , "flibs" <+> parens "foreign-libraries"
+                  ]
+        ]
+
+    caution =
+      text . wrapText $
+        "WARNING: For a package, all, module or filepath target, cabal target [TARGETS] \
+        \ will only show 'libs' and 'exes' of the [TARGETS] by default. To also show \
+        \ tests and benchmarks, enable them with '--enable-tests' and \
+        \ '--enable-benchmarks'."
+
+    unique =
+      text . wrapText $
+        "NOTE: For commands expecting a unique TARGET, a fully-qualified target is the safe \
+        \ way to go but it may be convenient to type out a shorter TARGET. For example, if the \
+        \ set of 'cabal target all:exes' has one item then 'cabal list-bin all:exes' will \
+        \ work too."
+
+    examples pname =
+      vcat
+        [ text "Examples" Pretty.<> colon
+        , nest 2 $
+            vcat
+              [ vcat
+                  [ text pname <+> text "v2-target all"
+                  , nest 2 $ text "Targets of the package in the current directory or all packages in the project"
+                  ]
+              , vcat
+                  [ text pname <+> text "v2-target pkgname"
+                  , nest 2 $ text "Targets of the package named pkgname in the project"
+                  ]
+              , vcat
+                  [ text pname <+> text "v2-target ./pkgfoo"
+                  , nest 2 $ text "Targets of the package in the ./pkgfoo directory"
+                  ]
+              , vcat
+                  [ text pname <+> text "v2-target cname"
+                  , nest 2 $ text "Targets of the component named cname in the project"
+                  ]
+              ]
+        ]
+
+-------------------------------------------------------------------------------
+-- Action
+-------------------------------------------------------------------------------
+
+targetAction :: NixStyleFlags () -> [String] -> GlobalFlags -> IO ()
+targetAction flags@NixStyleFlags{..} ts globalFlags = do
+  ProjectBaseContext
+    { distDirLayout
+    , cabalDirLayout
+    , projectConfig
+    , localPackages
+    } <-
+    establishProjectBaseContext verbosity cliConfig OtherCommand
+
+  (_, elaboratedPlan, _, _, _) <-
+    rebuildInstallPlan
+      verbosity
+      distDirLayout
+      cabalDirLayout
+      projectConfig
+      localPackages
+      Nothing
+
+  targetSelectors <-
+    either (reportTargetSelectorProblems verbosity) return
+      =<< readTargetSelectors localPackages Nothing targetStrings
+
+  targets :: TargetsMap <-
+    either (reportBuildTargetProblems verbosity) return $
+      resolveTargets
+        selectPackageTargets
+        selectComponentTarget
+        elaboratedPlan
+        Nothing
+        targetSelectors
+
+  printTargetForms verbosity targetStrings targets elaboratedPlan
+  where
+    verbosity = fromFlagOrDefault normal (configVerbosity configFlags)
+    targetStrings = if null ts then ["all"] else ts
+    cliConfig =
+      commandLineFlagsToProjectConfig
+        globalFlags
+        flags
+        mempty
+
+reportBuildTargetProblems :: Verbosity -> [TargetProblem'] -> IO a
+reportBuildTargetProblems verbosity = reportTargetProblems verbosity "target"
+
+printTargetForms :: Verbosity -> [String] -> TargetsMap -> ElaboratedInstallPlan -> IO ()
+printTargetForms verbosity targetStrings targets elaboratedPlan =
+  noticeDoc verbosity $
+    vcat
+      [ text "Fully qualified target forms" Pretty.<> colon
+      , nest 1 $ vcat [text "-" <+> text tf | tf <- targetForms]
+      , found
+      ]
+  where
+    found =
+      let n = length targets
+          t = if n == 1 then "target" else "targets"
+          query = intercalate ", " targetStrings
+       in text "Found" <+> int n <+> text t <+> text "matching" <+> text query Pretty.<> char '.'
+
+    localPkgs =
+      [x | Configured x@ElaboratedConfiguredPackage{elabLocalToProject = True} <- InstallPlan.toList elaboratedPlan]
+
+    targetForm ct x =
+      let pkgId@PackageIdentifier{pkgName = n} = elabPkgSourceId x
+       in render $ pretty n Pretty.<> colon Pretty.<> text (showComponentTarget pkgId ct)
+
+    targetForms =
+      sort $
+        catMaybes
+          [ targetForm ct <$> pkg
+          | (u :: UnitId, xs) <- Map.toAscList targets
+          , let pkg = safeHead $ filter ((== u) . elabUnitId) localPkgs
+          , (ct :: ComponentTarget, _) <- xs
+          ]
diff --git a/cabal-install/src/Distribution/Client/Main.hs b/cabal-install/src/Distribution/Client/Main.hs
index 373662dd8421b9355636e1e86610139e8df7fc8c..39caec854cdb71b1c33f66adce9a090ffc07061c 100644
--- a/cabal-install/src/Distribution/Client/Main.hs
+++ b/cabal-install/src/Distribution/Client/Main.hs
@@ -130,6 +130,7 @@ import qualified Distribution.Client.CmdPath as CmdPath
 import qualified Distribution.Client.CmdRepl as CmdRepl
 import qualified Distribution.Client.CmdRun as CmdRun
 import qualified Distribution.Client.CmdSdist as CmdSdist
+import qualified Distribution.Client.CmdTarget as CmdTarget
 import qualified Distribution.Client.CmdTest as CmdTest
 import qualified Distribution.Client.CmdUpdate as CmdUpdate
 
@@ -460,6 +461,7 @@ mainWorker args = do
           , newCmd CmdExec.execCommand CmdExec.execAction
           , newCmd CmdClean.cleanCommand CmdClean.cleanAction
           , newCmd CmdSdist.sdistCommand CmdSdist.sdistAction
+          , newCmd CmdTarget.targetCommand CmdTarget.targetAction
           , legacyCmd configureExCommand configureAction
           , legacyCmd buildCommand buildAction
           , legacyCmd replCommand replAction
diff --git a/cabal-install/src/Distribution/Client/ProjectOrchestration.hs b/cabal-install/src/Distribution/Client/ProjectOrchestration.hs
index fef9f6efde42d2d97ef8f7d3d5397982fd6586b5..a14d43e4b998f6a5c5a610944d5dc3c7d2396d34 100644
--- a/cabal-install/src/Distribution/Client/ProjectOrchestration.hs
+++ b/cabal-install/src/Distribution/Client/ProjectOrchestration.hs
@@ -934,7 +934,6 @@ distinctTargetComponents targetsMap =
 
 ------------------------------------------------------------------------------
 -- Displaying what we plan to do
---
 
 -- | Print a user-oriented presentation of the install plan, indicating what
 -- will be built.
diff --git a/cabal-install/src/Distribution/Client/Setup.hs b/cabal-install/src/Distribution/Client/Setup.hs
index c68f0dec44a229e62db5b200183a7434d934b4b6..78fcf7c2e1f0096cdccaa7dec01c99e3472c791c 100644
--- a/cabal-install/src/Distribution/Client/Setup.hs
+++ b/cabal-install/src/Distribution/Client/Setup.hs
@@ -282,6 +282,7 @@ globalCommand commands =
               , "unpack"
               , "init"
               , "configure"
+              , "target"
               , "build"
               , "clean"
               , "run"
@@ -302,6 +303,7 @@ globalCommand commands =
               , "path"
               , "new-build"
               , "new-configure"
+              , "new-target"
               , "new-repl"
               , "new-freeze"
               , "new-run"
@@ -334,7 +336,8 @@ globalCommand commands =
               , "v1-register"
               , "v1-reconfigure"
               , -- v2 commands, nix-style
-                "v2-build"
+                "v2-target"
+              , "v2-build"
               , "v2-configure"
               , "v2-repl"
               , "v2-freeze"
@@ -379,6 +382,7 @@ globalCommand commands =
                 , addCmd "gen-bounds"
                 , addCmd "outdated"
                 , addCmd "path"
+                , addCmd "target"
                 , par
                 , startGroup "project building and installing"
                 , addCmd "build"
@@ -406,6 +410,7 @@ globalCommand commands =
                 , addCmd "hscolour"
                 , par
                 , startGroup "new-style projects (forwards-compatible aliases)"
+                , addCmd "v2-target"
                 , addCmd "v2-build"
                 , addCmd "v2-configure"
                 , addCmd "v2-repl"
diff --git a/cabal-testsuite/PackageTests/Target/cabal.all-benches.out b/cabal-testsuite/PackageTests/Target/cabal.all-benches.out
new file mode 100644
index 0000000000000000000000000000000000000000..ea70119f01971cee49d7fe59d5b4d594b437b337
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Target/cabal.all-benches.out
@@ -0,0 +1,8 @@
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Resolving dependencies...
+Fully qualified target forms:
+ - a:bench:a-bench
+ - b:bench:b-bench
+Found 2 targets matching all:benches.
diff --git a/cabal-testsuite/PackageTests/Target/cabal.all-enable-benches.out b/cabal-testsuite/PackageTests/Target/cabal.all-enable-benches.out
new file mode 100644
index 0000000000000000000000000000000000000000..76e0c88fe29fa82821ed7b62ce8a2a649907b17e
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Target/cabal.all-enable-benches.out
@@ -0,0 +1,15 @@
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Resolving dependencies...
+Fully qualified target forms:
+ - a:bench:a-bench
+ - a:exe:a-exe
+ - a:lib:a
+ - a:lib:a-sublib
+ - b:bench:b-bench
+ - b:exe:b-exe
+ - b:lib:b
+ - b:lib:b-sublib
+ - c:lib:c
+Found 9 targets matching all.
diff --git a/cabal-testsuite/PackageTests/Target/cabal.all-enable-tests.out b/cabal-testsuite/PackageTests/Target/cabal.all-enable-tests.out
new file mode 100644
index 0000000000000000000000000000000000000000..de04e17ca32f8914d4cbfc48e94139234f8face1
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Target/cabal.all-enable-tests.out
@@ -0,0 +1,15 @@
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Resolving dependencies...
+Fully qualified target forms:
+ - a:exe:a-exe
+ - a:lib:a
+ - a:lib:a-sublib
+ - a:test:a-test
+ - b:exe:b-exe
+ - b:lib:b
+ - b:lib:b-sublib
+ - b:test:b-test
+ - c:lib:c
+Found 9 targets matching all.
diff --git a/cabal-testsuite/PackageTests/Target/cabal.all-exes.out b/cabal-testsuite/PackageTests/Target/cabal.all-exes.out
new file mode 100644
index 0000000000000000000000000000000000000000..c9c362a5f7b79a4897761e1d8d3a84435a8228ac
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Target/cabal.all-exes.out
@@ -0,0 +1,8 @@
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Resolving dependencies...
+Fully qualified target forms:
+ - a:exe:a-exe
+ - b:exe:b-exe
+Found 2 targets matching all:exes.
diff --git a/cabal-testsuite/PackageTests/Target/cabal.all-tests.out b/cabal-testsuite/PackageTests/Target/cabal.all-tests.out
new file mode 100644
index 0000000000000000000000000000000000000000..7511696f48a98b62b8f277eea259068d6c7b5b3e
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Target/cabal.all-tests.out
@@ -0,0 +1,8 @@
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Resolving dependencies...
+Fully qualified target forms:
+ - a:test:a-test
+ - b:test:b-test
+Found 2 targets matching all:tests.
diff --git a/cabal-testsuite/PackageTests/Target/cabal.component-target-bench.out b/cabal-testsuite/PackageTests/Target/cabal.component-target-bench.out
new file mode 100644
index 0000000000000000000000000000000000000000..9ec0e6f070540535e66aa5d9d15e595b30fa7fb9
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Target/cabal.component-target-bench.out
@@ -0,0 +1,19 @@
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Resolving dependencies...
+Fully qualified target forms:
+ - a:bench:a-bench
+Found 1 target matching a:bench:a-bench.
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Fully qualified target forms:
+ - a:bench:a-bench
+Found 1 target matching bench:a-bench.
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Fully qualified target forms:
+ - a:bench:a-bench
+Found 1 target matching a:a-bench.
diff --git a/cabal-testsuite/PackageTests/Target/cabal.component-target-exe.out b/cabal-testsuite/PackageTests/Target/cabal.component-target-exe.out
new file mode 100644
index 0000000000000000000000000000000000000000..84f1841fa2cd3e9423735e08f2235d24b4e64cce
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Target/cabal.component-target-exe.out
@@ -0,0 +1,19 @@
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Resolving dependencies...
+Fully qualified target forms:
+ - a:exe:a-exe
+Found 1 target matching a:exe:a-exe.
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Fully qualified target forms:
+ - a:exe:a-exe
+Found 1 target matching exe:a-exe.
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Fully qualified target forms:
+ - a:exe:a-exe
+Found 1 target matching a:a-exe.
diff --git a/cabal-testsuite/PackageTests/Target/cabal.component-target-lib.out b/cabal-testsuite/PackageTests/Target/cabal.component-target-lib.out
new file mode 100644
index 0000000000000000000000000000000000000000..63925d3dffd8ae7934134f11cfec66bc76da208e
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Target/cabal.component-target-lib.out
@@ -0,0 +1,19 @@
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Resolving dependencies...
+Fully qualified target forms:
+ - a:lib:a
+Found 1 target matching a:lib:a.
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Fully qualified target forms:
+ - a:lib:a
+Found 1 target matching lib:a.
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Fully qualified target forms:
+ - a:lib:a
+Found 1 target matching a:a.
diff --git a/cabal-testsuite/PackageTests/Target/cabal.component-target-test.out b/cabal-testsuite/PackageTests/Target/cabal.component-target-test.out
new file mode 100644
index 0000000000000000000000000000000000000000..890e8e0ea390ca7232bfe54bbd20982229254913
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Target/cabal.component-target-test.out
@@ -0,0 +1,19 @@
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Resolving dependencies...
+Fully qualified target forms:
+ - a:test:a-test
+Found 1 target matching a:test:a-test.
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Fully qualified target forms:
+ - a:test:a-test
+Found 1 target matching test:a-test.
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Fully qualified target forms:
+ - a:test:a-test
+Found 1 target matching a:a-test.
diff --git a/cabal-testsuite/PackageTests/Target/cabal.ctype-target.out b/cabal-testsuite/PackageTests/Target/cabal.ctype-target.out
new file mode 100644
index 0000000000000000000000000000000000000000..98c0e43d833e0c9e14a1275c6d9b8475b0697861
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Target/cabal.ctype-target.out
@@ -0,0 +1,26 @@
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Resolving dependencies...
+Fully qualified target forms:
+ - a:lib:a
+ - a:lib:a-sublib
+Found 2 targets matching a:libs.
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Fully qualified target forms:
+ - a:exe:a-exe
+Found 1 target matching a:exes.
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Fully qualified target forms:
+ - a:test:a-test
+Found 1 target matching a:tests.
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Fully qualified target forms:
+ - a:bench:a-bench
+Found 1 target matching a:benches.
diff --git a/cabal-testsuite/PackageTests/Target/cabal.default-all.out b/cabal-testsuite/PackageTests/Target/cabal.default-all.out
new file mode 100644
index 0000000000000000000000000000000000000000..3c387ebf42e6940f5c99a1bd7ad01d32a8f25b49
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Target/cabal.default-all.out
@@ -0,0 +1,13 @@
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Resolving dependencies...
+Fully qualified target forms:
+ - a:exe:a-exe
+ - a:lib:a
+ - a:lib:a-sublib
+ - b:exe:b-exe
+ - b:lib:b
+ - b:lib:b-sublib
+ - c:lib:c
+Found 7 targets matching all.
diff --git a/cabal-testsuite/PackageTests/Target/cabal.everything.out b/cabal-testsuite/PackageTests/Target/cabal.everything.out
new file mode 100644
index 0000000000000000000000000000000000000000..c3cc5659a55c0384312f67b6b4af6b563bd3a775
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Target/cabal.everything.out
@@ -0,0 +1,17 @@
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Resolving dependencies...
+Fully qualified target forms:
+ - a:bench:a-bench
+ - a:exe:a-exe
+ - a:lib:a
+ - a:lib:a-sublib
+ - a:test:a-test
+ - b:bench:b-bench
+ - b:exe:b-exe
+ - b:lib:b
+ - b:lib:b-sublib
+ - b:test:b-test
+ - c:lib:c
+Found 11 targets matching all.
diff --git a/cabal-testsuite/PackageTests/Target/cabal.explicit-all.out b/cabal-testsuite/PackageTests/Target/cabal.explicit-all.out
new file mode 100644
index 0000000000000000000000000000000000000000..3c387ebf42e6940f5c99a1bd7ad01d32a8f25b49
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Target/cabal.explicit-all.out
@@ -0,0 +1,13 @@
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Resolving dependencies...
+Fully qualified target forms:
+ - a:exe:a-exe
+ - a:lib:a
+ - a:lib:a-sublib
+ - b:exe:b-exe
+ - b:lib:b
+ - b:lib:b-sublib
+ - c:lib:c
+Found 7 targets matching all.
diff --git a/cabal-testsuite/PackageTests/Target/cabal.missing-target.out b/cabal-testsuite/PackageTests/Target/cabal.missing-target.out
new file mode 100644
index 0000000000000000000000000000000000000000..973cc5d97f1eb068f887b2e6f1e4894b8244bf31
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Target/cabal.missing-target.out
@@ -0,0 +1,16 @@
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Resolving dependencies...
+Error: [Cabal-7127]
+Cannot target the executables in the package c-0.1 because it does not contain any executables. Check the .cabal file for the package and make sure that it properly declares the components that you expect.
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Error: [Cabal-7127]
+Cannot target the test suites in the package c-0.1 because it does not contain any test suites. Check the .cabal file for the package and make sure that it properly declares the components that you expect.
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Error: [Cabal-7127]
+Cannot target the benchmarks in the package c-0.1 because it does not contain any benchmarks. Check the .cabal file for the package and make sure that it properly declares the components that you expect.
diff --git a/cabal-testsuite/PackageTests/Target/cabal.package-target.out b/cabal-testsuite/PackageTests/Target/cabal.package-target.out
new file mode 100644
index 0000000000000000000000000000000000000000..8b122c97a69f51c2f99ead89b5fbdabf8c62811c
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Target/cabal.package-target.out
@@ -0,0 +1,20 @@
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Resolving dependencies...
+Fully qualified target forms:
+ - a:exe:a-exe
+ - a:lib:a
+ - a:lib:a-sublib
+Found 3 targets matching a.
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Resolving dependencies...
+Fully qualified target forms:
+ - a:bench:a-bench
+ - a:exe:a-exe
+ - a:lib:a
+ - a:lib:a-sublib
+ - a:test:a-test
+Found 5 targets matching a.
diff --git a/cabal-testsuite/PackageTests/Target/cabal.path-target.out b/cabal-testsuite/PackageTests/Target/cabal.path-target.out
new file mode 100644
index 0000000000000000000000000000000000000000..4e4bc9cec2092a91b1e9fdc18d6313d6295b59af
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Target/cabal.path-target.out
@@ -0,0 +1,20 @@
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Resolving dependencies...
+Fully qualified target forms:
+ - a:exe:a-exe
+ - a:lib:a
+ - a:lib:a-sublib
+Found 3 targets matching dir-a/.
+# cabal v2-target
+Configuration is affected by the following files:
+- cabal.project
+Resolving dependencies...
+Fully qualified target forms:
+ - a:bench:a-bench
+ - a:exe:a-exe
+ - a:lib:a
+ - a:lib:a-sublib
+ - a:test:a-test
+Found 5 targets matching dir-a/.
diff --git a/cabal-testsuite/PackageTests/Target/cabal.project b/cabal-testsuite/PackageTests/Target/cabal.project
new file mode 100644
index 0000000000000000000000000000000000000000..5cad90c821031482e5111adfe41e3c7c22f966b4
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Target/cabal.project
@@ -0,0 +1 @@
+packages: dir-a dir-b dir-c
diff --git a/cabal-testsuite/PackageTests/Target/cabal.test.hs b/cabal-testsuite/PackageTests/Target/cabal.test.hs
new file mode 100644
index 0000000000000000000000000000000000000000..4307b5ecfb6242c5ef1a41f15ba2c6aa09dbf1ee
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Target/cabal.test.hs
@@ -0,0 +1,65 @@
+import Test.Cabal.Prelude
+
+main = do
+  cabalTest' "default-all" $ do
+    cabal "v2-target" []
+
+  cabalTest' "explicit-all" $ do
+    cabal "v2-target" ["all"]
+
+  cabalTest' "all-enable-tests" $ do
+    cabal "v2-target" ["all", "--enable-tests"]
+
+  cabalTest' "all-enable-benches" $ do
+    cabal "v2-target" ["all", "--enable-benchmarks"]
+
+  cabalTest' "everything" $ do
+    cabal "v2-target" ["all", "--enable-tests", "--enable-benchmarks"]
+
+  cabalTest' "all-exes" $ do
+    cabal "v2-target" ["all:exes"]
+
+  cabalTest' "all-tests" $ do
+    cabal "v2-target" ["all:tests"]
+
+  cabalTest' "all-benches" $ do
+    cabal "v2-target" ["all:benches"]
+
+  cabalTest' "package-target" $ do
+    cabal "v2-target" ["a"]
+    cabal "v2-target" ["a", "--enable-tests", "--enable-benchmarks"]
+
+  cabalTest' "path-target" $ do
+    cabal "v2-target" ["dir-a/"]
+    cabal "v2-target" ["dir-a/", "--enable-tests", "--enable-benchmarks"]
+
+  cabalTest' "component-target-lib" $ do
+    cabal "v2-target" ["a:lib:a"]
+    cabal "v2-target" ["lib:a"]
+    cabal "v2-target" ["a:a"]
+
+  cabalTest' "component-target-exe" $ do
+    cabal "v2-target" ["a:exe:a-exe"]
+    cabal "v2-target" ["exe:a-exe"]
+    cabal "v2-target" ["a:a-exe"]
+
+  cabalTest' "component-target-bench" $ do
+    cabal "v2-target" ["a:bench:a-bench"]
+    cabal "v2-target" ["bench:a-bench"]
+    cabal "v2-target" ["a:a-bench"]
+
+  cabalTest' "component-target-test" $ do
+    cabal "v2-target" ["a:test:a-test"]
+    cabal "v2-target" ["test:a-test"]
+    cabal "v2-target" ["a:a-test"]
+
+  cabalTest' "ctype-target" $ do
+    cabal "v2-target" ["a:libs"]
+    cabal "v2-target" ["a:exes"]
+    cabal "v2-target" ["a:tests"]
+    cabal "v2-target" ["a:benches"]
+
+  cabalTest' "missing-target" $ do
+    fails $ cabal "v2-target" ["c:exes"]
+    fails $ cabal "v2-target" ["c:tests"]
+    fails $ cabal "v2-target" ["c:benches"]
diff --git a/cabal-testsuite/PackageTests/Target/dir-a/a.cabal b/cabal-testsuite/PackageTests/Target/dir-a/a.cabal
new file mode 100644
index 0000000000000000000000000000000000000000..681032bcdf078e033eba613ad252c2c86039c6c8
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Target/dir-a/a.cabal
@@ -0,0 +1,15 @@
+name:           a
+version:        0.1
+license:        BSD3
+cabal-version:  >= 1.8
+build-type:     Simple
+
+library
+library a-sublib
+executable a-exe
+test-suite a-test
+    type: exitcode-stdio-1.0
+    main-is: Test.hs
+benchmark a-bench
+    type: exitcode-stdio-1.0
+    main-is: Bench.hs
diff --git a/cabal-testsuite/PackageTests/Target/dir-b/b.cabal b/cabal-testsuite/PackageTests/Target/dir-b/b.cabal
new file mode 100644
index 0000000000000000000000000000000000000000..b31ca9e81d380fd56f2a224eea0c1667602b7555
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Target/dir-b/b.cabal
@@ -0,0 +1,15 @@
+name:           b
+version:        0.1
+license:        BSD3
+cabal-version:  >= 1.8
+build-type:     Simple
+
+library
+library b-sublib
+executable b-exe
+test-suite b-test
+    type: exitcode-stdio-1.0
+    main-is: Test.hs
+benchmark b-bench
+    type: exitcode-stdio-1.0
+    main-is: Bench.hs
diff --git a/cabal-testsuite/PackageTests/Target/dir-c/c.cabal b/cabal-testsuite/PackageTests/Target/dir-c/c.cabal
new file mode 100644
index 0000000000000000000000000000000000000000..875f7a9fc69ff9a70f21a615efbb028268c9c8c5
--- /dev/null
+++ b/cabal-testsuite/PackageTests/Target/dir-c/c.cabal
@@ -0,0 +1,7 @@
+name:           c
+version:        0.1
+license:        BSD3
+cabal-version:  >= 1.8
+build-type:     Simple
+
+library
diff --git a/changelog.d/pr-9744.md b/changelog.d/pr-9744.md
new file mode 100644
index 0000000000000000000000000000000000000000..6f149d82162c155733e190f4ac52f0d5252c2570
--- /dev/null
+++ b/changelog.d/pr-9744.md
@@ -0,0 +1,18 @@
+---
+synopsis: Discover targets in a project
+packages: [cabal-install]
+prs: 9744
+issues: [4070,8953]
+significance: significant
+---
+
+Adds a `cabal target` command that is useful for discovering targets in a
+project for use with other commands taking ``[TARGETS]``.
+
+Any target form except for a script target can be used with ``cabal target``.
+
+This command, like many others, takes ``[TARGETS]``. Taken together, these will
+select for a set of targets in the project. When none are supplied, the command
+acts as if ``all`` was supplied. Targets in the returned subset are shown sorted
+and fully-qualified with package, component type and component name such as
+`Cabal-tests:test:hackage-tests`.
diff --git a/doc/cabal-commands.rst b/doc/cabal-commands.rst
index 6a1d9e6e6957f7e25f529e60efe482be5f23a34b..7f0b37ac48f3564ccad33bd499d40b49fcf2f97b 100644
--- a/doc/cabal-commands.rst
+++ b/doc/cabal-commands.rst
@@ -36,6 +36,7 @@ Commands
       gen-bounds             Generate dependency bounds.
       outdated               Check for outdated dependencies.
       path                   Query for simple project information.
+      target                 Target a subset of all targets.
 
      [project building and installing]
       build                  Compile targets within the project.
@@ -212,6 +213,8 @@ Arguments and flags common to some or all commands are:
 
     Already generated `build-info.json` files will be removed since they would be stale otherwise.
 
+.. _target-forms:
+
 Target Forms
 ------------
 
@@ -734,6 +737,53 @@ Scripting example:
    $ ls $(cabal path --installdir)
    ...
 
+cabal target
+^^^^^^^^^^^^
+
+This command is useful for discovering targets in a project for use with other
+commands taking ``[TARGETS]``.
+
+Any :ref:`target form<target-forms>` except for a script target can be used with
+``cabal target``.
+
+This command, like many others, takes ``[TARGETS]``. Taken together, these will
+select for a set of targets in the project. When none are supplied, the command
+acts as if ``all`` was supplied. Targets in the returned subset are shown sorted
+and fully-qualified.
+
+.. code-block:: console
+
+    $ cabal target all:tests
+    ...
+    Fully qualified target forms:
+     - Cabal-tests:test:check-tests
+     - Cabal-tests:test:custom-setup-tests
+     - Cabal-tests:test:hackage-tests
+     - Cabal-tests:test:no-thunks-test
+     - Cabal-tests:test:parser-tests
+     - Cabal-tests:test:rpmvercmp
+     - Cabal-tests:test:unit-tests
+     - cabal-benchmarks:test:cabal-benchmarks
+     - cabal-install-solver:test:unit-tests
+     - cabal-install:test:integration-tests2
+     - cabal-install:test:long-tests
+     - cabal-install:test:mem-use-tests
+     - cabal-install:test:unit-tests
+     - solver-benchmarks:test:unit-tests
+
+.. warning::
+
+    For a package, all, module or filepath target, ``cabal target [TARGETS]`` will
+    only show ``libs`` and ``exes`` of the ``[TARGETS]`` by default. To also show tests and
+    benchmarks, enable them with ``--enable-tests`` and ``--enable-benchmarks``.
+
+.. note::
+
+    For commands expecting a unique ``TARGET``, a fully-qualified target is the safe
+    way to go but it may be convenient to type out a shorter ``TARGET``. For
+    example, if the set of ``cabal target all:exes`` has one item then ``cabal
+    list-bin all:exes`` will work too.
+
 .. _command-group-build:
 
 Project building and installing