diff --git a/cabal-install/src/Distribution/Client/ScriptUtils.hs b/cabal-install/src/Distribution/Client/ScriptUtils.hs
index aeae4eaf45912f8f7741b46ff9a06add4d85df9e..d4f152a455715590aacaadb9b9a6c45df53b4392 100644
--- a/cabal-install/src/Distribution/Client/ScriptUtils.hs
+++ b/cabal-install/src/Distribution/Client/ScriptUtils.hs
@@ -305,9 +305,9 @@ withContextAndSelectors noTargets kind flags@NixStyleFlags{..} targetStrings glo
         (withGlobalConfig verbosity globalConfigFlag $ withoutProject mkTmpDir)
 
     (tc', ctx', sels) <- case targetStrings of
-      -- Only script targets may contain spaces and or end with ':'.
+      -- Only script targets may end with ':'.
       -- Trying to readTargetSelectors such a target leads to a parse error.
-      [target] | any (\c -> isSpace c) target || ":" `isSuffixOf` target -> do
+      [target] | ":" `isSuffixOf` target -> do
         scriptOrError target [TargetSelectorNoScript $ TargetString1 target]
       _ -> do
         -- In the case where a selector is both a valid target and script, assume it is a target,
diff --git a/cabal-install/src/Distribution/Client/TargetSelector.hs b/cabal-install/src/Distribution/Client/TargetSelector.hs
index 856168103d199c8f8d73fbbb200dd10b20dd59cf..f287400e1e173a392ac7fcf50758d08a8692a157 100644
--- a/cabal-install/src/Distribution/Client/TargetSelector.hs
+++ b/cabal-install/src/Distribution/Client/TargetSelector.hs
@@ -324,13 +324,13 @@ parseTargetString =
     parseTargetApprox :: Parse.ReadP r TargetString
     parseTargetApprox =
       ( do
-          a <- tokenQ
+          a <- tokenQEnd
           return (TargetString1 a)
       )
         +++ ( do
                 a <- tokenQ0
                 _ <- Parse.char ':'
-                b <- tokenQ
+                b <- tokenQEnd
                 return (TargetString2 a b)
             )
         +++ ( do
@@ -338,7 +338,7 @@ parseTargetString =
                 _ <- Parse.char ':'
                 b <- tokenQ
                 _ <- Parse.char ':'
-                c <- tokenQ
+                c <- tokenQEnd
                 return (TargetString3 a b c)
             )
         +++ ( do
@@ -348,7 +348,7 @@ parseTargetString =
                 _ <- Parse.char ':'
                 c <- tokenQ
                 _ <- Parse.char ':'
-                d <- tokenQ
+                d <- tokenQEnd
                 return (TargetString4 a b c d)
             )
         +++ ( do
@@ -360,7 +360,7 @@ parseTargetString =
                 _ <- Parse.char ':'
                 d <- tokenQ
                 _ <- Parse.char ':'
-                e <- tokenQ
+                e <- tokenQEnd
                 return (TargetString5 a b c d e)
             )
         +++ ( do
@@ -376,7 +376,7 @@ parseTargetString =
                 _ <- Parse.char ':'
                 f <- tokenQ
                 _ <- Parse.char ':'
-                g <- tokenQ
+                g <- tokenQEnd
                 return (TargetString7 a b c d e f g)
             )
 
@@ -384,6 +384,8 @@ parseTargetString =
     tokenQ = parseHaskellString <++ token
     token0 = Parse.munch (\x -> not (isSpace x) && x /= ':')
     tokenQ0 = parseHaskellString <++ token0
+    tokenEnd = Parse.munch1 (/= ':')
+    tokenQEnd = parseHaskellString <++ tokenEnd
     parseHaskellString :: Parse.ReadP r String
     parseHaskellString = Parse.readS_to_P reads
 
diff --git a/cabal-install/tests/IntegrationTests2.hs b/cabal-install/tests/IntegrationTests2.hs
index 6579b2ddcc2f3ac1690bd143a0441d715a03d090..3598b357d699004f98885d56836a7b9794accdf9 100644
--- a/cabal-install/tests/IntegrationTests2.hs
+++ b/cabal-install/tests/IntegrationTests2.hs
@@ -260,11 +260,14 @@ testTargetSelectors reportSubCase = do
                                   ":pkg:q:lib:q:file:Q.y"
                      , "app/Main.hs", "p:app/Main.hs", "exe:ppexe:app/Main.hs", "p:ppexe:app/Main.hs",
                                   ":pkg:p:exe:ppexe:file:app/Main.hs"
+                     , "a p p/Main.hs", "p:a p p/Main.hs", "exe:pppexe:a p p/Main.hs", "p:pppexe:a p p/Main.hs",
+                                  ":pkg:p:exe:pppexe:file:a p p/Main.hs"
                      ]
        ts @?= replicate 5 (TargetComponent "p-0.1" (CLibName LMainLibName) (FileTarget "P"))
            ++ replicate 5 (TargetComponent "q-0.1" (CLibName LMainLibName) (FileTarget "QQ"))
            ++ replicate 5 (TargetComponent "q-0.1" (CLibName LMainLibName) (FileTarget "Q"))
            ++ replicate 5 (TargetComponent "p-0.1" (CExeName "ppexe") (FileTarget ("app" </> "Main.hs")))
+           ++ replicate 5 (TargetComponent "p-0.1" (CExeName "pppexe") (FileTarget ("a p p" </> "Main.hs")))
        -- Note there's a bit of an inconsistency here: for the single-part
        -- syntax the target has to point to a file that exists, whereas for
        -- all the other forms we don't require that.
