diff --git a/cabal-testsuite/PackageTests/SetupDep/Setup.hs b/cabal-testsuite/PackageTests/SetupDep/Setup.hs
new file mode 100644
index 0000000000000000000000000000000000000000..89d816ae6d9df408a259fe1d12e00ad69280bef8
--- /dev/null
+++ b/cabal-testsuite/PackageTests/SetupDep/Setup.hs
@@ -0,0 +1,6 @@
+module Main where
+
+import SetupDep ( depMain )
+
+main :: IO ()
+main = depMain
diff --git a/cabal-testsuite/PackageTests/SetupDep/SetupDep.hs b/cabal-testsuite/PackageTests/SetupDep/SetupDep.hs
new file mode 100644
index 0000000000000000000000000000000000000000..55220d8ba41f52edc0e2f3362271e5cdad139ac5
--- /dev/null
+++ b/cabal-testsuite/PackageTests/SetupDep/SetupDep.hs
@@ -0,0 +1,6 @@
+module SetupDep where
+
+import Distribution.Simple
+
+depMain :: IO ()
+depMain = defaultMain
diff --git a/cabal-testsuite/PackageTests/SetupDep/cabal.project b/cabal-testsuite/PackageTests/SetupDep/cabal.project
new file mode 100644
index 0000000000000000000000000000000000000000..e6fdbadb4398bc0e333947b5fb8021778310d943
--- /dev/null
+++ b/cabal-testsuite/PackageTests/SetupDep/cabal.project
@@ -0,0 +1 @@
+packages: .
diff --git a/cabal-testsuite/PackageTests/SetupDep/setup-dep.cabal b/cabal-testsuite/PackageTests/SetupDep/setup-dep.cabal
new file mode 100644
index 0000000000000000000000000000000000000000..78d47d16da3cad3730969bfea806964adca4929d
--- /dev/null
+++ b/cabal-testsuite/PackageTests/SetupDep/setup-dep.cabal
@@ -0,0 +1,16 @@
+cabal-version:       2.2
+name:                setup-dep
+version:             0.1.0.0
+synopsis:            Test for a Setup.hs with a dependency
+license:             BSD-3-Clause
+author:              NA
+maintainer:          NA
+category:            Testing
+build-type:          Custom
+
+custom-setup
+  setup-depends: Cabal, base
+
+library
+  build-depends:       base
+  default-language:    Haskell2010
diff --git a/cabal-testsuite/PackageTests/SetupDep/setup.out b/cabal-testsuite/PackageTests/SetupDep/setup.out
new file mode 100644
index 0000000000000000000000000000000000000000..1e49680dc04f6a8381e9a0e1bc913feba8b37d39
--- /dev/null
+++ b/cabal-testsuite/PackageTests/SetupDep/setup.out
@@ -0,0 +1,5 @@
+# Setup configure
+Configuring setup-dep-0.1.0.0...
+# Setup build
+Preprocessing library for setup-dep-0.1.0.0...
+Building library for setup-dep-0.1.0.0...
diff --git a/cabal-testsuite/PackageTests/SetupDep/setup.test.hs b/cabal-testsuite/PackageTests/SetupDep/setup.test.hs
new file mode 100644
index 0000000000000000000000000000000000000000..2df426a5dbf90950ec8f125d12f00b7bf8abb062
--- /dev/null
+++ b/cabal-testsuite/PackageTests/SetupDep/setup.test.hs
@@ -0,0 +1,4 @@
+import Test.Cabal.Prelude
+main = setupTest $ do
+  setup "configure" []
+  setup "build" []
diff --git a/cabal-testsuite/src/Test/Cabal/Script.hs b/cabal-testsuite/src/Test/Cabal/Script.hs
index 943ea784c8d05a638b9d1458eabc7101b9786cc7..308c390140ba82b580f854dd12ee0ae762dafabe 100644
--- a/cabal-testsuite/src/Test/Cabal/Script.hs
+++ b/cabal-testsuite/src/Test/Cabal/Script.hs
@@ -77,23 +77,32 @@ runghc senv mb_cwd env_overrides script_path args = do
 -- script with 'runghc'.
 runnerCommand :: ScriptEnv -> Maybe FilePath -> [(String, Maybe String)]
               -> FilePath -> [String] -> IO (FilePath, [String])
-runnerCommand senv _mb_cwd _env_overrides script_path args = do
+runnerCommand senv mb_cwd _env_overrides script_path args = do
     (prog, _) <- requireProgram verbosity runghcProgram (runnerProgramDb senv)
     return (programPath prog,
             runghc_args ++ ["--"] ++ map ("--ghc-arg="++) ghc_args ++ [script_path] ++ args)
   where
     verbosity = runnerVerbosity senv
     runghc_args = []
-    ghc_args = runnerGhcArgs senv
+    ghc_args = runnerGhcArgs senv mb_cwd
 
 -- | Compute the GHC flags to invoke 'runghc' with under a 'ScriptEnv'.
-runnerGhcArgs :: ScriptEnv -> [String]
-runnerGhcArgs senv =
+runnerGhcArgs :: ScriptEnv -> Maybe FilePath -> [String]
+runnerGhcArgs senv mb_cwd =
     renderGhcOptions (runnerCompiler senv) (runnerPlatform senv) ghc_options
   where
     ghc_options = M.mempty { ghcOptPackageDBs = runnerPackageDbStack senv
                            , ghcOptPackages   = toNubListR (runnerPackages senv)
                            , ghcOptHideAllPackages = Flag True
                            -- Avoid picking stray module files that look
-                           -- like our imports
-                           , ghcOptSourcePathClear = Flag True }
+                           -- like our imports...
+                           , ghcOptSourcePathClear = Flag True
+                           -- ... yet retain the current directory as an included
+                           -- directory, e.g. so that we can compile a Setup.hs
+                           -- script which imports a locally defined module.
+                           -- See the PackageTests/SetupDep test.
+                           , ghcOptSourcePath = toNubListR $
+                              case mb_cwd of
+                                Nothing -> []
+                                Just wd -> [wd]
+                            }
diff --git a/cabal-testsuite/src/Test/Cabal/Server.hs b/cabal-testsuite/src/Test/Cabal/Server.hs
index 145d686bb3018429a282cee914bc058acb95b05f..6f94798b688c09ffde5340de66fb0856dd66a860 100644
--- a/cabal-testsuite/src/Test/Cabal/Server.hs
+++ b/cabal-testsuite/src/Test/Cabal/Server.hs
@@ -218,7 +218,7 @@ runMain ref m = do
 startServer :: Chan ServerLogMsg -> ScriptEnv -> IO Server
 startServer chan senv = do
     (prog, _) <- requireProgram verbosity ghcProgram (runnerProgramDb senv)
-    let ghc_args = runnerGhcArgs senv ++ ["--interactive", "-v0", "-ignore-dot-ghci"]
+    let ghc_args = runnerGhcArgs senv Nothing ++ ["--interactive", "-v0", "-ignore-dot-ghci"]
         proc_spec = (proc (programPath prog) ghc_args) {
                         create_group = True,
                         -- Closing fds is VERY important to avoid