diff --git a/Cabal/Cabal.cabal b/Cabal/Cabal.cabal
index a0ddc690df97785a3e110f578187ca5c1c69c6c5..a7e6ff46e858832f091f30218e75dcf8c9cdf57a 100644
--- a/Cabal/Cabal.cabal
+++ b/Cabal/Cabal.cabal
@@ -117,13 +117,14 @@ extra-source-files:
   tests/PackageTests/TestSuiteTests/ExeV10/Foo.hs
   tests/PackageTests/TestSuiteTests/ExeV10/my.cabal
   tests/PackageTests/TestSuiteTests/ExeV10/tests/test-Foo.hs
-  tests/PackageTests/TestSuiteTests/LibV09/LibV09.cabal
   tests/PackageTests/TestSuiteTests/LibV09/Lib.hs
+  tests/PackageTests/TestSuiteTests/LibV09/LibV09.cabal
   tests/PackageTests/TestSuiteTests/LibV09/tests/Deadlock.hs
   tests/PackageTests/UniqueIPID/P1/M.hs
   tests/PackageTests/UniqueIPID/P1/my.cabal
   tests/PackageTests/UniqueIPID/P2/M.hs
   tests/PackageTests/UniqueIPID/P2/my.cabal
+  tests/PackageTests/multInst/my.cabal
   tests/Setup.hs
   tests/Test/Distribution/Version.hs
   tests/Test/Laws.hs
diff --git a/cabal-install/cabal-install.cabal b/cabal-install/cabal-install.cabal
index 7a500fbfb4e0f90ba13a094934dddc2990de279e..1ba5fba8751e483323137d237f5f51b25e968e58 100644
--- a/cabal-install/cabal-install.cabal
+++ b/cabal-install/cabal-install.cabal
@@ -27,7 +27,35 @@ Extra-Source-Files:
   README.md bash-completion/cabal bootstrap.sh changelog
 
   -- Generated with '../Cabal/misc/gen-extra-source-files.sh | sort'
-  tests/PackageTests/Freeze/my.cabal
+  tests/IntegrationTests/exec/common.sh
+  tests/IntegrationTests/exec/should_run/Foo.hs
+  tests/IntegrationTests/exec/should_run/My.hs
+  tests/IntegrationTests/exec/should_run/adds_sandbox_bin_directory_to_path.sh
+  tests/IntegrationTests/exec/should_run/auto_configures_on_exec.sh
+  tests/IntegrationTests/exec/should_run/can_run_executables_installed_in_sandbox.sh
+  tests/IntegrationTests/exec/should_run/configures_cabal_to_use_sandbox.sh
+  tests/IntegrationTests/exec/should_run/configures_ghc_to_use_sandbox.sh
+  tests/IntegrationTests/exec/should_run/exit_with_failure_without_args.sh
+  tests/IntegrationTests/exec/should_run/my.cabal
+  tests/IntegrationTests/exec/should_run/runs_given_command.sh
+  tests/IntegrationTests/freeze/common.sh
+  tests/IntegrationTests/freeze/should_run/disable_benchmarks_freezes_bench_deps.sh
+  tests/IntegrationTests/freeze/should_run/disable_tests_freezes_test_deps.sh
+  tests/IntegrationTests/freeze/should_run/does_not_freeze_nondeps.sh
+  tests/IntegrationTests/freeze/should_run/does_not_freeze_self.sh
+  tests/IntegrationTests/freeze/should_run/dry_run_does_not_create_config.sh
+  tests/IntegrationTests/freeze/should_run/enable_benchmarks_freezes_bench_deps.sh
+  tests/IntegrationTests/freeze/should_run/enable_tests_freezes_test_deps.sh
+  tests/IntegrationTests/freeze/should_run/freezes_direct_dependencies.sh
+  tests/IntegrationTests/freeze/should_run/freezes_transitive_dependencies.sh
+  tests/IntegrationTests/freeze/should_run/my.cabal
+  tests/IntegrationTests/freeze/should_run/runs_without_error.sh
+  tests/IntegrationTests/multiple-source/common.sh
+  tests/IntegrationTests/multiple-source/should_run/finds_second_source_of_multiple_source.sh
+  tests/IntegrationTests/multiple-source/should_run/p/Setup.hs
+  tests/IntegrationTests/multiple-source/should_run/p/p.cabal
+  tests/IntegrationTests/multiple-source/should_run/q/Setup.hs
+  tests/IntegrationTests/multiple-source/should_run/q/q.cabal
 
 source-repository head
   type:     git
@@ -229,29 +257,20 @@ Test-Suite unit-tests
     ghc-options: -threaded
   default-language: Haskell2010
 
--- Large, system tests that build packages.
-test-suite package-tests
+test-suite integration-tests
   type: exitcode-stdio-1.0
   hs-source-dirs: tests
-  main-is: PackageTests.hs
-  other-modules:
-    PackageTests.Exec.Check
-    PackageTests.Freeze.Check
-    PackageTests.MultipleSource.Check
-    PackageTests.PackageTester
+  main-is: IntegrationTests.hs
   build-depends:
     Cabal,
-    QuickCheck >= 2.1.0.1 && < 2.9,
+    async,
     base,
     bytestring,
     directory,
-    extensible-exceptions,
     filepath,
     process,
-    regex-posix,
     tasty,
-    tasty-hunit,
-    tasty-quickcheck
+    tasty-hunit
 
   if os(windows)
     build-depends: Win32 >= 2 && < 3
