diff --git a/cabal-testsuite/main/cabal-tests.hs b/cabal-testsuite/main/cabal-tests.hs
index 2ea070bff0790e4e9ce91233660e421f091852ec..8f8e8ec2807eee38cf64823eff4ee06715dcaa73 100644
--- a/cabal-testsuite/main/cabal-tests.hs
+++ b/cabal-testsuite/main/cabal-tests.hs
@@ -34,6 +34,35 @@ import Data.Monoid ((<>))
 import Data.Monoid (mempty)
 #endif
 
+{- Note [Testsuite package environments]
+
+There are three different package environments which are used when running the
+testsuite.
+
+1. Environment used to compile `cabal-tests` executable
+2. Environment used to run test scripts "setup.test.hs"
+3. Environment made available to tests themselves via `./Setup configure`
+
+These are all distinct from each other and should be specified separately.
+
+Where are these environments specified:
+
+1. The build-depends on `cabal-tests` executable in `cabal-testsuite.cabal`
+2. The build-depends of `test-runtime-deps` executable in `cabal-testsuite.cabal`
+   These dependencies are injected in a special module (`Test.Cabal.ScriptEnv0`) which
+   then is consulted in `Test.Cabal.Monad` in order to pass the right environmnet.
+   This is mechanism by which the `./Setup` tests have access to the in-tree `Cabal`
+   and `Cabal-syntax` libraries.
+3. No specification, only the `GlobalPackageDb` is available (see
+   `testPackageDBStack`) unless the test itself augments the environment with
+   `withPackageDb`.
+
+At the moment, `cabal-install` tests always use the bootstrap cabal, which is a
+bit confusing but `cabal-install` is not flexible enough to be given additional
+package databases (yet).
+
+-}
+
 -- | Record for arguments that can be passed to @cabal-tests@ executable.
 data MainArgs = MainArgs {
         mainArgThreads :: Int,
diff --git a/cabal-testsuite/src/Test/Cabal/Monad.hs b/cabal-testsuite/src/Test/Cabal/Monad.hs
index c1ecf3dfecbfa5d0415ac5bf5ebab90fbcacc560..36621773309e8bfc3ac06733b91cf75ad1a6d966 100644
--- a/cabal-testsuite/src/Test/Cabal/Monad.hs
+++ b/cabal-testsuite/src/Test/Cabal/Monad.hs
@@ -289,24 +289,7 @@ runTestM mode m = withSystemTempDirectory "cabal-testsuite" $ \tmp_dir -> do
     -- them up we must configure them
     program_db <- configureAllKnownPrograms verbosity program_db3
 
-    let ghcAndRunnedGhcAreTheSame :: Bool
-        ghcAndRunnedGhcAreTheSame = fromMaybe False $ do
-            ghc_program        <- lookupProgram ghcProgram program_db
-            runner_ghc_program <- lookupProgram ghcProgram (runnerProgramDb senv)
-            return $ programPath ghc_program == programPath runner_ghc_program
-
-    let db_stack =
-            case argGhcPath (testCommonArgs args) of
-                Nothing -> runnerPackageDbStack senv -- NB: canonicalized
-                -- Can't use the build package db stack since they
-                -- are all for the wrong versions!  TODO: Make
-                -- this configurable
-                --
-                -- Oleg: if runner ghc and provided ghc are the same,
-                -- use runnerPackageDbStack. See 'hasCabalForGhc' check.
-                Just _
-                    | ghcAndRunnedGhcAreTheSame -> runnerPackageDbStack senv
-                    | otherwise                 -> [GlobalPackageDB]
+    let db_stack = [GlobalPackageDB]
         env = TestEnv {
                     testSourceDir = script_dir,
                     testTmpDir = tmp_dir,