@@ -278,9 +281,8 @@ testTargetSelectors reportSubCase = do
 testTargetSelectorBadSyntax :: Assertion
 testTargetSelectorBadSyntax = do
     (_, _, _, localPackages, _) <- configureProject testdir config
-    let targets = [ "foo bar",  " foo"
-                  , "foo:", "foo::bar"
-                  , "foo: ", "foo: :bar"
+    let targets = [ "foo:", "foo::bar"
+                  , " :foo", "foo: :bar"
                   , "a:b:c:d:e:f", "a:b:c:d:e:f:g:h" ]
     Left errs <- readTargetSelectors localPackages Nothing targets
     zipWithM_ (@?=) errs (map TargetSelectorUnrecognised targets)
diff --git a/cabal-install/tests/IntegrationTests2/targets/simple/a p p/Main.hs b/cabal-install/tests/IntegrationTests2/targets/simple/a p p/Main.hs
new file mode 100644
index 0000000000000000000000000000000000000000..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391
diff --git a/cabal-install/tests/IntegrationTests2/targets/simple/p.cabal b/cabal-install/tests/IntegrationTests2/targets/simple/p.cabal
index 75b24e0eadc1e889340f0380ae5dd2455499aa0b..33ffc0d3a5f56f953728d04b1e532e3f962179dd 100644
--- a/cabal-install/tests/IntegrationTests2/targets/simple/p.cabal
+++ b/cabal-install/tests/IntegrationTests2/targets/simple/p.cabal
@@ -15,3 +15,8 @@ executable ppexe
   main-is: Main.hs
   hs-source-dirs: app
   other-modules: PMain
+
+executable pppexe
+  main-is: Main.hs
+  hs-source-dirs: "a p p"
+  other-modules: PMain
diff --git a/cabal-testsuite/PackageTests/NewBuild/T8875/T8875.cabal b/cabal-testsuite/PackageTests/NewBuild/T8875/T8875.cabal
new file mode 100644
index 0000000000000000000000000000000000000000..9372c1977f9322c4e81013fdaa9121f88d959fac
--- /dev/null
+++ b/cabal-testsuite/PackageTests/NewBuild/T8875/T8875.cabal
@@ -0,0 +1,9 @@
+cabal-version: 3.0
+name: T8875
+version: 0.1.0.0
+
+executable foo
+    main-is: Main.hs
+    build-depends: base
+    hs-source-dirs: "a app"
+    default-language: Haskell2010
diff --git a/cabal-testsuite/PackageTests/NewBuild/T8875/a app/Main.hs b/cabal-testsuite/PackageTests/NewBuild/T8875/a app/Main.hs
new file mode 100644
index 0000000000000000000000000000000000000000..b3549c2fe3d794dddfdf687ed1163ff5302f20e8
--- /dev/null
+++ b/cabal-testsuite/PackageTests/NewBuild/T8875/a app/Main.hs	
@@ -0,0 +1 @@
+main = return ()
diff --git a/cabal-testsuite/PackageTests/NewBuild/T8875/cabal.out b/cabal-testsuite/PackageTests/NewBuild/T8875/cabal.out
new file mode 100644
index 0000000000000000000000000000000000000000..7bb94dd545c037f0ff624507cc8c5a89d658c023
--- /dev/null
+++ b/cabal-testsuite/PackageTests/NewBuild/T8875/cabal.out
@@ -0,0 +1,8 @@
+# cabal v2-build
+Resolving dependencies...
+Build profile: -w ghc-<GHCVER> -O1
+In order, the following will be built:
+ - T8875-0.1.0.0 (exe:foo) (first run)
+Configuring executable 'foo' for T8875-0.1.0.0...
+Preprocessing executable 'foo' for T8875-0.1.0.0...
+Building executable 'foo' for T8875-0.1.0.0...
diff --git a/cabal-testsuite/PackageTests/NewBuild/T8875/cabal.project b/cabal-testsuite/PackageTests/NewBuild/T8875/cabal.project
new file mode 100644
index 0000000000000000000000000000000000000000..e6fdbadb4398bc0e333947b5fb8021778310d943
--- /dev/null
+++ b/cabal-testsuite/PackageTests/NewBuild/T8875/cabal.project
@@ -0,0 +1 @@
+packages: .
diff --git a/cabal-testsuite/PackageTests/NewBuild/T8875/cabal.test.hs b/cabal-testsuite/PackageTests/NewBuild/T8875/cabal.test.hs
new file mode 100644
index 0000000000000000000000000000000000000000..a9120447cb97a31554630758be8738f5e7eab277
--- /dev/null
+++ b/cabal-testsuite/PackageTests/NewBuild/T8875/cabal.test.hs
@@ -0,0 +1,5 @@
+import Test.Cabal.Prelude
+
+main = cabalTest . void $ do
+    -- Building a target that contains whitespace
+    cabal' "v2-build" ["a app/Main.hs"]
diff --git a/changelog.d/issue-8875 b/changelog.d/issue-8875
new file mode 100644
index 0000000000000000000000000000000000000000..6642609a0e60973e22624780b170801c1f90eafd
--- /dev/null
+++ b/changelog.d/issue-8875
@@ -0,0 +1,10 @@
+synopsis: Allow whitespace in targets
+packages: cabal-install
+prs: #10032
+issues: #8875
+
+description: {
+Allow spaces in the final component of target selectors. This resolves an issue
+where using absolute paths in selectors can fail if there is whitespace in the
+parent directories of the project.
+}