diff --git a/cabal-install/tests/IntegrationTests.hs b/cabal-install/tests/IntegrationTests.hs
new file mode 100644
index 0000000000000000000000000000000000000000..f6c10e0e0ef16553bfb01074ccd7a89db51381be
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests.hs
@@ -0,0 +1,274 @@
+-- | Groups black-box tests of cabal-install and configures them to test
+-- the correct binary.
+--
+-- This file should do nothing but import tests from other modules and run
+-- them with the path to the correct cabal-install binary.
+module Main
+       where
+
+-- Modules from Cabal.
+import Distribution.Compat.CreatePipe (createPipe)
+import Distribution.Compat.Environment (setEnv)
+import Distribution.Compat.Internal.TempFile (createTempDirectory)
+import Distribution.Simple.Configure (findDistPrefOrDefault)
+import Distribution.Simple.Program.Builtin (ghcPkgProgram)
+import Distribution.Simple.Program.Db
+        (defaultProgramDb, requireProgram, setProgramSearchPath)
+import Distribution.Simple.Program.Find
+        (ProgramSearchPathEntry(ProgramSearchPathDir), defaultProgramSearchPath)
+import Distribution.Simple.Program.Types
+        ( Program(..), simpleProgram, programPath)
+import Distribution.Simple.Setup ( Flag(..) )
+import Distribution.Simple.Utils ( findProgramVersion, copyDirectoryRecursive )
+import Distribution.Verbosity (normal)
+
+-- Third party modules.
+import Control.Concurrent.Async (withAsync, wait)
+import Control.Exception (bracket)
+import System.Directory
+        ( canonicalizePath
+        , getDirectoryContents
+        , getTemporaryDirectory
+        , doesDirectoryExist
+        , removeDirectoryRecursive
+        , doesFileExist )
+import System.FilePath ((</>), replaceExtension)
+import Test.Tasty (TestTree, defaultMain, testGroup)
+import Test.Tasty.HUnit (testCase, Assertion, assertFailure)
+import Control.Monad ( filterM, forM, when )
+import Data.List (isPrefixOf, isSuffixOf, sort)
+import Data.IORef (newIORef, writeIORef, readIORef)
+import System.Exit (ExitCode(..))
+import System.IO (withBinaryFile, IOMode(ReadMode))
+import System.Process (runProcess, waitForProcess)
+import qualified Data.ByteString as B
+import qualified Data.ByteString.Char8 as C8
+import           Data.ByteString (ByteString)
+
+-- | Test case.
+data TestCase = TestCase
+    { tcName :: String -- ^ Name of the shell script
+    , tcBaseDirectory :: FilePath
+    , tcCategory :: String
+    , tcShouldX :: String
+    , tcStdOutPath :: Maybe FilePath -- ^ File path of "golden standard output"
+    , tcStdErrPath :: Maybe FilePath -- ^ File path of "golden standard error"
+    }
+
+-- | Test result.
+data TestResult = TestResult
+    { trExitCode :: ExitCode
+    , trStdOut :: ByteString
+    , trStdErr :: ByteString
+    , trWorkingDirectory :: FilePath
+    }
+
+-- | Cabal executable
+cabalProgram :: Program
+cabalProgram = (simpleProgram "cabal") {
+    programFindVersion = findProgramVersion "--numeric-version" id
+  }
+
+-- | Convert test result to string.
+testResultToString :: TestResult -> String
+testResultToString testResult =
+    exitStatus ++ "\n" ++ workingDirectory ++ "\n\n" ++ stdOut ++ "\n\n" ++ stdErr
+  where
+    exitStatus = "Exit status: " ++ show (trExitCode testResult)
+    workingDirectory = "Working directory: " ++ (trWorkingDirectory testResult)
+    stdOut = "<stdout> was:\n" ++ C8.unpack (trStdOut testResult)
+    stdErr = "<stderr> was:\n" ++ C8.unpack (trStdErr testResult)
+
+-- | Returns the command that was issued, the return code, and the output text
+run :: FilePath -> String -> [String] -> IO TestResult
+run cwd path args = do
+  -- path is relative to the current directory; canonicalizePath makes it
+  -- absolute, so that runProcess will find it even when changing directory.
+  path' <- canonicalizePath path
+
+  (pid, hReadStdOut, hReadStdErr) <- do
+    -- Create pipes for StdOut and StdErr
+    (hReadStdOut, hWriteStdOut) <- createPipe
+    (hReadStdErr, hWriteStdErr) <- createPipe
+    -- Run the process
+    pid <- runProcess path' args (Just cwd) Nothing Nothing (Just hWriteStdOut) (Just hWriteStdErr)
+    -- Return the pid and read ends of the pipes
+    return (pid, hReadStdOut, hReadStdErr)
+  -- Read subprocess output using asynchronous threads; we need to
+  -- do this aynchronously to avoid deadlocks due to buffers filling
+  -- up.
+  withAsync (B.hGetContents hReadStdOut) $ \stdOutAsync -> do
+    withAsync (B.hGetContents hReadStdErr) $ \stdErrAsync -> do
+      -- Wait for the subprocess to terminate
+      exitcode <- waitForProcess pid
+      -- We can now be sure that no further output is going to arrive,
+      -- so we wait for the results of the asynchronous reads.
+      stdOut <- wait stdOutAsync
+      stdErr <- wait stdErrAsync
+      -- Done
+      return $ TestResult exitcode stdOut stdErr cwd
+
+-- | Get a list of all names in a directory, excluding all hidden or
+-- system files/directories such as '.', '..'  or any files/directories
+-- starting with a '.'.
+listDirectory :: FilePath -> IO [String]
+listDirectory directory = do
+  fmap (filter notHidden) $ getDirectoryContents directory
+  where
+    notHidden = not . isHidden
+    isHidden name = "." `isPrefixOf` name
+
+-- | List a directory as per 'listDirectory', but return an empty list
+-- in case the directory does not exist.
+listDirectoryLax :: FilePath -> IO [String]
+listDirectoryLax directory = do
+  d <- doesDirectoryExist directory
+  if d then
+    listDirectory directory
+  else
+    return [ ]
+
+pathIfExists :: FilePath -> IO (Maybe FilePath)
+pathIfExists p = do
+  e <- doesFileExist p
+  if e then
+    return $ Just p
+    else
+      return Nothing
+
+fileMatchesString :: FilePath -> ByteString -> IO Bool
+fileMatchesString p s = do
+  withBinaryFile p ReadMode $ \h -> do
+    s' <- B.hGetContents h -- Strict
+    return $ normalizeLinebreaks s' == normalizeLinebreaks s
+  where
+    -- This is a bit of a hack, but since we're comparing
+    -- *text* output, we should be OK.
+    normalizeLinebreaks = B.filter (not . ((==) 13))
+
+mustMatch :: TestResult -> String -> ByteString -> Maybe FilePath -> Assertion
+mustMatch _          _          _ Nothing  =  return ()
+mustMatch testResult handleName s (Just p) = do
+  m <- fileMatchesString p s
+  if not m then
+      assertFailure $ "<" ++ handleName ++ "> did not match file '" ++ p ++ "'.\n" ++ testResultToString testResult
+    else
+      return ()
+
+discoverTestCategories :: FilePath -> IO [String]
+discoverTestCategories directory = do
+  names <- listDirectory directory
+  fmap sort $ filterM (\name -> doesDirectoryExist $ directory </> name) names
+
+discoverTestCases :: FilePath -> String -> String -> IO [TestCase]
+discoverTestCases baseDirectory category shouldX = do
+  -- Find the names of the shell scripts
+  names <- fmap (filter isTestCase) $ listDirectoryLax directory
+  -- Fill in TestCase for each script
+  forM (sort names) $ \name -> do
+    stdOutPath <- pathIfExists $ directory </> name `replaceExtension` ".out"
+    stdErrPath <- pathIfExists $ directory </> name `replaceExtension` ".err"
+    return $ TestCase { tcName = name
+                      , tcBaseDirectory = baseDirectory
+                      , tcCategory = category
+                      , tcShouldX = shouldX
+                      , tcStdOutPath = stdOutPath
+                      , tcStdErrPath = stdErrPath
+                      }
+  where
+    directory = baseDirectory </> category </> shouldX
+    isTestCase name = ".sh" `isSuffixOf` name
+
+createTestCases :: [TestCase] -> (TestCase -> Assertion) -> IO [TestTree]
+createTestCases testCases mk =
+  return $ (flip map) testCases $ \tc -> testCase (tcName tc ++ suffix tc) $ mk tc
+  where
+    suffix tc = case (tcStdOutPath tc, tcStdErrPath tc) of
+      (Nothing, Nothing) -> " (ignoring stdout+stderr)"
+      (Just _ , Nothing) -> " (ignoring stderr)"
+      (Nothing, Just _ ) -> " (ignoring stdout)"
+      (Just _ , Just _ ) -> ""
+
+runTestCase :: (TestResult -> Assertion) -> TestCase -> IO ()
+runTestCase assertResult tc = do
+  doRemove <- newIORef False
+  bracket createWorkDirectory (removeWorkDirectory doRemove) $ \workDirectory -> do
+    -- Run
+    let scriptDirectory = workDirectory </> tcShouldX tc
+    testResult <- run scriptDirectory "/bin/sh" [ "-e", tcName tc]
+    -- Assert that we got what we expected
+    assertResult testResult
+    mustMatch testResult "stdout" (trStdOut testResult) (tcStdOutPath tc)
+    mustMatch testResult "stderr" (trStdErr testResult) (tcStdErrPath tc)
+    -- Only remove working directory if test succeeded
+    writeIORef doRemove True
+  where
+    createWorkDirectory = do
+      -- Create the temporary directory
+      tempDirectory <- getTemporaryDirectory
+      workDirectory <- createTempDirectory tempDirectory "cabal-install-test"
+      -- Copy all the files from the category into the working directory.
+      copyDirectoryRecursive normal
+        (tcBaseDirectory tc </> tcCategory tc)
+        workDirectory
+      -- Done
+      return workDirectory
+    removeWorkDirectory doRemove workDirectory = do
+        remove <- readIORef doRemove
+        when remove $ removeDirectoryRecursive workDirectory
+
+makeShouldXTests :: FilePath -> String -> String -> (TestResult -> Assertion) -> IO [TestTree]
+makeShouldXTests baseDirectory category shouldX assertResult = do
+  testCases <- discoverTestCases baseDirectory category shouldX
+  createTestCases testCases $ \tc ->
+      runTestCase assertResult tc
+
+makeShouldRunTests :: FilePath -> String -> IO [TestTree]
+makeShouldRunTests baseDirectory category = do
+  makeShouldXTests baseDirectory category "should_run" $ \testResult -> do
+    case trExitCode testResult of
+      ExitSuccess ->
+        return () -- We're good
+      ExitFailure _ ->
+        assertFailure $ "Unexpected exit status.\n\n" ++ testResultToString testResult
+
+makeShouldFailTests :: FilePath -> String -> IO [TestTree]
+makeShouldFailTests baseDirectory category = do
+  makeShouldXTests baseDirectory category "should_fail" $ \testResult -> do
+    case trExitCode testResult of
+      ExitSuccess ->
+        assertFailure $ "Unexpected exit status.\n\n" ++ testResultToString testResult
+      ExitFailure _ ->
+        return () -- We're good
+
+discoverCategoryTests :: FilePath -> String -> IO [TestTree]
+discoverCategoryTests baseDirectory category = do
+  srTests <- makeShouldRunTests baseDirectory category
+  sfTests <- makeShouldFailTests baseDirectory category
+  return [ testGroup "should_run" srTests
+         , testGroup "should_fail" sfTests
+         ]
+
+main :: IO ()
+main = do
+  -- Find executables and build directories, etc.
+  distPref <- findDistPrefOrDefault NoFlag
+  buildDir <- canonicalizePath (distPref </> "build/cabal")
+  let programSearchPath = ProgramSearchPathDir buildDir : defaultProgramSearchPath
+  (cabal, _) <- requireProgram normal cabalProgram (setProgramSearchPath programSearchPath defaultProgramDb)
+  (ghcPkg, _) <- requireProgram normal ghcPkgProgram defaultProgramDb
+  baseDirectory <- canonicalizePath $ "tests" </> "IntegrationTests"
+  -- Set up environment variables for test scripts
+  setEnv "GHC_PKG" $ programPath ghcPkg
+  setEnv "CABAL" $ programPath cabal
+  setEnv "CABAL_ARGS" $ "--config-file=config-file"
+  -- Discover all the test caregories
+  categories <- discoverTestCategories baseDirectory
+  -- Discover tests in each category
+  tests <- forM categories $ \category -> do
+    categoryTests <- discoverCategoryTests baseDirectory category
+    return (category, categoryTests)
+  -- Map into a test tree
+  let testTree = map (\(category, categoryTests) -> testGroup category categoryTests) tests
+  -- Run the tests
+  defaultMain $ testGroup "Integration Tests" $ testTree
diff --git a/cabal-install/tests/IntegrationTests/exec/common.sh b/cabal-install/tests/IntegrationTests/exec/common.sh
new file mode 100644
index 0000000000000000000000000000000000000000..7e4d714e1565d56ea2353d2efa33e127d8f0263f
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/exec/common.sh
@@ -0,0 +1,9 @@
+# Helper to run Cabal
+cabal() {
+    $CABAL $CABAL_ARGS "$@"
+}
+
+die() {
+    echo "die: $@"
+    exit 1
+}
diff --git a/cabal-install/tests/PackageTests/Exec/Foo.hs b/cabal-install/tests/IntegrationTests/exec/should_run/Foo.hs
similarity index 100%
rename from cabal-install/tests/PackageTests/Exec/Foo.hs
rename to cabal-install/tests/IntegrationTests/exec/should_run/Foo.hs
diff --git a/cabal-install/tests/PackageTests/Exec/My.hs b/cabal-install/tests/IntegrationTests/exec/should_run/My.hs
similarity index 100%
rename from cabal-install/tests/PackageTests/Exec/My.hs
rename to cabal-install/tests/IntegrationTests/exec/should_run/My.hs
diff --git a/cabal-install/tests/IntegrationTests/exec/should_run/adds_sandbox_bin_directory_to_path.out b/cabal-install/tests/IntegrationTests/exec/should_run/adds_sandbox_bin_directory_to_path.out
new file mode 100644
index 0000000000000000000000000000000000000000..27df3614e9486111c642c052faafcc31f215439b
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/exec/should_run/adds_sandbox_bin_directory_to_path.out
@@ -0,0 +1 @@
+This is my-executable
diff --git a/cabal-install/tests/IntegrationTests/exec/should_run/adds_sandbox_bin_directory_to_path.sh b/cabal-install/tests/IntegrationTests/exec/should_run/adds_sandbox_bin_directory_to_path.sh
new file mode 100644
index 0000000000000000000000000000000000000000..e4c00ab22e656ecc93b795529c22a4a692460788
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/exec/should_run/adds_sandbox_bin_directory_to_path.sh
@@ -0,0 +1,10 @@
+. ../common.sh
+
+cabal sandbox delete > /dev/null
+cabal exec my-executable && die "Unexpectedly found executable"
+
+cabal sandbox init > /dev/null
+cabal install > /dev/null
+
+# Execute indirectly via bash to ensure that we go through $PATH
+cabal exec sh -- -c my-executable || die "Did not find executable"
diff --git a/cabal-install/tests/IntegrationTests/exec/should_run/auto_configures_on_exec.out b/cabal-install/tests/IntegrationTests/exec/should_run/auto_configures_on_exec.out
new file mode 100644
index 0000000000000000000000000000000000000000..b28a60dc6a3fdcb8c236619e1c549eece469133d
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/exec/should_run/auto_configures_on_exec.out
@@ -0,0 +1,4 @@
+Config file path source is commandline option.
+Config file config-file not found.
+Writing default configuration to config-file
+find_me_in_output
diff --git a/cabal-install/tests/IntegrationTests/exec/should_run/auto_configures_on_exec.sh b/cabal-install/tests/IntegrationTests/exec/should_run/auto_configures_on_exec.sh
new file mode 100644
index 0000000000000000000000000000000000000000..e55a88f18e7954093dee34af132942f7da818bf8
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/exec/should_run/auto_configures_on_exec.sh
@@ -0,0 +1,2 @@
+. ../common.sh
+cabal exec echo find_me_in_output
diff --git a/cabal-install/tests/IntegrationTests/exec/should_run/can_run_executables_installed_in_sandbox.out b/cabal-install/tests/IntegrationTests/exec/should_run/can_run_executables_installed_in_sandbox.out
new file mode 100644
index 0000000000000000000000000000000000000000..27df3614e9486111c642c052faafcc31f215439b
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/exec/should_run/can_run_executables_installed_in_sandbox.out
@@ -0,0 +1 @@
+This is my-executable
diff --git a/cabal-install/tests/IntegrationTests/exec/should_run/can_run_executables_installed_in_sandbox.sh b/cabal-install/tests/IntegrationTests/exec/should_run/can_run_executables_installed_in_sandbox.sh
new file mode 100644
index 0000000000000000000000000000000000000000..b5a35f2ad9309f41d9e4253437de60a17b7e0ce6
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/exec/should_run/can_run_executables_installed_in_sandbox.sh
@@ -0,0 +1,9 @@
+. ../common.sh
+
+cabal sandbox delete > /dev/null
+cabal exec my-executable && die "Unexpectedly found executable"
+
+cabal sandbox init > /dev/null
+cabal install > /dev/null
+
+cabal exec my-executable || die "Did not find executable"
diff --git a/cabal-install/tests/IntegrationTests/exec/should_run/configures_cabal_to_use_sandbox.sh b/cabal-install/tests/IntegrationTests/exec/should_run/configures_cabal_to_use_sandbox.sh
new file mode 100644
index 0000000000000000000000000000000000000000..a8e5925abe754c444ee7856e6fc45b123961effc
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/exec/should_run/configures_cabal_to_use_sandbox.sh
@@ -0,0 +1,14 @@
+. ../common.sh
+
+cabal sandbox delete > /dev/null
+cabal exec my-executable && die "Unexpectedly found executable"
+
+cabal sandbox init > /dev/null
+cabal install > /dev/null
+
+# The library should not be available outside the sandbox
+$GHC_PKG list | grep -v "my-0.1"
+
+# When run inside 'cabal-exec' the 'sandbox hc-pkg list' sub-command
+# should find the library.
+cabal exec sh -- -c "cd subdir && $CABAL sandbox hc-pkg list" | grep "my-0.1"
diff --git a/cabal-install/tests/IntegrationTests/exec/should_run/configures_ghc_to_use_sandbox.sh b/cabal-install/tests/IntegrationTests/exec/should_run/configures_ghc_to_use_sandbox.sh
new file mode 100644
index 0000000000000000000000000000000000000000..a5ed2958263057e06560b2004025d23e4a52282d
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/exec/should_run/configures_ghc_to_use_sandbox.sh
@@ -0,0 +1,13 @@
+. ../common.sh
+
+cabal sandbox delete > /dev/null
+cabal exec my-executable && die "Unexpectedly found executable"
+
+cabal sandbox init > /dev/null
+cabal install > /dev/null
+
+# The library should not be available outside the sandbox
+$GHC_PKG list | grep -v "my-0.1"
+
+# Execute ghc-pkg inside the sandbox; it should find my-0.1
+cabal exec ghc-pkg list | grep "my-0.1"
diff --git a/cabal-install/tests/IntegrationTests/exec/should_run/exit_with_failure_without_args.sh b/cabal-install/tests/IntegrationTests/exec/should_run/exit_with_failure_without_args.sh
new file mode 100644
index 0000000000000000000000000000000000000000..fa8c1ff50f110f614fb87cc759d103da3a68896e
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/exec/should_run/exit_with_failure_without_args.sh
@@ -0,0 +1,6 @@
+. ../common.sh
+
+# We should probably be using a .err file and should_fail,
+# but this fails on windows due to the ".exe" on the cabal
+# executable in the output.
+cabal exec 2>&1 > /dev/null | grep "Please specify an executable to run"
diff --git a/cabal-install/tests/PackageTests/Exec/my.cabal b/cabal-install/tests/IntegrationTests/exec/should_run/my.cabal
similarity index 100%
rename from cabal-install/tests/PackageTests/Exec/my.cabal
rename to cabal-install/tests/IntegrationTests/exec/should_run/my.cabal
diff --git a/cabal-install/tests/IntegrationTests/exec/should_run/runs_given_command.out b/cabal-install/tests/IntegrationTests/exec/should_run/runs_given_command.out
new file mode 100644
index 0000000000000000000000000000000000000000..95908116346b6cc01c3ec3ffd31bf1a58b77da7c
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/exec/should_run/runs_given_command.out
@@ -0,0 +1 @@
+this string
diff --git a/cabal-install/tests/IntegrationTests/exec/should_run/runs_given_command.sh b/cabal-install/tests/IntegrationTests/exec/should_run/runs_given_command.sh
new file mode 100644
index 0000000000000000000000000000000000000000..30e73e256786abfd00b1b62fb786449d6edde491
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/exec/should_run/runs_given_command.sh
@@ -0,0 +1,3 @@
+. ../common.sh
+cabal configure > /dev/null
+cabal exec echo this string
diff --git a/cabal-install/tests/PackageTests/Exec/subdir/.gitkeep b/cabal-install/tests/IntegrationTests/exec/should_run/subdir/.gitkeep
similarity index 100%
rename from cabal-install/tests/PackageTests/Exec/subdir/.gitkeep
rename to cabal-install/tests/IntegrationTests/exec/should_run/subdir/.gitkeep
diff --git a/cabal-install/tests/IntegrationTests/freeze/common.sh b/cabal-install/tests/IntegrationTests/freeze/common.sh
new file mode 100644
index 0000000000000000000000000000000000000000..7e4d714e1565d56ea2353d2efa33e127d8f0263f
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/freeze/common.sh
@@ -0,0 +1,9 @@
+# Helper to run Cabal
+cabal() {
+    $CABAL $CABAL_ARGS "$@"
+}
+
+die() {
+    echo "die: $@"
+    exit 1
+}
diff --git a/cabal-install/tests/IntegrationTests/freeze/should_run/disable_benchmarks_freezes_bench_deps.sh b/cabal-install/tests/IntegrationTests/freeze/should_run/disable_benchmarks_freezes_bench_deps.sh
new file mode 100644
index 0000000000000000000000000000000000000000..a151aed1714245eedd1ef4c72c466a9e044e56ce
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/freeze/should_run/disable_benchmarks_freezes_bench_deps.sh
@@ -0,0 +1,3 @@
+. ../common.sh
+cabal freeze --disable-benchmarks
+grep -v " criterion ==" cabal.config || die "should NOT have frozen criterion"
diff --git a/cabal-install/tests/IntegrationTests/freeze/should_run/disable_tests_freezes_test_deps.sh b/cabal-install/tests/IntegrationTests/freeze/should_run/disable_tests_freezes_test_deps.sh
new file mode 100644
index 0000000000000000000000000000000000000000..8fd70d951f5b0794d394e779c336aacbe844294c
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/freeze/should_run/disable_tests_freezes_test_deps.sh
@@ -0,0 +1,3 @@
+. ../common.sh
+cabal freeze --disable-tests
+grep -v " test-framework ==" cabal.config || die "should NOT have frozen test-framework"
diff --git a/cabal-install/tests/IntegrationTests/freeze/should_run/does_not_freeze_nondeps.sh b/cabal-install/tests/IntegrationTests/freeze/should_run/does_not_freeze_nondeps.sh
new file mode 100644
index 0000000000000000000000000000000000000000..ea927e39cd8f7d390b2c8560926261710a071e76
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/freeze/should_run/does_not_freeze_nondeps.sh
@@ -0,0 +1,5 @@
+. ../common.sh
+# TODO: Test this against a package installed in the sandbox but not
+# depended upon.
+cabal freeze
+grep -v "exceptions ==" cabal.config || die "should not have frozen exceptions"
diff --git a/cabal-install/tests/IntegrationTests/freeze/should_run/does_not_freeze_self.sh b/cabal-install/tests/IntegrationTests/freeze/should_run/does_not_freeze_self.sh
new file mode 100644
index 0000000000000000000000000000000000000000..eac17b254068f19309bcdca412d43db3b8edad11
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/freeze/should_run/does_not_freeze_self.sh
@@ -0,0 +1,3 @@
+. ../common.sh
+cabal freeze
+grep -v " my ==" cabal.config || die "should not have frozen self"
diff --git a/cabal-install/tests/IntegrationTests/freeze/should_run/dry_run_does_not_create_config.sh b/cabal-install/tests/IntegrationTests/freeze/should_run/dry_run_does_not_create_config.sh
new file mode 100644
index 0000000000000000000000000000000000000000..08841fef7d8aea122f54bbb411ee1cafa2fa3090
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/freeze/should_run/dry_run_does_not_create_config.sh
@@ -0,0 +1,3 @@
+. ../common.sh
+cabal freeze --dry-run
+[ ! -e cabal.config ] || die "cabal.config file should not have been created"
diff --git a/cabal-install/tests/IntegrationTests/freeze/should_run/enable_benchmarks_freezes_bench_deps.sh b/cabal-install/tests/IntegrationTests/freeze/should_run/enable_benchmarks_freezes_bench_deps.sh
new file mode 100644
index 0000000000000000000000000000000000000000..dba68bd245408ee1ff5556e1ce9d2f2f2181a6c5
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/freeze/should_run/enable_benchmarks_freezes_bench_deps.sh
@@ -0,0 +1,3 @@
+. ../common.sh
+cabal freeze --enable-benchmarks
+grep " criterion ==" cabal.config || die "should have frozen criterion"
diff --git a/cabal-install/tests/IntegrationTests/freeze/should_run/enable_tests_freezes_test_deps.sh b/cabal-install/tests/IntegrationTests/freeze/should_run/enable_tests_freezes_test_deps.sh
new file mode 100644
index 0000000000000000000000000000000000000000..cc91f636f7961d5625b609ca861778164a65d586
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/freeze/should_run/enable_tests_freezes_test_deps.sh
@@ -0,0 +1,3 @@
+. ../common.sh
+cabal freeze --enable-tests
+grep " test-framework ==" cabal.config || die "should have frozen test-framework"
diff --git a/cabal-install/tests/IntegrationTests/freeze/should_run/freezes_direct_dependencies.sh b/cabal-install/tests/IntegrationTests/freeze/should_run/freezes_direct_dependencies.sh
new file mode 100644
index 0000000000000000000000000000000000000000..c5ced2a4f4ea109c4bb95f3d3c1273901c75bc88
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/freeze/should_run/freezes_direct_dependencies.sh
@@ -0,0 +1,3 @@
+. ../common.sh
+cabal freeze
+grep " base ==" cabal.config || die "'base' should have been frozen"
diff --git a/cabal-install/tests/IntegrationTests/freeze/should_run/freezes_transitive_dependencies.sh b/cabal-install/tests/IntegrationTests/freeze/should_run/freezes_transitive_dependencies.sh
new file mode 100644
index 0000000000000000000000000000000000000000..895d8272a75be0aadfba3d2444421446010680dd
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/freeze/should_run/freezes_transitive_dependencies.sh
@@ -0,0 +1,3 @@
+. ../common.sh
+cabal freeze
+grep " ghc-prim ==" cabal.config || die "'ghc-prim' should have been frozen"
diff --git a/cabal-install/tests/PackageTests/Freeze/my.cabal b/cabal-install/tests/IntegrationTests/freeze/should_run/my.cabal
similarity index 100%
rename from cabal-install/tests/PackageTests/Freeze/my.cabal
rename to cabal-install/tests/IntegrationTests/freeze/should_run/my.cabal
diff --git a/cabal-install/tests/IntegrationTests/freeze/should_run/runs_without_error.sh b/cabal-install/tests/IntegrationTests/freeze/should_run/runs_without_error.sh
new file mode 100644
index 0000000000000000000000000000000000000000..4c88eca9b09302ac1f534554f7d230b05ad8eefd
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/freeze/should_run/runs_without_error.sh
@@ -0,0 +1,2 @@
+. ../common.sh
+cabal freeze
diff --git a/cabal-install/tests/IntegrationTests/multiple-source/common.sh b/cabal-install/tests/IntegrationTests/multiple-source/common.sh
new file mode 100644
index 0000000000000000000000000000000000000000..db09249a166c2cfdd7f4808d2b4208098074b5c2
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/multiple-source/common.sh
@@ -0,0 +1,8 @@
+cabal() {
+    $CABAL $CABAL_ARGS "$@"
+}
+
+die() {
+    echo "die: $@"
+    exit 1
+}
diff --git a/cabal-install/tests/IntegrationTests/multiple-source/should_run/finds_second_source_of_multiple_source.sh b/cabal-install/tests/IntegrationTests/multiple-source/should_run/finds_second_source_of_multiple_source.sh
new file mode 100644
index 0000000000000000000000000000000000000000..340689ec0e7978227038a0fbfc53677dea342af5
--- /dev/null
+++ b/cabal-install/tests/IntegrationTests/multiple-source/should_run/finds_second_source_of_multiple_source.sh
@@ -0,0 +1,11 @@
+. ../common.sh
+
+# Create the sandbox
+cabal sandbox init
+
+# Add the sources
+cabal sandbox add-source p
+cabal sandbox add-source q
+
+# Install the second package
+cabal install q
diff --git a/cabal-install/tests/PackageTests/MultipleSource/p/LICENSE b/cabal-install/tests/IntegrationTests/multiple-source/should_run/p/LICENSE
similarity index 100%
rename from cabal-install/tests/PackageTests/MultipleSource/p/LICENSE
rename to cabal-install/tests/IntegrationTests/multiple-source/should_run/p/LICENSE
diff --git a/cabal-install/tests/PackageTests/MultipleSource/p/Setup.hs b/cabal-install/tests/IntegrationTests/multiple-source/should_run/p/Setup.hs
similarity index 100%
rename from cabal-install/tests/PackageTests/MultipleSource/p/Setup.hs
rename to cabal-install/tests/IntegrationTests/multiple-source/should_run/p/Setup.hs
diff --git a/cabal-install/tests/PackageTests/MultipleSource/p/p.cabal b/cabal-install/tests/IntegrationTests/multiple-source/should_run/p/p.cabal
similarity index 100%
rename from cabal-install/tests/PackageTests/MultipleSource/p/p.cabal
rename to cabal-install/tests/IntegrationTests/multiple-source/should_run/p/p.cabal
diff --git a/cabal-install/tests/PackageTests/MultipleSource/q/LICENSE b/cabal-install/tests/IntegrationTests/multiple-source/should_run/q/LICENSE
similarity index 100%
rename from cabal-install/tests/PackageTests/MultipleSource/q/LICENSE
rename to cabal-install/tests/IntegrationTests/multiple-source/should_run/q/LICENSE
diff --git a/cabal-install/tests/PackageTests/MultipleSource/q/Setup.hs b/cabal-install/tests/IntegrationTests/multiple-source/should_run/q/Setup.hs
similarity index 100%
rename from cabal-install/tests/PackageTests/MultipleSource/q/Setup.hs
rename to cabal-install/tests/IntegrationTests/multiple-source/should_run/q/Setup.hs
diff --git a/cabal-install/tests/PackageTests/MultipleSource/q/q.cabal b/cabal-install/tests/IntegrationTests/multiple-source/should_run/q/q.cabal
similarity index 100%
rename from cabal-install/tests/PackageTests/MultipleSource/q/q.cabal
rename to cabal-install/tests/IntegrationTests/multiple-source/should_run/q/q.cabal
diff --git a/cabal-install/tests/PackageTests.hs b/cabal-install/tests/PackageTests.hs
deleted file mode 100644
index 481a2a7eee16c1ecc71d3b82b3164ffeee189922..0000000000000000000000000000000000000000
--- a/cabal-install/tests/PackageTests.hs
+++ /dev/null
@@ -1,95 +0,0 @@
--- | Groups black-box tests of cabal-install and configures them to test
--- the correct binary.
---
--- This file should do nothing but import tests from other modules and run
--- them with the path to the correct cabal-install binary.
-module Main
-       where
-
--- Modules from Cabal.
-import Distribution.Simple.Configure (findDistPrefOrDefault)
-import Distribution.Simple.Program.Builtin (ghcPkgProgram)
-import Distribution.Simple.Program.Db
-        (defaultProgramDb, requireProgram, setProgramSearchPath)
-import Distribution.Simple.Program.Find
-        (ProgramSearchPathEntry(ProgramSearchPathDir), defaultProgramSearchPath)
-import Distribution.Simple.Program.Types
-        ( Program(..), simpleProgram, programPath)
-import Distribution.Simple.Setup ( Flag(..) )
-import Distribution.Simple.Utils ( findProgramVersion )
-import Distribution.Verbosity (normal)
-
--- Third party modules.
-import qualified Control.Exception.Extensible as E
-import Distribution.Compat.Environment ( setEnv )
-import System.Directory
-        ( canonicalizePath, getCurrentDirectory, setCurrentDirectory
-        , removeFile, doesFileExist )
-import System.FilePath ((</>))
-import Test.Tasty (TestTree, defaultMain, testGroup)
-import Control.Monad ( when )
-
--- Module containing common test code.
-
-import PackageTests.PackageTester ( TestsPaths(..)
-                                  , packageTestsDirectory
-                                  , packageTestsConfigFile )
-
--- Modules containing the tests.
-import qualified PackageTests.Exec.Check
-import qualified PackageTests.Freeze.Check
-import qualified PackageTests.MultipleSource.Check
-
--- List of tests to run. Each test will be called with the path to the
--- cabal binary to use.
-tests :: PackageTests.PackageTester.TestsPaths -> TestTree
-tests paths = testGroup "Package Tests" $
-    [ testGroup "Freeze"         $ PackageTests.Freeze.Check.tests         paths
-    , testGroup "Exec"           $ PackageTests.Exec.Check.tests           paths
-    , testGroup "MultipleSource" $ PackageTests.MultipleSource.Check.tests paths
-    ]
-
-cabalProgram :: Program
-cabalProgram = (simpleProgram "cabal") {
-    programFindVersion = findProgramVersion "--numeric-version" id
-  }
-
-main :: IO ()
-main = do
-    -- Find the builddir used to build Cabal
-    distPref <- findDistPrefOrDefault NoFlag
-    -- Use the default builddir for all of the subsequent package tests
-    setEnv "CABAL_BUILDDIR" "dist"
-    buildDir <- canonicalizePath (distPref </> "build/cabal")
-    let programSearchPath = ProgramSearchPathDir buildDir : defaultProgramSearchPath
-    (cabal, _) <- requireProgram normal cabalProgram
-                      (setProgramSearchPath programSearchPath defaultProgramDb)
-    (ghcPkg, _) <- requireProgram normal ghcPkgProgram defaultProgramDb
-    canonicalConfigPath <- canonicalizePath $ "tests" </> packageTestsDirectory
-
-    let testsPaths = TestsPaths {
-          cabalPath = programPath cabal,
-          ghcPkgPath = programPath ghcPkg,
-          configPath = canonicalConfigPath </> packageTestsConfigFile
-        }
-
-    putStrLn $ "Using cabal: "   ++ cabalPath  testsPaths
-    putStrLn $ "Using ghc-pkg: " ++ ghcPkgPath testsPaths
-
-    cwd <- getCurrentDirectory
-    let confFile = packageTestsDirectory </> "cabal-config"
-        removeConf = do
-          b <- doesFileExist confFile
-          when b $ removeFile confFile
-    let runTests = do
-          setCurrentDirectory "tests"
-          removeConf -- assert that there is no existing config file
-                     -- (we want deterministic testing with the default
-                     --  config values)
-          defaultMain $ tests testsPaths
-    runTests `E.finally` do
-        -- remove the default config file that got created by the tests
-        removeConf
-        -- Change back to the old working directory so that the tests can be
-        -- repeatedly run in `cabal repl` via `:main`.
-        setCurrentDirectory cwd
diff --git a/cabal-install/tests/PackageTests/Exec/Check.hs b/cabal-install/tests/PackageTests/Exec/Check.hs
deleted file mode 100644
index c6b5cd848af624f2debe43b33d68d317e7b2d6e5..0000000000000000000000000000000000000000
--- a/cabal-install/tests/PackageTests/Exec/Check.hs
+++ /dev/null
@@ -1,145 +0,0 @@
-{-# LANGUAGE CPP #-}
-module PackageTests.Exec.Check
-       ( tests
-       ) where
-
-
-import PackageTests.PackageTester
-
-import Test.Tasty
-import Test.Tasty.HUnit
-
-#if !MIN_VERSION_base(4,8,0)
-import Control.Applicative ((<$>))
-#endif
-import Control.Monad (when)
-import Data.List (intercalate, isInfixOf)
-import System.FilePath ((</>))
-import System.Directory (getDirectoryContents)
-
-dir :: FilePath
-dir = packageTestsDirectory </> "Exec"
-
-tests :: TestsPaths -> [TestTree]
-tests paths =
-    [ testCase "exits with failure if given no argument" $ do
-          result <- cabal_exec paths dir []
-          assertExecFailed result
-
-    , testCase "prints error message if given no argument" $ do
-          result <- cabal_exec paths dir []
-          assertExecFailed result
-          let output = outputText result
-              expected = "specify an executable to run"
-              errMsg = "should have requested an executable be specified\n" ++
-                       output
-          assertBool errMsg $
-              expected `isInfixOf` (intercalate " " . lines $ output)
-
-    , testCase "runs the given command" $ do
-          result <- cabal_exec paths dir ["echo", "this", "string"]
-          assertExecSucceeded result
-          let output = outputText result
-              expected = "this string"
-              errMsg = "should have ran the given command\n" ++ output
-          assertBool errMsg $
-              expected `isInfixOf` (intercalate " " . lines $ output)
-
-    , testCase "can run executables installed in the sandbox" $ do
-          -- Test that an executable installed into the sandbox can be found.
-          -- We do this by removing any existing sandbox. Checking that the
-          -- executable cannot be found. Creating a new sandbox. Installing
-          -- the executable and checking it can be run.
-
-          cleanPreviousBuilds paths
-          assertMyExecutableNotFound paths
-          assertPackageInstall paths
-
-          result <- cabal_exec paths dir ["my-executable"]
-          assertExecSucceeded result
-          let output = outputText result
-              expected = "This is my-executable"
-              errMsg = "should have found a my-executable\n" ++ output
-          assertBool errMsg $
-              expected `isInfixOf` (intercalate " " . lines $ output)
-
-    , testCase "adds the sandbox bin directory to the PATH" $ do
-          cleanPreviousBuilds paths
-          assertMyExecutableNotFound paths
-          assertPackageInstall paths
-
-          result <- cabal_exec paths dir ["bash", "--", "-c", "my-executable"]
-          assertExecSucceeded result
-          let output = outputText result
-              expected = "This is my-executable"
-              errMsg = "should have found a my-executable\n" ++ output
-          assertBool errMsg $
-              expected `isInfixOf` (intercalate " " . lines $ output)
-
-    , testCase "configures GHC to use the sandbox" $ do
-          let libNameAndVersion = "my-0.1"
-
-          cleanPreviousBuilds paths
-          assertPackageInstall paths
-
-          assertMyLibIsNotAvailableOutsideofSandbox paths libNameAndVersion
-
-          result <- cabal_exec paths dir ["ghc-pkg", "list"]
-          assertExecSucceeded result
-          let output = outputText result
-              errMsg = "my library should have been found"
-          assertBool errMsg $
-              libNameAndVersion `isInfixOf` (intercalate " " . lines $ output)
-          
-
-    -- , testCase "can find executables built from the package" $ do
-
-    , testCase "configures cabal to use the sandbox" $ do
-          let libNameAndVersion = "my-0.1"
-
-          cleanPreviousBuilds paths
-          assertPackageInstall paths
-
-          assertMyLibIsNotAvailableOutsideofSandbox paths libNameAndVersion
-
-          result <- cabal_exec paths dir ["bash", "--", "-c", "cd subdir ; cabal sandbox hc-pkg list"]
-          assertExecSucceeded result
-          let output = outputText result
-              errMsg = "my library should have been found"
-          assertBool errMsg $
-              libNameAndVersion `isInfixOf` (intercalate " " . lines $ output)
-    ]
-
-cleanPreviousBuilds :: TestsPaths -> IO ()
-cleanPreviousBuilds paths = do
-    sandboxExists <- not . null . filter (== "cabal.sandbox.config") <$>
-                         getDirectoryContents dir
-    assertCleanSucceeded   =<< cabal_clean paths dir []
-    when sandboxExists $ do
-        assertSandboxSucceeded =<< cabal_sandbox paths dir ["delete"]
-
-
-assertPackageInstall :: TestsPaths -> IO ()
-assertPackageInstall paths = do
-    assertSandboxSucceeded =<< cabal_sandbox paths dir ["init"]
-    assertInstallSucceeded =<< cabal_install paths dir []
-
-
-assertMyExecutableNotFound :: TestsPaths -> IO ()
-assertMyExecutableNotFound paths = do
-    result <- cabal_exec paths dir ["my-executable"]
-    assertExecFailed result
-    let output = outputText result
-        expected = "The program 'my-executable' is required but it " ++
-                   "could not be found"
-        errMsg = "should not have found a my-executable\n" ++ output
-    assertBool errMsg $
-        expected `isInfixOf` (intercalate " " . lines $ output)
-
-
-
-assertMyLibIsNotAvailableOutsideofSandbox :: TestsPaths -> String -> IO ()
-assertMyLibIsNotAvailableOutsideofSandbox paths libNameAndVersion = do
-    (_, _, output) <- run (Just $ dir) (ghcPkgPath paths) ["list"]
-    assertBool "my library should not have been found" $ not $
-        libNameAndVersion `isInfixOf` (intercalate " " . lines $ output)
diff --git a/cabal-install/tests/PackageTests/Freeze/Check.hs b/cabal-install/tests/PackageTests/Freeze/Check.hs
deleted file mode 100644
index 8f2ca8c2df2b3b987366a8b304fbe59d99cc341d..0000000000000000000000000000000000000000
--- a/cabal-install/tests/PackageTests/Freeze/Check.hs
+++ /dev/null
@@ -1,116 +0,0 @@
-{-# LANGUAGE ScopedTypeVariables #-}
-
-module PackageTests.Freeze.Check
-       ( tests
-       ) where
-
-import PackageTests.PackageTester
-
-import Test.Tasty
-import Test.Tasty.HUnit
-
-import qualified Control.Exception.Extensible as E
-import Data.List (intercalate, isInfixOf)
-import System.Directory (doesFileExist, removeFile)
-import System.FilePath ((</>))
-import System.IO.Error (isDoesNotExistError)
-
-dir :: FilePath
-dir = packageTestsDirectory </> "Freeze"
-
-tests :: TestsPaths -> [TestTree]
-tests paths =
-    [ testCase "runs without error" $ do
-          removeCabalConfig
-          result <- cabal_freeze paths dir []
-          assertFreezeSucceeded result
-
-    , testCase "freezes direct dependencies" $ do
-          removeCabalConfig
-          result <- cabal_freeze paths dir []
-          assertFreezeSucceeded result
-          c <- readCabalConfig
-          assertBool ("should have frozen base\n" ++ c) $
-              " base ==" `isInfixOf` (intercalate " " $ lines $ c)
-
-    , testCase "freezes transitory dependencies" $ do
-          removeCabalConfig
-          result <- cabal_freeze paths dir []
-          assertFreezeSucceeded result
-          c <- readCabalConfig
-          assertBool ("should have frozen ghc-prim\n" ++ c) $
-              " ghc-prim ==" `isInfixOf` (intercalate " " $ lines $ c)
-
-    , testCase "does not freeze packages which are not dependend upon" $ do
-          -- TODO: Test this against a package installed in the sandbox but
-          -- not depended upon.
-          removeCabalConfig
-          result <- cabal_freeze paths dir []
-          assertFreezeSucceeded result
-          c <- readCabalConfig
-          assertBool ("should not have frozen exceptions\n" ++ c) $ not $
-              " exceptions ==" `isInfixOf` (intercalate " " $ lines $ c)
-
-    , testCase "does not include a constraint for the package being frozen" $ do
-          removeCabalConfig
-          result <- cabal_freeze paths dir []
-          assertFreezeSucceeded result
-          c <- readCabalConfig
-          assertBool ("should not have frozen self\n" ++ c) $ not $
-              " my ==" `isInfixOf` (intercalate " " $ lines $ c)
-
-    , testCase "--dry-run does not modify the cabal.config file" $ do
-          removeCabalConfig
-          result <- cabal_freeze paths dir ["--dry-run"]
-          assertFreezeSucceeded result
-          c <- doesFileExist $ dir </> "cabal.config"
-          assertBool "cabal.config file should not have been created" (not c)
-
-    , testCase "--enable-tests freezes test dependencies" $ do
-          removeCabalConfig
-          result <- cabal_freeze paths dir ["--enable-tests"]
-          assertFreezeSucceeded result
-          c <- readCabalConfig
-          assertBool ("should have frozen test-framework\n" ++ c) $
-              " test-framework ==" `isInfixOf` (intercalate " " $ lines $ c)
-
-    , testCase "--disable-tests does not freeze test dependencies" $ do
-          removeCabalConfig
-          result <- cabal_freeze paths dir ["--disable-tests"]
-          assertFreezeSucceeded result
-          c <- readCabalConfig
-          assertBool ("should not have frozen test-framework\n" ++ c) $ not $
-              " test-framework ==" `isInfixOf` (intercalate " " $ lines $ c)
-
-    , testCase "--enable-benchmarks freezes benchmark dependencies" $ do
-          removeCabalConfig
-          result <- cabal_freeze paths dir ["--disable-benchmarks"]
-          assertFreezeSucceeded result
-          c <- readCabalConfig
-          assertBool ("should not have frozen criterion\n" ++ c) $ not $
-              " criterion ==" `isInfixOf` (intercalate " " $ lines $ c)
-
-    , testCase "--disable-benchmarks does not freeze benchmark dependencies" $ do
-          removeCabalConfig
-          result <- cabal_freeze paths dir ["--disable-benchmarks"]
-          assertFreezeSucceeded result
-          c <- readCabalConfig
-          assertBool ("should not have frozen criterion\n" ++ c) $ not $
-              " criterion ==" `isInfixOf` (intercalate " " $ lines $ c)
-    ]
-
-removeCabalConfig :: IO ()
-removeCabalConfig = do
-    removeFile (dir </> "cabal.config")
-    `E.catch` \ (e :: IOError) ->
-        if isDoesNotExistError e
-        then return ()
-        else E.throw e
-
-
-readCabalConfig :: IO String
-readCabalConfig = do
-    config <- readFile $ dir </> "cabal.config"
-    -- Ensure that the file is closed so that it can be
-    -- deleted by the next test on Windows.
-    length config `seq` return config
diff --git a/cabal-install/tests/PackageTests/MultipleSource/Check.hs b/cabal-install/tests/PackageTests/MultipleSource/Check.hs
deleted file mode 100644
index 0fe6361299fb7780725b54b2aa2bc5082cca16d4..0000000000000000000000000000000000000000
--- a/cabal-install/tests/PackageTests/MultipleSource/Check.hs
+++ /dev/null
@@ -1,28 +0,0 @@
-module PackageTests.MultipleSource.Check
-       ( tests
-       ) where
-
-
-import PackageTests.PackageTester
-
-import Test.Tasty
-import Test.Tasty.HUnit
-
-import Control.Monad    (void, when)
-import System.Directory (doesDirectoryExist)
-import System.FilePath  ((</>))
-
-dir :: FilePath
-dir = packageTestsDirectory </> "MultipleSource"
-
-tests :: TestsPaths -> [TestTree]
-tests paths =
-    [ testCase "finds second source of multiple source" $ do
-          sandboxExists <- doesDirectoryExist $ dir </> ".cabal-sandbox"
-          when sandboxExists $
-            void $ cabal_sandbox paths dir ["delete"]
-          assertSandboxSucceeded =<< cabal_sandbox paths dir ["init"]
-          assertSandboxSucceeded =<< cabal_sandbox paths dir ["add-source", "p"]
-          assertSandboxSucceeded =<< cabal_sandbox paths dir ["add-source", "q"]
-          assertInstallSucceeded =<< cabal_install paths dir ["q"]
-    ]
diff --git a/cabal-install/tests/PackageTests/PackageTester.hs b/cabal-install/tests/PackageTests/PackageTester.hs
deleted file mode 100644
index 2068099b6d58c415dd0d76dedf572719008424aa..0000000000000000000000000000000000000000
--- a/cabal-install/tests/PackageTests/PackageTester.hs
+++ /dev/null
@@ -1,232 +0,0 @@
-{-# LANGUAGE ScopedTypeVariables #-}
-
--- TODO This module was originally based on the PackageTests.PackageTester
--- module in Cabal, however it has a few differences. I suspect that as
--- this module ages the two modules will diverge further. As such, I have
--- not attempted to merge them into a single module nor to extract a common
--- module from them.  Refactor this module and/or Cabal's
--- PackageTests.PackageTester to remove commonality.
---   2014-05-15 Ben Armston
-
--- | Routines for black-box testing cabal-install.
---
--- Instead of driving the tests by making library calls into
--- Distribution.Simple.* or Distribution.Client.* this module only every
--- executes the `cabal-install` binary.
---
--- You can set the following VERBOSE environment variable to control
--- the verbosity of the output generated by this module.
-module PackageTests.PackageTester
-    ( TestsPaths(..)
-    , Result(..)
-
-    , packageTestsDirectory
-    , packageTestsConfigFile
-
-    -- * Running cabal commands
-    , cabal_clean
-    , cabal_exec
-    , cabal_freeze
-    , cabal_install
-    , cabal_sandbox
-    , run
-
-    -- * Test helpers
-    , assertCleanSucceeded
-    , assertExecFailed
-    , assertExecSucceeded
-    , assertFreezeSucceeded
-    , assertInstallSucceeded
-    , assertSandboxSucceeded
-    ) where
-
-import qualified Control.Exception.Extensible as E
-import Control.Monad (when, unless)
-import Data.Maybe (fromMaybe)
-import System.Directory (canonicalizePath, doesFileExist)
-import System.Environment (getEnv)
-import System.Exit (ExitCode(ExitSuccess))
-import System.FilePath ( (<.>)  )
-import System.IO (hClose, hGetChar, hIsEOF)
-import System.IO.Error (isDoesNotExistError)
-import System.Process (runProcess, waitForProcess)
-import Test.Tasty.HUnit (Assertion, assertFailure)
-
-import Distribution.Simple.BuildPaths (exeExtension)
-import Distribution.Simple.Utils (printRawCommandAndArgs)
-import Distribution.Compat.CreatePipe (createPipe)
-import Distribution.ReadE (readEOrFail)
-import Distribution.Verbosity (Verbosity, flagToVerbosity, normal)
-
-data Success = Failure
-             -- | ConfigureSuccess
-             -- | BuildSuccess
-             -- | TestSuccess
-             -- | BenchSuccess
-             | CleanSuccess
-             | ExecSuccess
-             | FreezeSuccess
-             | InstallSuccess
-             | SandboxSuccess
-             deriving (Eq, Show)
-
-data TestsPaths = TestsPaths
-    { cabalPath  :: FilePath -- ^ absolute path to cabal executable.
-    , ghcPkgPath :: FilePath -- ^ absolute path to ghc-pkg executable.
-    , configPath :: FilePath -- ^ absolute path of the default config file
-                             --   to use for tests (tests are free to use
-                             --   a different one).
-    }
-
-data Result = Result
-    { successful :: Bool
-    , success    :: Success
-    , outputText :: String
-    } deriving Show
-
-nullResult :: Result
-nullResult = Result True Failure ""
-
-------------------------------------------------------------------------
--- * Config
-
-packageTestsDirectory :: FilePath
-packageTestsDirectory = "PackageTests"
-
-packageTestsConfigFile :: FilePath
-packageTestsConfigFile = "cabal-config"
-
-------------------------------------------------------------------------
--- * Running cabal commands
-
-recordRun :: (String, ExitCode, String) -> Success -> Result -> Result
-recordRun (cmd, exitCode, exeOutput) thisSucc res =
-    res { successful = successful res && exitCode == ExitSuccess
-        , success    = if exitCode == ExitSuccess then thisSucc
-                       else success res
-        , outputText =
-            (if null $ outputText res then "" else outputText res ++ "\n") ++
-            cmd ++ "\n" ++ exeOutput
-        }
-
--- | Run the clean command and return its result.
-cabal_clean :: TestsPaths -> FilePath -> [String] -> IO Result
-cabal_clean paths dir args = do
-    res <- cabal paths dir (["clean"] ++ args)
-    return $ recordRun res CleanSuccess nullResult
-
--- | Run the exec command and return its result.
-cabal_exec :: TestsPaths -> FilePath -> [String] -> IO Result
-cabal_exec paths dir args = do
-    res <- cabal paths dir (["exec"] ++ args)
-    return $ recordRun res ExecSuccess nullResult
-
--- | Run the freeze command and return its result.
-cabal_freeze :: TestsPaths -> FilePath -> [String] -> IO Result
-cabal_freeze paths dir args = do
-    res <- cabal paths dir (["freeze"] ++ args)
-    return $ recordRun res FreezeSuccess nullResult
-
--- | Run the install command and return its result.
-cabal_install :: TestsPaths -> FilePath -> [String] -> IO Result
-cabal_install paths dir args = do
-    res <- cabal paths dir (["install"] ++ args)
-    return $ recordRun res InstallSuccess nullResult
-
--- | Run the sandbox command and return its result.
-cabal_sandbox :: TestsPaths -> FilePath -> [String] -> IO Result
-cabal_sandbox paths dir args = do
-    res <- cabal paths dir (["sandbox"] ++ args)
-    return $ recordRun res SandboxSuccess nullResult
-
--- | Returns the command that was issued, the return code, and the output text.
-cabal :: TestsPaths -> FilePath -> [String] -> IO (String, ExitCode, String)
-cabal paths dir cabalArgs = do
-    run (Just dir) (cabalPath paths) args
-  where
-    args = configFileArg : cabalArgs
-    configFileArg = "--config-file=" ++ configPath paths
-
--- | Returns the command that was issued, the return code, and the output text
-run :: Maybe FilePath -> String -> [String] -> IO (String, ExitCode, String)
-run cwd path args = do
-    verbosity <- getVerbosity
-    -- path is relative to the current directory; canonicalizePath makes it
-    -- absolute, so that runProcess will find it even when changing directory.
-    path' <- do pathExists <- doesFileExist path
-                canonicalizePath (if pathExists then path else path <.> exeExtension)
-    printRawCommandAndArgs verbosity path' args
-    (readh, writeh) <- createPipe
-    pid <- runProcess path' args cwd Nothing Nothing (Just writeh) (Just writeh)
-
-    -- fork off a thread to start consuming the output
-    out <- suckH [] readh
-    hClose readh
-
-    -- wait for the program to terminate
-    exitcode <- waitForProcess pid
-    let fullCmd = unwords (path' : args)
-    return ("\"" ++ fullCmd ++ "\" in " ++ fromMaybe "" cwd, exitcode, out)
-  where
-    suckH output h = do
-        eof <- hIsEOF h
-        if eof
-            then return (reverse output)
-            else do
-                c <- hGetChar h
-                suckH (c:output) h
-
-------------------------------------------------------------------------
--- * Test helpers
-
-assertCleanSucceeded :: Result -> Assertion
-assertCleanSucceeded result = unless (successful result) $
-    assertFailure $
-    "expected: \'cabal clean\' should succeed\n" ++
-    "  output: " ++ outputText result
-
-assertExecSucceeded :: Result -> Assertion
-assertExecSucceeded result = unless (successful result) $
-    assertFailure $
-    "expected: \'cabal exec\' should succeed\n" ++
-    "  output: " ++ outputText result
-
-assertExecFailed :: Result -> Assertion
-assertExecFailed result = when (successful result) $
-    assertFailure $
-    "expected: \'cabal exec\' should fail\n" ++
-    "  output: " ++ outputText result
-
-assertFreezeSucceeded :: Result -> Assertion
-assertFreezeSucceeded result = unless (successful result) $
-    assertFailure $
-    "expected: \'cabal freeze\' should succeed\n" ++
-    "  output: " ++ outputText result
-
-assertInstallSucceeded :: Result -> Assertion
-assertInstallSucceeded result = unless (successful result) $
-    assertFailure $
-    "expected: \'cabal install\' should succeed\n" ++
-    "  output: " ++ outputText result
-
-assertSandboxSucceeded :: Result -> Assertion
-assertSandboxSucceeded result = unless (successful result) $
-    assertFailure $
-    "expected: \'cabal sandbox\' should succeed\n" ++
-    "  output: " ++ outputText result
-
-------------------------------------------------------------------------
--- Verbosity
-
-lookupEnv :: String -> IO (Maybe String)
-lookupEnv name =
-    (fmap Just $ getEnv name)
-    `E.catch` \ (e :: IOError) ->
-        if isDoesNotExistError e
-        then return Nothing
-        else E.throw e
-
--- TODO: Convert to a "-v" flag instead.
-getVerbosity :: IO Verbosity
-getVerbosity = do
-    maybe normal (readEOrFail flagToVerbosity) `fmap` lookupEnv "VERBOSE"