diff --git a/Cabal/src/Distribution/Simple/Configure.hs b/Cabal/src/Distribution/Simple/Configure.hs index 4324d67a09574ca1ad6ca05ef48615242ce1dc96..1cf7214f035a0f8cdd330105152b5f2ff5c90a62 100644 --- a/Cabal/src/Distribution/Simple/Configure.hs +++ b/Cabal/src/Distribution/Simple/Configure.hs @@ -2587,7 +2587,12 @@ checkRelocatable verbosity pkg lbi = -- @shortRelativePath prefix pkgroot@ will return a path with -- @..@s and following check will fail without @canonicalizePath@. canonicalized <- canonicalizePath libdir - unless (p `isPrefixOf` canonicalized) $ + -- The @prefix@ itself must also be canonicalized because + -- canonicalizing @libdir@ may expand symlinks which would make + -- @prefix@ no longer being a prefix of @canonical libdir@, + -- while @canonical p@ could be a prefix of @canonical libdir@ + p' <- canonicalizePath p + unless (p' `isPrefixOf` canonicalized) $ dieWithException verbosity $ LibDirDepsPrefixNotRelative libdir p | otherwise = diff --git a/cabal-testsuite/PackageTests/AutoconfBadPaths/cabal.out b/cabal-testsuite/PackageTests/AutoconfBadPaths/cabal.out index 2e491b9c3488197a5d405af60e390d4808a5e0ab..057b79b0de6925e73905a90075a29207b3c87d03 100644 --- a/cabal-testsuite/PackageTests/AutoconfBadPaths/cabal.out +++ b/cabal-testsuite/PackageTests/AutoconfBadPaths/cabal.out @@ -1,82 +1,82 @@ # cabal v1-configure Resolving dependencies... Configuring test-0... -Warning: The path to the './configure' script, '/<ROOT>/cabal.dist/foo bar/configure', contains the character ' ' (space). This may cause the script to fail with an obscure error, or for building the package to fail later. +Warning: The path to the './configure' script, '/<ROOT>/foo bar/configure', contains the character ' ' (space). This may cause the script to fail with an obscure error, or for building the package to fail later. # cabal v1-configure Resolving dependencies... Configuring test-0... -Warning: The path to the './configure' script, '/<ROOT>/cabal.dist/foo bar/configure', contains the character ' ' (tab). This may cause the script to fail with an obscure error, or for building the package to fail later. +Warning: The path to the './configure' script, '/<ROOT>/foo bar/configure', contains the character ' ' (tab). This may cause the script to fail with an obscure error, or for building the package to fail later. # cabal v1-configure Resolving dependencies... Configuring test-0... -Warning: The path to the './configure' script, '/<ROOT>/cabal.dist/foo +Warning: The path to the './configure' script, '/<ROOT>/foo bar/configure', contains the character ' ' (newline). This may cause the script to fail with an obscure error, or for building the package to fail later. # cabal v1-configure Resolving dependencies... Configuring test-0... -Warning: The path to the './configure' script, '/<ROOT>/cabal.dist/foo"bar/configure', contains the character '"' (double quote). This may cause the script to fail with an obscure error, or for building the package to fail later. +Warning: The path to the './configure' script, '/<ROOT>/foo"bar/configure', contains the character '"' (double quote). This may cause the script to fail with an obscure error, or for building the package to fail later. # cabal v1-configure Resolving dependencies... Configuring test-0... -Warning: The path to the './configure' script, '/<ROOT>/cabal.dist/foo#bar/configure', contains the character '#' (hash). This may cause the script to fail with an obscure error, or for building the package to fail later. +Warning: The path to the './configure' script, '/<ROOT>/foo#bar/configure', contains the character '#' (hash). This may cause the script to fail with an obscure error, or for building the package to fail later. # cabal v1-configure Resolving dependencies... Configuring test-0... -Warning: The path to the './configure' script, '/<ROOT>/cabal.dist/foo$bar/configure', contains the character '$' (dollar sign). This may cause the script to fail with an obscure error, or for building the package to fail later. +Warning: The path to the './configure' script, '/<ROOT>/foo$bar/configure', contains the character '$' (dollar sign). This may cause the script to fail with an obscure error, or for building the package to fail later. # cabal v1-configure Resolving dependencies... Configuring test-0... -Warning: The path to the './configure' script, '/<ROOT>/cabal.dist/foo&bar/configure', contains the character '&' (ampersand). This may cause the script to fail with an obscure error, or for building the package to fail later. +Warning: The path to the './configure' script, '/<ROOT>/foo&bar/configure', contains the character '&' (ampersand). This may cause the script to fail with an obscure error, or for building the package to fail later. # cabal v1-configure Resolving dependencies... Configuring test-0... -Warning: The path to the './configure' script, '/<ROOT>/cabal.dist/foo'bar/configure', contains the character ''' (single quote). This may cause the script to fail with an obscure error, or for building the package to fail later. +Warning: The path to the './configure' script, '/<ROOT>/foo'bar/configure', contains the character ''' (single quote). This may cause the script to fail with an obscure error, or for building the package to fail later. # cabal v1-configure Resolving dependencies... Configuring test-0... -Warning: The path to the './configure' script, '/<ROOT>/cabal.dist/foo(bar/configure', contains the character '(' (left bracket). This may cause the script to fail with an obscure error, or for building the package to fail later. +Warning: The path to the './configure' script, '/<ROOT>/foo(bar/configure', contains the character '(' (left bracket). This may cause the script to fail with an obscure error, or for building the package to fail later. # cabal v1-configure Resolving dependencies... Configuring test-0... -Warning: The path to the './configure' script, '/<ROOT>/cabal.dist/foo)bar/configure', contains the character ')' (right bracket). This may cause the script to fail with an obscure error, or for building the package to fail later. +Warning: The path to the './configure' script, '/<ROOT>/foo)bar/configure', contains the character ')' (right bracket). This may cause the script to fail with an obscure error, or for building the package to fail later. # cabal v1-configure Resolving dependencies... Configuring test-0... -Warning: The path to the './configure' script, '/<ROOT>/cabal.dist/foo*bar/configure', contains the character '*' (star). This may cause the script to fail with an obscure error, or for building the package to fail later. +Warning: The path to the './configure' script, '/<ROOT>/foo*bar/configure', contains the character '*' (star). This may cause the script to fail with an obscure error, or for building the package to fail later. # cabal v1-configure Resolving dependencies... Configuring test-0... -Warning: The path to the './configure' script, '/<ROOT>/cabal.dist/foo;bar/configure', contains the character ';' (semicolon). This may cause the script to fail with an obscure error, or for building the package to fail later. +Warning: The path to the './configure' script, '/<ROOT>/foo;bar/configure', contains the character ';' (semicolon). This may cause the script to fail with an obscure error, or for building the package to fail later. # cabal v1-configure Resolving dependencies... Configuring test-0... -Warning: The path to the './configure' script, '/<ROOT>/cabal.dist/foo<bar/configure', contains the character '<' (less-than sign). This may cause the script to fail with an obscure error, or for building the package to fail later. +Warning: The path to the './configure' script, '/<ROOT>/foo<bar/configure', contains the character '<' (less-than sign). This may cause the script to fail with an obscure error, or for building the package to fail later. # cabal v1-configure Resolving dependencies... Configuring test-0... -Warning: The path to the './configure' script, '/<ROOT>/cabal.dist/foo=bar/configure', contains the character '=' (equals sign). This may cause the script to fail with an obscure error, or for building the package to fail later. +Warning: The path to the './configure' script, '/<ROOT>/foo=bar/configure', contains the character '=' (equals sign). This may cause the script to fail with an obscure error, or for building the package to fail later. # cabal v1-configure Resolving dependencies... Configuring test-0... -Warning: The path to the './configure' script, '/<ROOT>/cabal.dist/foo>bar/configure', contains the character '>' (greater-than sign). This may cause the script to fail with an obscure error, or for building the package to fail later. +Warning: The path to the './configure' script, '/<ROOT>/foo>bar/configure', contains the character '>' (greater-than sign). This may cause the script to fail with an obscure error, or for building the package to fail later. # cabal v1-configure Resolving dependencies... Configuring test-0... -Warning: The path to the './configure' script, '/<ROOT>/cabal.dist/foo?bar/configure', contains the character '?' (question mark). This may cause the script to fail with an obscure error, or for building the package to fail later. +Warning: The path to the './configure' script, '/<ROOT>/foo?bar/configure', contains the character '?' (question mark). This may cause the script to fail with an obscure error, or for building the package to fail later. # cabal v1-configure Resolving dependencies... Configuring test-0... -Warning: The path to the './configure' script, '/<ROOT>/cabal.dist/foo[bar/configure', contains the character '[' (left square bracket). This may cause the script to fail with an obscure error, or for building the package to fail later. +Warning: The path to the './configure' script, '/<ROOT>/foo[bar/configure', contains the character '[' (left square bracket). This may cause the script to fail with an obscure error, or for building the package to fail later. # cabal v1-configure Resolving dependencies... Configuring test-0... -Warning: The path to the './configure' script, '/<ROOT>/cabal.dist/foo/bar/configure', contains the character '/' (backslash). This may cause the script to fail with an obscure error, or for building the package to fail later. +Warning: The path to the './configure' script, '/<ROOT>/foo/bar/configure', contains the character '/' (backslash). This may cause the script to fail with an obscure error, or for building the package to fail later. # cabal v1-configure Resolving dependencies... Configuring test-0... -Warning: The path to the './configure' script, '/<ROOT>/cabal.dist/foo`bar/configure', contains the character '`' (backtick). This may cause the script to fail with an obscure error, or for building the package to fail later. +Warning: The path to the './configure' script, '/<ROOT>/foo`bar/configure', contains the character '`' (backtick). This may cause the script to fail with an obscure error, or for building the package to fail later. # cabal v1-configure Resolving dependencies... Configuring test-0... -Warning: The path to the './configure' script, '/<ROOT>/cabal.dist/foo|bar/configure', contains the character '|' (pipe). This may cause the script to fail with an obscure error, or for building the package to fail later. +Warning: The path to the './configure' script, '/<ROOT>/foo|bar/configure', contains the character '|' (pipe). This may cause the script to fail with an obscure error, or for building the package to fail later. diff --git a/cabal-testsuite/PackageTests/AutoconfBadPaths/cabal.test.hs b/cabal-testsuite/PackageTests/AutoconfBadPaths/cabal.test.hs index 74c9d8806b882c7b7b83f30cb6a972a77543e301..7325eb0684ccdc7d3ad680d763e641ca10fdbca8 100644 --- a/cabal-testsuite/PackageTests/AutoconfBadPaths/cabal.test.hs +++ b/cabal-testsuite/PackageTests/AutoconfBadPaths/cabal.test.hs @@ -1,5 +1,7 @@ import Test.Cabal.Prelude import Data.Foldable (traverse_) +import Distribution.Simple.Utils +import System.Directory main = cabalTest $ do -- Test the forbidden characters except NUL. Reference: -- https://www.gnu.org/software/autoconf/manual/autoconf.html#File-System-Conventions @@ -31,11 +33,21 @@ main = cabalTest $ do , "foo|bar" ] where + setup dir = do + env <- getTestEnv + let cwd = testCurrentDir env + liftIO $ createDirectory (testCurrentDir env </> dir) + liftIO $ copyFiles minBound (testCurrentDir env </> dir) + [ (cwd, "configure") + , (cwd, "Setup.hs") + , (cwd, "test.cabal") + ] -- 'cabal' from the prelude requires the command to succeed; we -- don't mind if it fails, so long as we get the warning. This is -- an inlined+specialised version of 'cabal' for v1-configure. - check dir = withSourceCopyDir dir $ + check dir = defaultRecordMode RecordMarked $ do + setup dir recordHeader ["cabal", "v1-configure"] env <- getTestEnv let args = @@ -46,7 +58,7 @@ main = cabalTest $ do ] configured_prog <- requireProgramM cabalProgram r <- liftIO $ run (testVerbosity env) - (Just (testCurrentDir env)) + (Just (testCurrentDir env </> dir)) (testEnvironment env) (programPath configured_prog) args Nothing diff --git a/cabal-testsuite/PackageTests/Check/ConfiguredPackage/Paths/InvalidWin/cabal.test.hs b/cabal-testsuite/PackageTests/Check/ConfiguredPackage/Paths/InvalidWin/cabal.test.hs index e99fccc6bc4450b0be706fc7c4e7259c2ce78122..2201d7c73dcbd4fdde3a9ed90bbb94ecfb64757d 100644 --- a/cabal-testsuite/PackageTests/Check/ConfiguredPackage/Paths/InvalidWin/cabal.test.hs +++ b/cabal-testsuite/PackageTests/Check/ConfiguredPackage/Paths/InvalidWin/cabal.test.hs @@ -3,7 +3,7 @@ import Test.Cabal.Prelude import System.Directory (createDirectoryIfMissing) -- Invalid Windows filepath. -main = cabalTest . withSourceCopy $ do +main = cabalTest $ do skipIfWindows cwd <- testCurrentDir <$> getTestEnv liftIO $ createDirectoryIfMissing False $ cwd </> "n?ul" diff --git a/cabal-testsuite/PackageTests/Check/ConfiguredPackage/Paths/RecursiveGlobInRoot/a.hs b/cabal-testsuite/PackageTests/Check/ConfiguredPackage/Paths/RecursiveGlobInRoot/a.hs new file mode 100644 index 0000000000000000000000000000000000000000..6ca9a1fce6e73b95c119bd6abf452df4047eea99 --- /dev/null +++ b/cabal-testsuite/PackageTests/Check/ConfiguredPackage/Paths/RecursiveGlobInRoot/a.hs @@ -0,0 +1 @@ +module Main where diff --git a/cabal-testsuite/PackageTests/Check/ConfiguredPackage/Paths/RelativeOutside/RelativeOutsideInner/cabal.out b/cabal-testsuite/PackageTests/Check/ConfiguredPackage/Paths/RelativeOutside/cabal.out similarity index 100% rename from cabal-testsuite/PackageTests/Check/ConfiguredPackage/Paths/RelativeOutside/RelativeOutsideInner/cabal.out rename to cabal-testsuite/PackageTests/Check/ConfiguredPackage/Paths/RelativeOutside/cabal.out diff --git a/cabal-testsuite/PackageTests/Check/ConfiguredPackage/Paths/RelativeOutside/RelativeOutsideInner/cabal.test.hs b/cabal-testsuite/PackageTests/Check/ConfiguredPackage/Paths/RelativeOutside/cabal.test.hs similarity index 57% rename from cabal-testsuite/PackageTests/Check/ConfiguredPackage/Paths/RelativeOutside/RelativeOutsideInner/cabal.test.hs rename to cabal-testsuite/PackageTests/Check/ConfiguredPackage/Paths/RelativeOutside/cabal.test.hs index 09a670ffb24902537889b3237f82910ecd79b8c0..8da253ff8b4a661d66f0b9f53a534c24284240bc 100644 --- a/cabal-testsuite/PackageTests/Check/ConfiguredPackage/Paths/RelativeOutside/RelativeOutsideInner/cabal.test.hs +++ b/cabal-testsuite/PackageTests/Check/ConfiguredPackage/Paths/RelativeOutside/cabal.test.hs @@ -2,4 +2,4 @@ import Test.Cabal.Prelude -- Relative filepath outside source tree. main = cabalTest $ - fails $ cabal "check" [] + fails $ withDirectory "RelativeOutsideInner" $ cabal "check" [] diff --git a/cabal-testsuite/PackageTests/Freeze/disable-benchmarks.test.hs b/cabal-testsuite/PackageTests/Freeze/disable-benchmarks.test.hs index 52ef66110deda3ce4531454343fb6d156382e221..ae5dca1369cf48826b930fcb6a62eda75ccc0979 100644 --- a/cabal-testsuite/PackageTests/Freeze/disable-benchmarks.test.hs +++ b/cabal-testsuite/PackageTests/Freeze/disable-benchmarks.test.hs @@ -1,6 +1,6 @@ import Test.Cabal.Prelude main = cabalTest $ do - withRepo "repo" . withSourceCopy $ do + withRepo "repo" $ do cabal "v1-freeze" ["--disable-benchmarks"] cwd <- fmap testCurrentDir getTestEnv assertFileDoesNotContain (cwd </> "cabal.config") "criterion" diff --git a/cabal-testsuite/PackageTests/Freeze/disable-tests.test.hs b/cabal-testsuite/PackageTests/Freeze/disable-tests.test.hs index a959240586c7dee89bbdda51487ea258d1a9d1d1..0d56e932614eb2eb7b87d9f0672f09a4be01f603 100644 --- a/cabal-testsuite/PackageTests/Freeze/disable-tests.test.hs +++ b/cabal-testsuite/PackageTests/Freeze/disable-tests.test.hs @@ -1,6 +1,6 @@ import Test.Cabal.Prelude main = cabalTest $ do - withRepo "repo" . withSourceCopy $ do + withRepo "repo" $ do cabal "v1-freeze" ["--disable-tests"] cwd <- fmap testCurrentDir getTestEnv assertFileDoesNotContain (cwd </> "cabal.config") "test-framework" diff --git a/cabal-testsuite/PackageTests/Freeze/dry-run.test.hs b/cabal-testsuite/PackageTests/Freeze/dry-run.test.hs index 11130ba8c2c5b3006f3f75065eeda5ea65d5bb15..89a650496a84f55ab7b36c5c18cf26f93dd59945 100644 --- a/cabal-testsuite/PackageTests/Freeze/dry-run.test.hs +++ b/cabal-testsuite/PackageTests/Freeze/dry-run.test.hs @@ -1,6 +1,6 @@ import Test.Cabal.Prelude main = cabalTest $ do - withRepo "repo" . withSourceCopy $ do + withRepo "repo" $ do recordMode DoNotRecord $ cabal "v1-freeze" ["--dry-run"] cwd <- fmap testCurrentDir getTestEnv shouldNotExist (cwd </> "cabal.config") diff --git a/cabal-testsuite/PackageTests/Freeze/enable-benchmarks.test.hs b/cabal-testsuite/PackageTests/Freeze/enable-benchmarks.test.hs index d525c1d26fffaff1d6682bcf548c95959f72e6ea..995b91025559ea451ac731792fd71f6c58baa4ff 100644 --- a/cabal-testsuite/PackageTests/Freeze/enable-benchmarks.test.hs +++ b/cabal-testsuite/PackageTests/Freeze/enable-benchmarks.test.hs @@ -1,6 +1,6 @@ import Test.Cabal.Prelude main = cabalTest $ do - withRepo "repo" . withSourceCopy $ do + withRepo "repo" $ do cabal "v1-freeze" ["--enable-benchmarks"] cwd <- fmap testCurrentDir getTestEnv assertFileDoesContain (cwd </> "cabal.config") "criterion" diff --git a/cabal-testsuite/PackageTests/Freeze/enable-tests.test.hs b/cabal-testsuite/PackageTests/Freeze/enable-tests.test.hs index 8a43b5b6dafea567b313b9dc489df1f357fbcfc5..d24eb5ee9ab9a5345dcad1c147d0c519273bfdf2 100644 --- a/cabal-testsuite/PackageTests/Freeze/enable-tests.test.hs +++ b/cabal-testsuite/PackageTests/Freeze/enable-tests.test.hs @@ -1,6 +1,6 @@ import Test.Cabal.Prelude main = cabalTest $ do - withRepo "repo" . withSourceCopy $ do + withRepo "repo" $ do cabal "v1-freeze" ["--enable-tests"] cwd <- fmap testCurrentDir getTestEnv assertFileDoesContain (cwd </> "cabal.config") "test-framework" diff --git a/cabal-testsuite/PackageTests/Freeze/freeze.test.hs b/cabal-testsuite/PackageTests/Freeze/freeze.test.hs index 2961a0e0055fb7a94a12e5adf094bce67d6b4bb7..e669febbd41060f6dd54c3389f59b1e322f9b4d6 100644 --- a/cabal-testsuite/PackageTests/Freeze/freeze.test.hs +++ b/cabal-testsuite/PackageTests/Freeze/freeze.test.hs @@ -1,6 +1,6 @@ import Test.Cabal.Prelude main = cabalTest $ do - withRepo "repo" . withSourceCopy $ do + withRepo "repo" $ do cabal "v1-freeze" [] cwd <- fmap testCurrentDir getTestEnv assertFileDoesNotContain (cwd </> "cabal.config") "exceptions" diff --git a/cabal-testsuite/PackageTests/HaddockProject/haddock-project.out b/cabal-testsuite/PackageTests/HaddockProject/haddock-project.out index a2f14d6a6f20a32d65ef138463addc7c7b80fd12..cde81e2c2bac6d9510fef06fb159312c6b02a16f 100644 --- a/cabal-testsuite/PackageTests/HaddockProject/haddock-project.out +++ b/cabal-testsuite/PackageTests/HaddockProject/haddock-project.out @@ -21,5 +21,5 @@ Installing library in <PATH> Configuring library for a-0.1.0.0... Preprocessing library for a-0.1.0.0... Running Haddock on library for a-0.1.0.0... -Documentation created: <ROOT>/haddock-project.dist/source/dist-newstyle/build/<ARCH>/ghc-<GHCVER>/a-0.1.0.0/doc/html/a/ +Documentation created: <ROOT>/dist-newstyle/build/<ARCH>/ghc-<GHCVER>/a-0.1.0.0/doc/html/a/ Documentation created: haddocks/index.html diff --git a/cabal-testsuite/PackageTests/HaddockProject/haddock-project.test.hs b/cabal-testsuite/PackageTests/HaddockProject/haddock-project.test.hs index 6d889a141635370c9eec541d074df64ba7ab7833..923b1ad87047ef4db1031903e0251aab3837fd68 100644 --- a/cabal-testsuite/PackageTests/HaddockProject/haddock-project.test.hs +++ b/cabal-testsuite/PackageTests/HaddockProject/haddock-project.test.hs @@ -1,7 +1,7 @@ import Test.Cabal.Prelude import System.Directory (doesFileExist, removeDirectory) -main = cabalTest . withRepo "repo" . withSourceCopy $ do +main = cabalTest . withRepo "repo" $ do skipUnlessGhcVersion ">= 9.4.0" env <- getTestEnv let testDir = testCurrentDir env diff --git a/cabal-testsuite/PackageTests/Init/init-backup.test.hs b/cabal-testsuite/PackageTests/Init/init-backup.test.hs index f1c4ab0fc74f79bd050a55608a43d3ebf91eda79..e9e5c1293581e558fc749e7a49b828396e9f9810 100644 --- a/cabal-testsuite/PackageTests/Init/init-backup.test.hs +++ b/cabal-testsuite/PackageTests/Init/init-backup.test.hs @@ -1,11 +1,10 @@ import Test.Cabal.Prelude -main = cabalTest $ - withSourceCopyDir "app" $ do - cwd <- fmap testSourceCopyDir getTestEnv +main = cabalTest $ do + cwd <- fmap testCurrentDir getTestEnv - (initOut, buildOut) <- withDirectory cwd $ do - initOut <- cabalWithStdin "init" ["-i"] + (initOut, buildOut) <- do + initOut <- cabalWithStdin "init" ["-i", "-p", "app"] "2\ny\n5\n\n\n2\n\n\n\n\n\n\n\n\n\n" setup "configure" [] buildOut <- setup' "build" ["app"] diff --git a/cabal-testsuite/PackageTests/Init/init-interactive-empty-folder.test.hs b/cabal-testsuite/PackageTests/Init/init-interactive-empty-folder.test.hs index 4c43824465179117884ad5ba7487566e36d500bb..87472bdc4164a0ba65da71a6a9bed69208374abb 100644 --- a/cabal-testsuite/PackageTests/Init/init-interactive-empty-folder.test.hs +++ b/cabal-testsuite/PackageTests/Init/init-interactive-empty-folder.test.hs @@ -1,8 +1,10 @@ import Test.Cabal.Prelude +import System.Directory main = cabalTest $ do - tmpDir <- testTmpDir <$> getTestEnv - withDirectory tmpDir $ do + tmpDir <- testCurrentDir <$> getTestEnv + liftIO $ createDirectory (tmpDir </> "empty") + withDirectory (tmpDir </> "empty") $ do res <- cabalWithStdin "init" ["-i"] (replicate 20 '\n') -- Default all the way down. diff --git a/cabal-testsuite/PackageTests/Init/init-interactive-ghc2021.test.hs b/cabal-testsuite/PackageTests/Init/init-interactive-ghc2021.test.hs index 8b53ce18b30ef07bfa66d71fcedb2eb1aa385764..7df3f662212f426ce070c73479bb095d546a4bdc 100644 --- a/cabal-testsuite/PackageTests/Init/init-interactive-ghc2021.test.hs +++ b/cabal-testsuite/PackageTests/Init/init-interactive-ghc2021.test.hs @@ -1,11 +1,9 @@ import Test.Cabal.Prelude -main = cabalTest $ - withSourceCopyDir "app" $ do - cwd <- fmap testSourceCopyDir getTestEnv +main = cabalTest $ do + env <- getTestEnv + buildOut <- + cabalWithStdin "init" ["-i", "-p", "app"] + "2\n\n5\n\n\n2\n\n\n\n\n\n\n3\n\n" - buildOut <- withDirectory cwd $ do - cabalWithStdin "init" ["-i"] - "2\n\n5\n\n\n2\n\n\n\n\n\n\n\n3\n\n" - - assertFileDoesContain (cwd </> "app.cabal") "GHC2021" + assertFileDoesContain (testCurrentDir env </> "app.cabal") "GHC2021" diff --git a/cabal-testsuite/PackageTests/Init/init-interactive-legacy.test.hs b/cabal-testsuite/PackageTests/Init/init-interactive-legacy.test.hs index 3fd9415d5701f8fe87fde63aeb1d4ea8eb2a9998..75b6472e142919dcde6d5597b54c2b11a02bab89 100644 --- a/cabal-testsuite/PackageTests/Init/init-interactive-legacy.test.hs +++ b/cabal-testsuite/PackageTests/Init/init-interactive-legacy.test.hs @@ -1,12 +1,10 @@ import Test.Cabal.Prelude -main = cabalTest $ - withSourceCopyDir "app" $ do - cwd <- fmap testSourceCopyDir getTestEnv - - buildOut <- withDirectory cwd $ do - cabalWithStdin "init" ["-i"] - "2\n\n1\n\n\n10\n\n\n\n\n\n\n\n\n\n" +main = cabalTest $ do + cwd <- testCurrentDir <$> getTestEnv + buildOut <- do + cabalWithStdin "init" ["-i", "-p", "app"] + "2\n\n1\n\n10\n\n\n\n\n\n\n\n\n\n" setup "configure" [] setup' "build" ["app"] diff --git a/cabal-testsuite/PackageTests/Init/init-interactive.test.hs b/cabal-testsuite/PackageTests/Init/init-interactive.test.hs index 86bda8b028af090960960c81ce86a1b7a42a91bc..4e1cbf816cfff67350fef1b51df7765d5af927e6 100644 --- a/cabal-testsuite/PackageTests/Init/init-interactive.test.hs +++ b/cabal-testsuite/PackageTests/Init/init-interactive.test.hs @@ -1,11 +1,10 @@ import Test.Cabal.Prelude -main = cabalTest $ - withSourceCopyDir "app" $ do - cwd <- fmap testSourceCopyDir getTestEnv +main = cabalTest $ do + cwd <- fmap testCurrentDir getTestEnv buildOut <- withDirectory cwd $ do - cabalWithStdin "init" ["-i"] + cabalWithStdin "init" ["-i", "-p", "app"] "2\n\n5\n\n\n\n\n\n\n\n\n\n\n\n\n" setup "configure" [] setup' "build" ["app"] diff --git a/cabal-testsuite/PackageTests/Init/init-legacy.test.hs b/cabal-testsuite/PackageTests/Init/init-legacy.test.hs index eac7b312fb5a5087b9e944a02f8f4ff0960933e3..e315315742828e148f3cf90e483682449044ee07 100644 --- a/cabal-testsuite/PackageTests/Init/init-legacy.test.hs +++ b/cabal-testsuite/PackageTests/Init/init-legacy.test.hs @@ -1,11 +1,10 @@ import Test.Cabal.Prelude -main = cabalTest $ - withSourceCopyDir "app" $ do - cwd <- fmap testSourceCopyDir getTestEnv +main = cabalTest $ do + cwd <- fmap testCurrentDir getTestEnv - buildOut <- withDirectory cwd $ do - cabal "init" ["-n", "--exe", "--application-dir=app", "--main-is=Main.hs", "--cabal-version=1.24"] + buildOut <- do + cabal "init" ["-n", "--exe", "-p", "app", "--application-dir=app", "--main-is=Main.hs", "--cabal-version=1.24"] setup "configure" [] setup' "build" ["app"] diff --git a/cabal-testsuite/PackageTests/Init/init.test.hs b/cabal-testsuite/PackageTests/Init/init.test.hs index 83a512d5893d7bfa78b42fca190bb8dfa8dffd7f..c7739c4fcb2a27dd214c2a1302b7a363a1219634 100644 --- a/cabal-testsuite/PackageTests/Init/init.test.hs +++ b/cabal-testsuite/PackageTests/Init/init.test.hs @@ -1,11 +1,11 @@ import Test.Cabal.Prelude +import System.Directory -main = cabalTest $ - withSourceCopyDir "app" $ do - cwd <- fmap testSourceCopyDir getTestEnv +main = cabalTest $ do + cwd <- fmap testCurrentDir getTestEnv - buildOut <- withDirectory cwd $ do - cabal "init" ["-n", "--exe", "--application-dir=app", "--main-is=Main.hs"] + buildOut <- do + cabal "init" ["-n", "--exe", "-p", "app", "--application-dir=app", "--main-is=Main.hs"] setup "configure" [] setup' "build" ["app"] diff --git a/cabal-testsuite/PackageTests/LinkerOptions/NonignoredConfigs/cabal.out b/cabal-testsuite/PackageTests/LinkerOptions/NonignoredConfigs/cabal.out index 34592d494be8068e0bfcb1248ec26b7fc6efe10e..ecd7f77f7c71950bae6c14b58e351d9fbc0ca1f0 100644 --- a/cabal-testsuite/PackageTests/LinkerOptions/NonignoredConfigs/cabal.out +++ b/cabal-testsuite/PackageTests/LinkerOptions/NonignoredConfigs/cabal.out @@ -1,6 +1,6 @@ # install options: --disable-deterministic --lib --package-env=<ROOT>/cabal.dist/basic0.env basic # cabal v2-install -Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz +Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic0/dist/sdist/basic-0.1.tar.gz Resolving dependencies... Build profile: -w ghc-<GHCVER> -O1 In order, the following will be built: @@ -11,16 +11,16 @@ Building library for basic-0.1... Installing library in <PATH> # install options: --disable-deterministic --lib --package-env=<ROOT>/cabal.dist/basic0.env basic # cabal v2-install -Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz +Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic0/dist/sdist/basic-0.1.tar.gz Error: [Cabal-7145] Packages requested to install already exist in environment file at <ROOT>/cabal.dist/basic0.env. Overwriting them may break other packages. Use --force-reinstalls to proceed anyway. Packages: basic # install options: --force-reinstalls --disable-deterministic --lib --package-env=<ROOT>/cabal.dist/basic0.env basic # cabal v2-install -Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz +Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic0/dist/sdist/basic-0.1.tar.gz Resolving dependencies... # install options: --disable-deterministic --lib --package-env=<ROOT>/cabal.dist/basic1.env --enable-shared --enable-executable-dynamic --disable-library-vanilla basic # cabal v2-install -Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz +Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic1/dist/sdist/basic-0.1.tar.gz Resolving dependencies... Build profile: -w ghc-<GHCVER> -O1 In order, the following will be built: @@ -31,36 +31,36 @@ Building library for basic-0.1... Installing library in <PATH> # install options: --disable-deterministic --lib --package-env=<ROOT>/cabal.dist/basic1.env --enable-shared --enable-executable-dynamic --disable-library-vanilla basic # cabal v2-install -Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz +Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic1/dist/sdist/basic-0.1.tar.gz Error: [Cabal-7145] Packages requested to install already exist in environment file at <ROOT>/cabal.dist/basic1.env. Overwriting them may break other packages. Use --force-reinstalls to proceed anyway. Packages: basic # install options: --force-reinstalls --disable-deterministic --lib --package-env=<ROOT>/cabal.dist/basic1.env --enable-shared --enable-executable-dynamic --disable-library-vanilla basic # cabal v2-install -Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz +Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic1/dist/sdist/basic-0.1.tar.gz Resolving dependencies... # install options: --disable-deterministic --lib --package-env=<ROOT>/cabal.dist/basic2.env basic # cabal v2-install -Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz +Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic2/dist/sdist/basic-0.1.tar.gz Resolving dependencies... # install options: --disable-deterministic --lib --package-env=<ROOT>/cabal.dist/basic2.env basic # cabal v2-install -Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz +Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic2/dist/sdist/basic-0.1.tar.gz Error: [Cabal-7145] Packages requested to install already exist in environment file at <ROOT>/cabal.dist/basic2.env. Overwriting them may break other packages. Use --force-reinstalls to proceed anyway. Packages: basic # install options: --force-reinstalls --disable-deterministic --lib --package-env=<ROOT>/cabal.dist/basic2.env basic # cabal v2-install -Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz +Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic2/dist/sdist/basic-0.1.tar.gz Resolving dependencies... # install options: --disable-deterministic --lib --package-env=<ROOT>/cabal.dist/basic3.env --enable-shared --enable-executable-dynamic --disable-library-vanilla basic # cabal v2-install -Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz +Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic3/dist/sdist/basic-0.1.tar.gz Resolving dependencies... # install options: --disable-deterministic --lib --package-env=<ROOT>/cabal.dist/basic3.env --enable-shared --enable-executable-dynamic --disable-library-vanilla basic # cabal v2-install -Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz +Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic3/dist/sdist/basic-0.1.tar.gz Error: [Cabal-7145] Packages requested to install already exist in environment file at <ROOT>/cabal.dist/basic3.env. Overwriting them may break other packages. Use --force-reinstalls to proceed anyway. Packages: basic # install options: --force-reinstalls --disable-deterministic --lib --package-env=<ROOT>/cabal.dist/basic3.env --enable-shared --enable-executable-dynamic --disable-library-vanilla basic # cabal v2-install -Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz +Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic3/dist/sdist/basic-0.1.tar.gz Resolving dependencies... diff --git a/cabal-testsuite/PackageTests/LinkerOptions/NonignoredConfigs/cabal.test.hs b/cabal-testsuite/PackageTests/LinkerOptions/NonignoredConfigs/cabal.test.hs index 899bb03b430d455eadc574eaa5c3409d0be02a04..8e7c8a6391db87765b1869a390449a916b6bc0ac 100644 --- a/cabal-testsuite/PackageTests/LinkerOptions/NonignoredConfigs/cabal.test.hs +++ b/cabal-testsuite/PackageTests/LinkerOptions/NonignoredConfigs/cabal.test.hs @@ -1,4 +1,5 @@ import Test.Cabal.Prelude +import Distribution.Simple.Utils -- This test ensures the following fix holds: -- > Fix project-local build flags being ignored. @@ -59,16 +60,12 @@ main = cabalTest $ do -- dynamic flags. skipIfWindows + env <- getTestEnv withPackageDb $ do -- Phase 1: get 4 hashes according to config flags. results <- forM (zip [0..] lrun) $ \(idx, linking) -> do - withDirectory "basic" $ do - withSourceCopyDir ("basic" ++ show idx) $ do - -- (Now do ‘cd ..’, since withSourceCopyDir made our previous - -- previous such withDirectories now accumulate to be - -- relative to setup.dist/basic0, not testSourceDir - -- (see 'testCurrentDir').) - withDirectory ".." $ do + liftIO $ copyDirectoryRecursive minBound (testCurrentDir env </> "basic") (testCurrentDir env </> "basic" ++ show idx) + withDirectory ("basic" ++ show idx) $ do packageEnv <- (</> ("basic" ++ show idx ++ ".env")) . testWorkDir <$> getTestEnv let installOptions = ["--disable-deterministic", "--lib", "--package-env=" ++ packageEnv] ++ linkConfigFlags linking ++ ["basic"] recordMode RecordMarked $ do diff --git a/cabal-testsuite/PackageTests/NewBuild/MonitorCabalFiles/cabal.test.hs b/cabal-testsuite/PackageTests/NewBuild/MonitorCabalFiles/cabal.test.hs index ad2600d686276e459a69f4aebd714beed88c0dae..f25f5bcf21c8c24c3ad2d4990c7b8e1625dee750 100644 --- a/cabal-testsuite/PackageTests/NewBuild/MonitorCabalFiles/cabal.test.hs +++ b/cabal-testsuite/PackageTests/NewBuild/MonitorCabalFiles/cabal.test.hs @@ -1,6 +1,5 @@ import Test.Cabal.Prelude -main = cabalTest $ do - withSourceCopy . withDelay $ do +main = cabalTest $ withDelay $ do copySourceFileTo "q/q-broken.cabal.in" "q/q.cabal" fails $ cabal "v2-build" ["q"] delay diff --git a/cabal-testsuite/PackageTests/NewConfigure/ConfigFile/cabal.test.hs b/cabal-testsuite/PackageTests/NewConfigure/ConfigFile/cabal.test.hs index bc0a574738c227d1c3cc973a1cab42c52af2fec1..1e10c0fc284b412421b8d218a355812f7d955980 100644 --- a/cabal-testsuite/PackageTests/NewConfigure/ConfigFile/cabal.test.hs +++ b/cabal-testsuite/PackageTests/NewConfigure/ConfigFile/cabal.test.hs @@ -2,7 +2,7 @@ import Test.Cabal.Prelude -- Test that 'cabal v2-configure' generates the config file appropriately main = withShorterPathForNewBuildStore $ \storeDir -> - cabalTest . withSourceCopy $ do + cabalTest $ do cwd <- fmap testCurrentDir getTestEnv let configFile = cwd </> "cabal.project.local" diff --git a/cabal-testsuite/PackageTests/NewConfigure/LocalConfigOverwrite/cabal.test.hs b/cabal-testsuite/PackageTests/NewConfigure/LocalConfigOverwrite/cabal.test.hs index ebb8c3d2f7299647203d1486ceb26892e913f087..5ae99640441cdff8490201178c0da6b0941f474d 100644 --- a/cabal-testsuite/PackageTests/NewConfigure/LocalConfigOverwrite/cabal.test.hs +++ b/cabal-testsuite/PackageTests/NewConfigure/LocalConfigOverwrite/cabal.test.hs @@ -1,7 +1,6 @@ import Test.Cabal.Prelude -main = cabalTest $ - withSourceCopy $ do +main = cabalTest $ do cabal' "v2-configure" [] >>= assertOutputContains "backing it up to 'cabal.project.local~'" diff --git a/cabal-testsuite/PackageTests/NewFreeze/BuildTools/new_freeze.out b/cabal-testsuite/PackageTests/NewFreeze/BuildTools/new_freeze.out index 24724d6229120b21cf51cb7ce2d1362ce5bb87c7..ff47b1dd0ccf1afea42b3e56e352f5a92ea0ff8c 100644 --- a/cabal-testsuite/PackageTests/NewFreeze/BuildTools/new_freeze.out +++ b/cabal-testsuite/PackageTests/NewFreeze/BuildTools/new_freeze.out @@ -10,7 +10,7 @@ In order, the following would be built: - my-local-package-1.0 (lib) (first run) # cabal v2-freeze Resolving dependencies... -Wrote freeze file: <ROOT>/new_freeze.dist/source/cabal.project.freeze +Wrote freeze file: <ROOT>/cabal.project.freeze # cabal v2-build Resolving dependencies... Build profile: -w ghc-<GHCVER> -O1 diff --git a/cabal-testsuite/PackageTests/NewFreeze/BuildTools/new_freeze.test.hs b/cabal-testsuite/PackageTests/NewFreeze/BuildTools/new_freeze.test.hs index ff35d59f53eb496832032b8c093213b27390a4f3..ca1b4c180ee13fa23887485403bf2c507aa050fa 100644 --- a/cabal-testsuite/PackageTests/NewFreeze/BuildTools/new_freeze.test.hs +++ b/cabal-testsuite/PackageTests/NewFreeze/BuildTools/new_freeze.test.hs @@ -9,7 +9,7 @@ import System.Directory -- is one local package, which requires >= 2, and a library dependency of the -- local package, which requires < 2, so cabal should pick versions 1.0 and 3.0 -- of the build tool when there are no constraints. -main = cabalTest $ withSourceCopy $ do +main = cabalTest $ do withRepo "repo" $ do cabal' "v2-build" ["--dry-run"] >>= assertUsesLatestBuildTool diff --git a/cabal-testsuite/PackageTests/NewFreeze/Flags/new_freeze.out b/cabal-testsuite/PackageTests/NewFreeze/Flags/new_freeze.out index fdaca207030c2436a6d6bf1bffcef9b8ca2236fc..d0cc7e4ee0cb285814f7b87df3caa73d70b5c5e2 100644 --- a/cabal-testsuite/PackageTests/NewFreeze/Flags/new_freeze.out +++ b/cabal-testsuite/PackageTests/NewFreeze/Flags/new_freeze.out @@ -9,7 +9,7 @@ In order, the following would be built: - my-local-package-1.0 (lib) (first run) # cabal v2-freeze Resolving dependencies... -Wrote freeze file: <ROOT>/new_freeze.dist/source/cabal.project.freeze +Wrote freeze file: <ROOT>/cabal.project.freeze # cabal v2-build Resolving dependencies... Build profile: -w ghc-<GHCVER> -O1 diff --git a/cabal-testsuite/PackageTests/NewFreeze/Flags/new_freeze.test.hs b/cabal-testsuite/PackageTests/NewFreeze/Flags/new_freeze.test.hs index 3aef354e2220055656478de32d867e7419d28d9d..f05f941b86c4948a3a651f1808355d912b89e522 100644 --- a/cabal-testsuite/PackageTests/NewFreeze/Flags/new_freeze.test.hs +++ b/cabal-testsuite/PackageTests/NewFreeze/Flags/new_freeze.test.hs @@ -6,7 +6,7 @@ import System.Directory -- Test that 'cabal v2-freeze' freezes flag choices. my-local-package depends -- on my-library-dep. my-library-dep has a flag, my-flag, which defaults to -- true. -main = cabalTest $ withSourceCopy $ +main = cabalTest $ withRepo "repo" $ do cabal' "v2-build" ["--dry-run"] >>= assertDependencyFlagChoice True diff --git a/cabal-testsuite/PackageTests/NewFreeze/FreezeFile/new_freeze.out b/cabal-testsuite/PackageTests/NewFreeze/FreezeFile/new_freeze.out index e768c91b531e392694fe543d1cd5c85a4e5268ab..36278f475427ca47610332f282ff9d0b465b60c7 100644 --- a/cabal-testsuite/PackageTests/NewFreeze/FreezeFile/new_freeze.out +++ b/cabal-testsuite/PackageTests/NewFreeze/FreezeFile/new_freeze.out @@ -12,7 +12,7 @@ Freeze file not written due to flag(s) Freeze file not written due to flag(s) # cabal v2-freeze Resolving dependencies... -Wrote freeze file: <ROOT>/new_freeze.dist/source/cabal.project.freeze +Wrote freeze file: <ROOT>/cabal.project.freeze # cabal v2-build Resolving dependencies... Build profile: -w ghc-<GHCVER> -O1 @@ -27,7 +27,7 @@ Configuring executable 'my-exe' for my-local-package-1.0... Preprocessing executable 'my-exe' for my-local-package-1.0... Building executable 'my-exe' for my-local-package-1.0... # cabal v2-freeze -Wrote freeze file: <ROOT>/new_freeze.dist/source/cabal.project.freeze +Wrote freeze file: <ROOT>/cabal.project.freeze # cabal v2-build Resolving dependencies... Build profile: -w ghc-<GHCVER> -O1 @@ -35,4 +35,4 @@ In order, the following would be built: - my-library-dep-2.0 (lib) (requires build) - my-local-package-1.0 (exe:my-exe) (configuration changed) # cabal v2-freeze -Wrote freeze file: <ROOT>/new_freeze.dist/source/cabal.project.freeze +Wrote freeze file: <ROOT>/cabal.project.freeze diff --git a/cabal-testsuite/PackageTests/NewFreeze/FreezeFile/new_freeze.test.hs b/cabal-testsuite/PackageTests/NewFreeze/FreezeFile/new_freeze.test.hs index 912649bba8c43cee66ed278069abf49473f7895d..b59c0ee7f319cce9a49dcedec23f88a16a1e7bc1 100644 --- a/cabal-testsuite/PackageTests/NewFreeze/FreezeFile/new_freeze.test.hs +++ b/cabal-testsuite/PackageTests/NewFreeze/FreezeFile/new_freeze.test.hs @@ -6,7 +6,7 @@ import System.Directory -- Test for 'cabal v2-freeze' with only a single library dependency. -- my-local-package depends on my-library-dep, which has versions 1.0 and 2.0. main = withShorterPathForNewBuildStore $ \storeDir -> - cabalTest $ withSourceCopy $ + cabalTest $ withRepo "repo" $ do cwd <- fmap testCurrentDir getTestEnv let freezeFile = cwd </> "cabal.project.freeze" diff --git a/cabal-testsuite/PackageTests/NewHaddock/HaddockOutput/HaddockOutputCmd/cabal.test.hs b/cabal-testsuite/PackageTests/NewHaddock/HaddockOutput/HaddockOutputCmd/cabal.test.hs index 47e4c5c38e851a6cf2f753d75723ccebd582374a..1bfe939dab9132f54e2adaae44754aab0546bd1c 100644 --- a/cabal-testsuite/PackageTests/NewHaddock/HaddockOutput/HaddockOutputCmd/cabal.test.hs +++ b/cabal-testsuite/PackageTests/NewHaddock/HaddockOutput/HaddockOutputCmd/cabal.test.hs @@ -4,7 +4,7 @@ import Test.Cabal.Prelude -- Test that `cabal haddock --haddock-output-dir` works from the command line. main = cabalTest . withRepo "repo" $ do - testDir <- testSourceDir <$> getTestEnv + testDir <- testCurrentDir <$> getTestEnv let docsDir = testDir </> "docs" liftIO (removePathForcibly docsDir) r <- cabal' "haddock" ["--haddock-output-dir=docs", "A"] diff --git a/cabal-testsuite/PackageTests/NewHaddock/HaddockOutput/HaddockOutputConfig/cabal.test.hs b/cabal-testsuite/PackageTests/NewHaddock/HaddockOutput/HaddockOutputConfig/cabal.test.hs index cd57928ff81f51f1469a058f4986dcf1073700b8..ba3a957ef6039fe390aa7b277c79ae787ebf99a1 100644 --- a/cabal-testsuite/PackageTests/NewHaddock/HaddockOutput/HaddockOutputConfig/cabal.test.hs +++ b/cabal-testsuite/PackageTests/NewHaddock/HaddockOutput/HaddockOutputConfig/cabal.test.hs @@ -4,7 +4,7 @@ import Test.Cabal.Prelude -- Test that `cabal haddock --haddock-output-dir` works from the config file. main = cabalTest . withRepo "repo" $ do - testDir <- testSourceDir <$> getTestEnv + testDir <- testCurrentDir <$> getTestEnv let docsDir = testDir </> "docs" liftIO (removePathForcibly docsDir) r <- cabal' "haddock" ["A"] diff --git a/cabal-testsuite/PackageTests/NewSdist/Globbing/cabal.test.hs b/cabal-testsuite/PackageTests/NewSdist/Globbing/cabal.test.hs index 832177dc84f3ce1892c34171eba292dca5bedfa1..c6fe551841b6ceb36944ff80d443d9be58c030df 100644 --- a/cabal-testsuite/PackageTests/NewSdist/Globbing/cabal.test.hs +++ b/cabal-testsuite/PackageTests/NewSdist/Globbing/cabal.test.hs @@ -1,4 +1,4 @@ import Test.Cabal.Prelude -main = cabalTest $ withSourceCopy $ do +main = cabalTest $ do cabal "v2-sdist" ["a", "--list-only"] diff --git a/cabal-testsuite/PackageTests/NewSdist/ManyDataFiles/many-data-files.out b/cabal-testsuite/PackageTests/NewSdist/ManyDataFiles/many-data-files.out index 7303a453b6e13d3bdf15d32eeb392a9104056184..926e5a2560e54e2065f757eb4da83ff3d910d1b8 100644 --- a/cabal-testsuite/PackageTests/NewSdist/ManyDataFiles/many-data-files.out +++ b/cabal-testsuite/PackageTests/NewSdist/ManyDataFiles/many-data-files.out @@ -1,2 +1,2 @@ # cabal v2-sdist -Wrote tarball sdist to <ROOT>/many-data-files.dist/source/dist-newstyle/sdist/many-data-files-0.tar.gz +Wrote tarball sdist to <ROOT>/dist-newstyle/sdist/many-data-files-0.tar.gz diff --git a/cabal-testsuite/PackageTests/NewSdist/ManyDataFiles/many-data-files.test.hs b/cabal-testsuite/PackageTests/NewSdist/ManyDataFiles/many-data-files.test.hs index e414b19b09307c7fd5df70251ba60780c6b2fc83..36192da93ece3d92c0960ef98afeecf112e004ca 100644 --- a/cabal-testsuite/PackageTests/NewSdist/ManyDataFiles/many-data-files.test.hs +++ b/cabal-testsuite/PackageTests/NewSdist/ManyDataFiles/many-data-files.test.hs @@ -4,14 +4,14 @@ import Control.Applicative ((<$>)) import System.Directory ( createDirectoryIfMissing ) import qualified Data.ByteString.Char8 as BS -main = cabalTest . withSourceCopy $ do +main = cabalTest $ do limit <- getOpenFilesLimit cwd <- testCurrentDir <$> getTestEnv case limit of Just n -> do liftIO $ createDirectoryIfMissing False (cwd </> "data") - forM_ [1 .. n + 100] $ \i -> + forM_ [1 .. n + 100] $ \i -> liftIO $ BS.writeFile (cwd </> "data" </> ("data-file-" ++ show i) <.> "txt") (BS.pack "a data file\n") cabal "v2-sdist" ["many-data-files"] Nothing -> skip "no open file limit" diff --git a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/all-output-dir.out b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/all-output-dir.out index 005c24ef82291d077401f321bd1a935787b3994e..abcbfc25590c231e2fba5fa869e1f4baa156dbe6 100644 --- a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/all-output-dir.out +++ b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/all-output-dir.out @@ -1,3 +1,3 @@ # cabal v2-sdist -Wrote tarball sdist to <ROOT>/all-output-dir.dist/source/archives/a-0.1.tar.gz -Wrote tarball sdist to <ROOT>/all-output-dir.dist/source/archives/b-0.1.tar.gz +Wrote tarball sdist to <ROOT>/archives/a-0.1.tar.gz +Wrote tarball sdist to <ROOT>/archives/b-0.1.tar.gz diff --git a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/all-output-dir.test.hs b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/all-output-dir.test.hs index 97a48c568929c30d2ad813d3f428d1efc7da3ad5..5ebe61befbea03d41bb77a60b6c9e87d1dd4b79b 100644 --- a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/all-output-dir.test.hs +++ b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/all-output-dir.test.hs @@ -1,6 +1,6 @@ import Test.Cabal.Prelude import System.Directory -main = cabalTest $ withSourceCopy $ do +main = cabalTest $ do cwd <- fmap testCurrentDir getTestEnv liftIO $ createDirectoryIfMissing False $ cwd </> "archives" cabal "v2-sdist" ["all", "--output-dir", "archives"] diff --git a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/all-test-sute.test.hs b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/all-test-sute.test.hs index 92bfd9522f4e610c9f8ddc9427ce7e38fe4533cc..736e326e1dd085dba478fdfbb9fbfcb8e762f629 100644 --- a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/all-test-sute.test.hs +++ b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/all-test-sute.test.hs @@ -1,5 +1,5 @@ import Test.Cabal.Prelude -main = cabalTest $ withSourceCopy $ do +main = cabalTest $ do cwd <- fmap testCurrentDir getTestEnv fails $ cabal "v2-sdist" ["all:tests"] shouldNotExist $ cwd </> "dist-newstyle/sdist/a-0.1.tar.gz" diff --git a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/all.out b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/all.out index 0bcab0b2531bea1b38a4f461067eafb0c55db62b..e370f410fe4619069554d169b4a73678fea35e2e 100644 --- a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/all.out +++ b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/all.out @@ -1,3 +1,3 @@ # cabal v2-sdist -Wrote tarball sdist to <ROOT>/all.dist/source/dist-newstyle/sdist/a-0.1.tar.gz -Wrote tarball sdist to <ROOT>/all.dist/source/dist-newstyle/sdist/b-0.1.tar.gz +Wrote tarball sdist to <ROOT>/dist-newstyle/sdist/a-0.1.tar.gz +Wrote tarball sdist to <ROOT>/dist-newstyle/sdist/b-0.1.tar.gz diff --git a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/all.test.hs b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/all.test.hs index d5b8c4420d926f0057b3af1f4ad63184013514a9..4423095bb870ae3b9e920abafe998bc90da1988b 100644 --- a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/all.test.hs +++ b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/all.test.hs @@ -1,5 +1,5 @@ import Test.Cabal.Prelude -main = cabalTest $ withSourceCopy $ do +main = cabalTest $ do cwd <- fmap testCurrentDir getTestEnv cabal "v2-sdist" ["all"] shouldExist $ cwd </> "dist-newstyle/sdist/a-0.1.tar.gz" diff --git a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/list-sources-output-dir.out b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/list-sources-output-dir.out index c6e7a37818a939a289e89eca05f1ea9a6a84ecd4..64b8452177fdab34eb5dcbcd53ffb455ad01a625 100644 --- a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/list-sources-output-dir.out +++ b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/list-sources-output-dir.out @@ -1,3 +1,3 @@ # cabal v2-sdist -Wrote source list to <ROOT>/list-sources-output-dir.dist/source/lists/a-0.1.list -Wrote source list to <ROOT>/list-sources-output-dir.dist/source/lists/b-0.1.list +Wrote source list to <ROOT>/lists/a-0.1.list +Wrote source list to <ROOT>/lists/b-0.1.list diff --git a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/list-sources-output-dir.test.hs b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/list-sources-output-dir.test.hs index 3f119909e0f4e5b562bcf7516dafee44aabae785..55af8b872ccc96943940994c3532dd8ce911a48b 100644 --- a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/list-sources-output-dir.test.hs +++ b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/list-sources-output-dir.test.hs @@ -1,7 +1,7 @@ import Test.Cabal.Prelude import System.Directory import System.FilePath -main = cabalTest $ withSourceCopy $ do +main = cabalTest $ do cwd <- fmap testCurrentDir getTestEnv liftIO $ createDirectoryIfMissing False $ cwd </> "lists" cabal "v2-sdist" ["all", "--list-only", "--output-dir", "lists"] diff --git a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/multi-archive-to-stdout.test.hs b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/multi-archive-to-stdout.test.hs index fdc3db695b2091aecc832104d85d8e29f8fac2d1..c9d20e9e70faee0e83ff8152d396ad035fe66a24 100644 --- a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/multi-archive-to-stdout.test.hs +++ b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/multi-archive-to-stdout.test.hs @@ -1,5 +1,5 @@ import Test.Cabal.Prelude -main = cabalTest $ withSourceCopy $ do +main = cabalTest $ do cwd <- fmap testCurrentDir getTestEnv fails $ cabal "v2-sdist" ["a", "b", "--output-dir", "-"] shouldNotExist $ cwd </> "dist-newstyle/sdist/a-0.1.tar.gz" diff --git a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/multi-list-sources.test.hs b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/multi-list-sources.test.hs index 2686d03598025881bf25a8d6fee8c8341d0c3005..d8a0237f39935078ba60528bac6fb623552c153a 100644 --- a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/multi-list-sources.test.hs +++ b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/multi-list-sources.test.hs @@ -1,4 +1,4 @@ import Test.Cabal.Prelude import Data.List -main = cabalTest $ withSourceCopy $ +main = cabalTest $ cabal "v2-sdist" ["a", "b", "--list-only"] diff --git a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/multi-target.out b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/multi-target.out index 567f028b0320c00423817d87348f770287f5eb85..e370f410fe4619069554d169b4a73678fea35e2e 100644 --- a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/multi-target.out +++ b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/multi-target.out @@ -1,3 +1,3 @@ # cabal v2-sdist -Wrote tarball sdist to <ROOT>/multi-target.dist/source/dist-newstyle/sdist/a-0.1.tar.gz -Wrote tarball sdist to <ROOT>/multi-target.dist/source/dist-newstyle/sdist/b-0.1.tar.gz +Wrote tarball sdist to <ROOT>/dist-newstyle/sdist/a-0.1.tar.gz +Wrote tarball sdist to <ROOT>/dist-newstyle/sdist/b-0.1.tar.gz diff --git a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/multi-target.test.hs b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/multi-target.test.hs index 92b50dd5b521e35eae65d102550e62be38a72a80..517c93e64e7f3a2fb06e7922b7d613e608b2daed 100644 --- a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/multi-target.test.hs +++ b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/multi-target.test.hs @@ -1,5 +1,5 @@ import Test.Cabal.Prelude -main = cabalTest $ withSourceCopy $ do +main = cabalTest $ do cwd <- fmap testCurrentDir getTestEnv cabal "v2-sdist" ["a", "b"] shouldExist $ cwd </> "dist-newstyle/sdist/a-0.1.tar.gz" diff --git a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/target-remote-package.test.hs b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/target-remote-package.test.hs index 45639a2aa23bb0f8bcd161d20c2d920ea0535904..324781b1171fb87413e157874abc6b41e7b5ab87 100644 --- a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/target-remote-package.test.hs +++ b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/target-remote-package.test.hs @@ -1,5 +1,5 @@ import Test.Cabal.Prelude -main = cabalTest $ withSourceCopy $ do +main = cabalTest $ do cwd <- fmap testCurrentDir getTestEnv fails $ cabal "v2-sdist" ["a", "base"] shouldNotExist $ cwd </> "dist-newstyle/sdist/a-0.1.tar.gz" diff --git a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/valid-and-test-suite.test.hs b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/valid-and-test-suite.test.hs index 0e2c15193c52f54b0104257256c8b9c0d9df4eca..4950fde708a6a68b4f9c8f27aedddf1d2cbe5df4 100644 --- a/cabal-testsuite/PackageTests/NewSdist/MultiTarget/valid-and-test-suite.test.hs +++ b/cabal-testsuite/PackageTests/NewSdist/MultiTarget/valid-and-test-suite.test.hs @@ -1,5 +1,5 @@ import Test.Cabal.Prelude -main = cabalTest $ withSourceCopy $ do +main = cabalTest $ do cwd <- fmap testCurrentDir getTestEnv fails $ cabal "v2-sdist" ["a", "b", "a-tests"] shouldNotExist $ cwd </> "dist-newstyle/sdist/a-0.1.tar.gz" diff --git a/cabal-testsuite/PackageTests/Regression/T3294/setup.test.hs b/cabal-testsuite/PackageTests/Regression/T3294/setup.test.hs index 810a4202b3a31620c9c7d108d8c017f3a157b0ad..b3ebe0c147c773f7e41aa1314fe0365ab0ace912 100644 --- a/cabal-testsuite/PackageTests/Regression/T3294/setup.test.hs +++ b/cabal-testsuite/PackageTests/Regression/T3294/setup.test.hs @@ -3,7 +3,7 @@ import Control.Monad.IO.Class -- Test that executable recompilation works -- https://github.com/haskell/setup/issues/3294 main = setupAndCabalTest $ do - withSourceCopy . withDelay $ do + withDelay $ do writeSourceFile "Main.hs" "main = putStrLn \"aaa\"" setup "configure" [] setup "build" [] diff --git a/cabal-testsuite/PackageTests/Regression/T4202/cabal.test.hs b/cabal-testsuite/PackageTests/Regression/T4202/cabal.test.hs index f7943be335f85cbfdecf2d1392021ee7f6460b2a..7b2aac05b2767dc0a14c7edc6f7c021b34947e13 100644 --- a/cabal-testsuite/PackageTests/Regression/T4202/cabal.test.hs +++ b/cabal-testsuite/PackageTests/Regression/T4202/cabal.test.hs @@ -1,6 +1,5 @@ import Test.Cabal.Prelude -main = cabalTest $ - withSourceCopy . withDelay $ do +main = cabalTest $ withDelay $ do writeSourceFile ("p/P.hs") "module P where\np = \"AAA\"" cabal "v2-build" ["p","q"] delay diff --git a/cabal-testsuite/PackageTests/Regression/T4986/cabal.test.hs b/cabal-testsuite/PackageTests/Regression/T4986/cabal.test.hs index 8f7fe8fdfa1a7825f7f799179eba9fc19bdc8315..b77b433a65247d90615589d36ceffd4f81cc49f0 100644 --- a/cabal-testsuite/PackageTests/Regression/T4986/cabal.test.hs +++ b/cabal-testsuite/PackageTests/Regression/T4986/cabal.test.hs @@ -1,4 +1,3 @@ import Test.Cabal.Prelude main = cabalTest $ - withSourceCopy $ cabal "v2-configure" [] diff --git a/cabal-testsuite/PackageTests/Regression/T5318/sdist-list-sources.out b/cabal-testsuite/PackageTests/Regression/T5318/sdist-list-sources.out index 82b4544383a4eb2f7bb039334cbaeb047fedc012..faefc513fe86845281c21d8dc33ce8445e46149e 100644 --- a/cabal-testsuite/PackageTests/Regression/T5318/sdist-list-sources.out +++ b/cabal-testsuite/PackageTests/Regression/T5318/sdist-list-sources.out @@ -1,2 +1,2 @@ # cabal v2-sdist -Wrote source list to <TMPDIR>/empty-data-dir-0.list +Wrote source list to <ROOT>/empty-data-dir-0.list diff --git a/cabal-testsuite/PackageTests/Regression/T5386/cabal.test.hs b/cabal-testsuite/PackageTests/Regression/T5386/cabal.test.hs index 565a3ce347411cadae561033e560ba3be8529512..e1a111cd4f38eefdafe6d4f95eecacce396f777e 100644 --- a/cabal-testsuite/PackageTests/Regression/T5386/cabal.test.hs +++ b/cabal-testsuite/PackageTests/Regression/T5386/cabal.test.hs @@ -1,5 +1,5 @@ import Test.Cabal.Prelude -- See #4332, dep solving output is not deterministic -main = cabalTest . recordMode DoNotRecord $ withSourceCopyDir "9" $ +main = cabalTest . recordMode DoNotRecord $ -- Note: we bundle the configure script so no need to autoreconf while building cabal "v2-build" ["all"] diff --git a/cabal-testsuite/PackageTests/Regression/T5782Diamond/cabal.test.hs b/cabal-testsuite/PackageTests/Regression/T5782Diamond/cabal.test.hs index 410a0eba1f1a02cdb66923e241a1c39aa7253735..2ec30f1c876d940d84950ae5ddfea2e227452714 100644 --- a/cabal-testsuite/PackageTests/Regression/T5782Diamond/cabal.test.hs +++ b/cabal-testsuite/PackageTests/Regression/T5782Diamond/cabal.test.hs @@ -21,8 +21,7 @@ import Test.Cabal.Prelude main = withShorterPathForNewBuildStore $ \storeDir -> - cabalTest $ - withSourceCopy . withDelay $ do + cabalTest $ withDelay $ do writeSourceFile "issue5782/src/Module.hs" "module Module where\nf = \"AAA\"" recordMode DoNotRecord $ cabalG ["--store-dir=" ++ storeDir, "--installdir=" ++ storeDir, "--overwrite-policy=always"] "v2-install" ["issue5782"] diff --git a/cabal-testsuite/PackageTests/RequireExplicit/FlagInProject/cabal.test.hs b/cabal-testsuite/PackageTests/RequireExplicit/FlagInProject/cabal.test.hs index 4a75ff3bc44488479e250ec1d2f5ab9a06c90aed..463357cd1b8b527c83e2172c8e4b4b04219ed8f0 100644 --- a/cabal-testsuite/PackageTests/RequireExplicit/FlagInProject/cabal.test.hs +++ b/cabal-testsuite/PackageTests/RequireExplicit/FlagInProject/cabal.test.hs @@ -1,6 +1,6 @@ import Test.Cabal.Prelude -- See #4332, dep solving output is not deterministic -main = cabalTest . recordMode DoNotRecord $ withRepo "../repo" $ do +main = cabalTest . recordMode DoNotRecord $ withRepo "repo" $ do -- other-lib is a dependency, but it's not listed in cabal.project res <- fails $ cabal' "v2-build" ["all", "--dry-run"] assertOutputContains "not a user-provided goal" res diff --git a/cabal-testsuite/PackageTests/RequireExplicit/FlagInProject/repo b/cabal-testsuite/PackageTests/RequireExplicit/FlagInProject/repo new file mode 120000 index 0000000000000000000000000000000000000000..2dd2305a1322cb247b39b34e18001d7d044219bb --- /dev/null +++ b/cabal-testsuite/PackageTests/RequireExplicit/FlagInProject/repo @@ -0,0 +1 @@ +../repo/ \ No newline at end of file diff --git a/cabal-testsuite/PackageTests/RequireExplicit/MultiPkg/cabal.test.hs b/cabal-testsuite/PackageTests/RequireExplicit/MultiPkg/cabal.test.hs index 487a4a400a2468df57ef78ca24cb9af970ee4700..271bddebf0b2e6ac3d3f71fc043f20df4612e448 100644 --- a/cabal-testsuite/PackageTests/RequireExplicit/MultiPkg/cabal.test.hs +++ b/cabal-testsuite/PackageTests/RequireExplicit/MultiPkg/cabal.test.hs @@ -1,6 +1,6 @@ import Test.Cabal.Prelude -- See #4332, dep solving output is not deterministic -main = cabalTest . recordMode DoNotRecord $ withRepo "../repo" $ do +main = cabalTest . recordMode DoNotRecord $ withRepo "repo" $ do -- other-lib is a dependency of b, but it's not listed in cabal.project res <- fails $ cabal' "v2-build" ["all", "--dry-run", "--reject-unconstrained-dependencies", "all", "--constraint", "some-exe -any"] assertOutputContains "not a user-provided goal" res diff --git a/cabal-testsuite/PackageTests/RequireExplicit/MultiPkg/repo b/cabal-testsuite/PackageTests/RequireExplicit/MultiPkg/repo new file mode 120000 index 0000000000000000000000000000000000000000..2dd2305a1322cb247b39b34e18001d7d044219bb --- /dev/null +++ b/cabal-testsuite/PackageTests/RequireExplicit/MultiPkg/repo @@ -0,0 +1 @@ +../repo/ \ No newline at end of file diff --git a/cabal-testsuite/PackageTests/SDist/ListSources/list-sources.out b/cabal-testsuite/PackageTests/SDist/ListSources/list-sources.out index c7b1ba4eaa2f6b195b7991f4491c4a266eb9f9e6..6f929e541fc6f31ade1304f3b0640d2a5080ec6c 100644 --- a/cabal-testsuite/PackageTests/SDist/ListSources/list-sources.out +++ b/cabal-testsuite/PackageTests/SDist/ListSources/list-sources.out @@ -1,2 +1,2 @@ # Setup sdist -List of package sources written to file '<TMPDIR>/sources' +List of package sources written to file '<ROOT>/sources' diff --git a/cabal-testsuite/PackageTests/SDist/T5195and5349/cabal.out b/cabal-testsuite/PackageTests/SDist/T5195and5349/cabal.out index 22e981ee6c1fa90cbb0f7e176eee483dd453fe75..f42c4e9817722298e1b833a7671d5d65e91a987a 100644 --- a/cabal-testsuite/PackageTests/SDist/T5195and5349/cabal.out +++ b/cabal-testsuite/PackageTests/SDist/T5195and5349/cabal.out @@ -2,4 +2,4 @@ Warning: Ignoring directory '././actually-a-directory' listed in a Cabal package field which should only include files (not directories). Warning: Ignoring directory './actually-a-directory' listed in a Cabal package field which should only include files (not directories). Warning: Ignoring directory './actually-a-directory' listed in a Cabal package field which should only include files (not directories). -Wrote source list to <TMPDIR>/t5195and5349-0.list +Wrote source list to <ROOT>/t5195and5349-0.list diff --git a/cabal-testsuite/PackageTests/SDist/T7028/cabal.out b/cabal-testsuite/PackageTests/SDist/T7028/cabal.out index 55fc123d51d8d32e251259d068ddb4eb3a09c07b..222d3c33c8bba352febeb97a794a92a740a226d8 100644 --- a/cabal-testsuite/PackageTests/SDist/T7028/cabal.out +++ b/cabal-testsuite/PackageTests/SDist/T7028/cabal.out @@ -1,2 +1,2 @@ # cabal v2-sdist -Wrote source list to <TMPDIR>/t7028-0.list +Wrote source list to <ROOT>/t7028-0.list diff --git a/cabal-testsuite/PackageTests/SDist/T7124/cabal-list.out b/cabal-testsuite/PackageTests/SDist/T7124/cabal-list.out index 8ebea21b6f42788ce254ec7513c1f6a2c2e6af20..cb65c326a568d3e2e9b84b8624b09d1debda5412 100644 --- a/cabal-testsuite/PackageTests/SDist/T7124/cabal-list.out +++ b/cabal-testsuite/PackageTests/SDist/T7124/cabal-list.out @@ -1,4 +1,4 @@ # cabal v2-sdist -Wrote source list to <TMPDIR>/pkg-a-0.list +Wrote source list to <ROOT>/pkg-a-0.list Error: [Cabal-6661] -filepath wildcard './data.txt' does not match any files. \ No newline at end of file +filepath wildcard './data.txt' does not match any files. diff --git a/cabal-testsuite/PackageTests/SDist/T7124/cabal.out b/cabal-testsuite/PackageTests/SDist/T7124/cabal.out index f212d6951c119356048649db7e333b1697456714..5dbaee755bca3159580165d3ce5c708c96f44d39 100644 --- a/cabal-testsuite/PackageTests/SDist/T7124/cabal.out +++ b/cabal-testsuite/PackageTests/SDist/T7124/cabal.out @@ -1,4 +1,4 @@ # cabal v2-sdist -Wrote tarball sdist to <TMPDIR>/pkg-a-0.tar.gz +Wrote tarball sdist to <ROOT>/pkg-a-0.tar.gz Error: [Cabal-6661] -filepath wildcard './data.txt' does not match any files. \ No newline at end of file +filepath wildcard './data.txt' does not match any files. diff --git a/cabal-testsuite/PackageTests/SDist/T7698/cabal.out b/cabal-testsuite/PackageTests/SDist/T7698/cabal.out index f04864ea8717cc436b79113fba7d0c42336e3708..99370eb5dd678ee910cd44184467e82f17971d43 100644 --- a/cabal-testsuite/PackageTests/SDist/T7698/cabal.out +++ b/cabal-testsuite/PackageTests/SDist/T7698/cabal.out @@ -1,2 +1,2 @@ # cabal v2-sdist -Wrote source list to <TMPDIR>/t7698-0.list +Wrote source list to <ROOT>/t7698-0.list diff --git a/cabal-testsuite/PackageTests/TestSuiteTests/ExeV10/setup-no-tix.cabal.out b/cabal-testsuite/PackageTests/TestSuiteTests/ExeV10/setup-no-tix.cabal.out index 6432eca3a1408d54bba3a604ccf6228920c36154..1a0105f8cd7a1767ee7a5a8fd82e2250e9d71aba 100644 --- a/cabal-testsuite/PackageTests/TestSuiteTests/ExeV10/setup-no-tix.cabal.out +++ b/cabal-testsuite/PackageTests/TestSuiteTests/ExeV10/setup-no-tix.cabal.out @@ -11,5 +11,5 @@ Building test suite 'test-Short' for my-0.1... Running 1 test suites... Test suite test-Short: RUNNING... Test suite test-Short: PASS -Test suite logged to: ../work/dist/test/my-0.1-test-Short.log +Test suite logged to: setup-no-tix.cabal.dist/work/dist/test/my-0.1-test-Short.log 1 of 1 test suites (1 of 1 test cases) passed. diff --git a/cabal-testsuite/PackageTests/TestSuiteTests/ExeV10/setup-no-tix.out b/cabal-testsuite/PackageTests/TestSuiteTests/ExeV10/setup-no-tix.out index 6432eca3a1408d54bba3a604ccf6228920c36154..6fd1e91bd004c41f61515baed7516ade9757bf47 100644 --- a/cabal-testsuite/PackageTests/TestSuiteTests/ExeV10/setup-no-tix.out +++ b/cabal-testsuite/PackageTests/TestSuiteTests/ExeV10/setup-no-tix.out @@ -11,5 +11,5 @@ Building test suite 'test-Short' for my-0.1... Running 1 test suites... Test suite test-Short: RUNNING... Test suite test-Short: PASS -Test suite logged to: ../work/dist/test/my-0.1-test-Short.log +Test suite logged to: setup-no-tix.dist/work/dist/test/my-0.1-test-Short.log 1 of 1 test suites (1 of 1 test cases) passed. diff --git a/cabal-testsuite/PackageTests/TestSuiteTests/ExeV10/setup-no-tix.test.hs b/cabal-testsuite/PackageTests/TestSuiteTests/ExeV10/setup-no-tix.test.hs index 073af976d5623a3d4a49a1248c7f1da3ea62b8ff..12db5895dd1f8972e5ab55392ff3c4ca754df6aa 100644 --- a/cabal-testsuite/PackageTests/TestSuiteTests/ExeV10/setup-no-tix.test.hs +++ b/cabal-testsuite/PackageTests/TestSuiteTests/ExeV10/setup-no-tix.test.hs @@ -12,9 +12,6 @@ import Distribution.Simple.Hpc -- at all.) -- main = setupAndCabalTest $ do - -- Source copy is necessary as GHC defaults to dumping tix - -- file in the CWD, and we do NOT clean it up after the fact. - withSourceCopy $ do dist_dir <- fmap testDistDir getTestEnv setup_build [ "--enable-tests" diff --git a/cabal-testsuite/README.md b/cabal-testsuite/README.md index b5036803bcef5bb51044299644c315e3909be7ad..f217617e9327fa9cc770afc7c9a391bd4cebe7b5 100644 --- a/cabal-testsuite/README.md +++ b/cabal-testsuite/README.md @@ -25,6 +25,9 @@ There are a few useful flags: the autodetection doesn't work correctly (which may be the case for old versions of GHC.) +* `--keep-tmp-files` can be used to keep the temporary directories that tests + are run in. + ### How to run the doctests You need to install the `doctest` tool. Make sure it's compiled with your current @@ -55,6 +58,16 @@ see the full contents of various commits which added a test for various functionality. See if you can find an existing test that is similar to what you want to test. +Tests are all run in temporary system directories. At the start of a test +all the files which are in the same folder as the test script are copied into +a system temporary directory and then the rest of the script operates in this +directory. + +**NOTE:** only files which are known to git are copied, so you have to +`git add` any files which are part of a test before running the test. +You can use the `--keep-tmp-files` flag to keep the temporary directories in +order to inspect the result of running a test. + Otherwise, here is a walkthrough: 1. Create the package(s) that you need for your test in a @@ -128,11 +141,6 @@ test output?** Only "marked" output is picked up by Cabal; currently, only `notice`, `warn` and `die` produce marked output. Use those combinators for your output. -**How do I safely let my test modify version-controlled source files?** -Use `withSourceCopy`. Note that you MUST `git add` -all files which are relevant to the test; otherwise they will not be -available when running the test. - **How can I add a dependency on a package from Hackage in a test?** By default, the test suite is completely independent of the contents of Hackage, to ensure that it keeps working across all GHC versions. @@ -182,14 +190,8 @@ string output test, if that is how your test is "failing." Hermetic tests -------------- -By default, we run tests directly on the source code that is checked into the -source code repository. However, some tests require programmatically -modifying source files, or interact with Cabal commands which are -not hermetic (e.g., `cabal freeze`). In this case, cabal-testsuite -supports opting into a hermetic test, where we first make copy of all -the relevant source code before starting the test. You can opt into -this mode using the `withSourceCopy` combinator (search for examples!) -This mode is subject to the following limitations: +Tests are run in a fresh temporary system directory. This attempts to isolate the +tests from anything specific to do with your directory structure. In particular * You must be running the test inside a valid Git checkout of the test suite (`withSourceCopy` uses Git to determine which files should be copied.) @@ -197,9 +199,6 @@ This mode is subject to the following limitations: * You must `git add` all files which are relevant to the test, otherwise they will not be copied. -* The source copy is still made at a well-known location, so running - a test is still not reentrant. (See also Known Limitations.) - Design notes ------------ @@ -344,11 +343,3 @@ Here are some things we do not currently plan on supporting: of our tests need substantial setup; for example, tests that have to setup a package repository. In this case, because there already is a setup necessary, we might consider making things easier here.) - -Known limitations ------------------ - -* Tests are NOT reentrant: test build products are always built into - the same location, and if you run the same test at the same time, - you will clobber each other. This is convenient for debugging and - doesn't seem to be a problem in practice. diff --git a/cabal-testsuite/src/Test/Cabal/Monad.hs b/cabal-testsuite/src/Test/Cabal/Monad.hs index 36621773309e8bfc3ac06733b91cf75ad1a6d966..14e9313506432e1119c44aafd9bf992cdadbbd8b 100644 --- a/cabal-testsuite/src/Test/Cabal/Monad.hs +++ b/cabal-testsuite/src/Test/Cabal/Monad.hs @@ -20,6 +20,9 @@ module Test.Cabal.Monad ( cabalProgram, diffProgram, python3Program, + requireSuccess, + initWorkDir, + recordLog, -- * The test environment TestEnv(..), getTestEnv, @@ -91,15 +94,20 @@ import System.Exit import System.FilePath import System.IO import System.IO.Error (isDoesNotExistError) -import System.IO.Temp (withSystemTempDirectory) +import Distribution.Simple.Utils hiding (info) import System.Process hiding (env) import Options.Applicative +import Test.Cabal.Run +import qualified Data.ByteString.Char8 as C +import Data.List +import GHC.Stack data CommonArgs = CommonArgs { argCabalInstallPath :: Maybe FilePath, argGhcPath :: Maybe FilePath, argHackageRepoToolPath :: Maybe FilePath, argHaddockPath :: Maybe FilePath, + argKeepTmpFiles :: Bool, argAccept :: Bool, argSkipSetupTests :: Bool } @@ -127,6 +135,10 @@ commonArgParser = CommonArgs <> long "with-haddock" <> metavar "PATH" )) + <*> switch + ( long "keep-tmp-files" + <> help "Keep temporary files" + ) <*> switch ( long "accept" <> help "Accept output" @@ -140,6 +152,7 @@ renderCommonArgs args = maybe [] (\x -> ["--with-haddock", x]) (argHaddockPath args) ++ maybe [] (\x -> ["--with-hackage-repo-tool", x]) (argHackageRepoToolPath args) ++ (if argAccept args then ["--accept"] else []) ++ + (if argKeepTmpFiles args then ["--keep-tmp-files"] else []) ++ (if argSkipSetupTests args then ["--skip-setup-tests"] else []) data TestArgs = TestArgs { @@ -178,6 +191,7 @@ unexpectedSuccess = liftIO $ do putStrLn "UNEXPECTED OK" E.throwIO TestCodeUnexpectedOk + trySkip :: IO a -> IO (Either String a) trySkip m = fmap Right m `E.catch` \e -> case e of TestCodeSkip msg -> return (Left msg) @@ -228,8 +242,12 @@ python3Program = simpleProgram "python3" -- | Run a test in the test monad according to program's arguments. runTestM :: String -> TestM a -> IO a -runTestM mode m = withSystemTempDirectory "cabal-testsuite" $ \tmp_dir -> do - args <- execParser (info testArgParser Data.Monoid.mempty) +runTestM mode m = + liftIO $ getTemporaryDirectory >>= \systemTmpDir -> + execParser (info testArgParser Data.Monoid.mempty) >>= \args -> + withTempDirectoryEx verbosity (defaultTempFileOptions { optKeepTempFiles = argKeepTmpFiles (testCommonArgs args) }) + systemTmpDir + "cabal-testsuite" $ \tmp_dir -> do let dist_dir = testArgDistDir args (script_dir0, script_filename) = splitFileName (testArgScriptPath args) @@ -319,16 +337,14 @@ runTestM mode m = withSystemTempDirectory "cabal-testsuite" $ \tmp_dir -> do testRelativeCurrentDir = ".", testHavePackageDb = False, testHaveRepo = False, - testHaveSourceCopy = False, testCabalInstallAsSetup = False, - testCabalProjectFile = "cabal.project", + testCabalProjectFile = Nothing, testPlan = Nothing, testRecordDefaultMode = DoNotRecord, - testRecordUserMode = Nothing, - testSourceCopyRelativeDir = "source" + testRecordUserMode = Nothing } let go = do cleanup - r <- m + r <- withSourceCopy m check_expect (argAccept (testCommonArgs args)) return r runReaderT go env @@ -373,6 +389,107 @@ readFileOrEmpty f = readFile f `E.catch` \e -> then return "" else E.throwIO e +-- | Run an IO action, and suppress a "does not exist" error. +onlyIfExists :: MonadIO m => IO () -> m () +onlyIfExists m = + liftIO $ E.catch m $ \(e :: IOError) -> + unless (isDoesNotExistError e) $ E.throwIO e + +-- | Make a hermetic copy of the test directory. +-- +-- This requires the test repository to be a Git checkout, because +-- we use the Git metadata to figure out what files to copy into the +-- hermetic copy. +-- +-- Also see 'withSourceCopyDir'. +withSourceCopy :: TestM a -> TestM a +withSourceCopy m = do + env <- getTestEnv + initWorkDir + let curdir = testSourceDir env + dest = testSourceCopyDir env + fs <- getSourceFiles + when (null fs) + (error (unlines [ "withSourceCopy: No files to copy from " ++ curdir + , "You need to \"git add\" any files before they are copied by the testsuite."])) + forM_ fs $ \f -> do + unless (isTestFile f) $ liftIO $ do + putStrLn ("Copying " ++ (curdir </> f) ++ " to " ++ (dest </> f)) + createDirectoryIfMissing True (takeDirectory (dest </> f)) + d <- liftIO $ doesDirectoryExist (curdir </> f) + if d + then + copyDirectoryRecursive normal (curdir </> f) (dest </> f) + else + copyFile (curdir </> f) (dest </> f) + m + + +-- NB: Keep this synchronized with partitionTests +isTestFile :: FilePath -> Bool +isTestFile f = + case takeExtensions f of + ".test.hs" -> True + ".multitest.hs" -> True + _ -> False + + +initWorkDir :: TestM () +initWorkDir = do + env <- getTestEnv + liftIO $ createDirectoryIfMissing True (testWorkDir env) + + + +getSourceFiles :: TestM [FilePath] +getSourceFiles = do + env <- getTestEnv + configured_prog <- requireProgramM gitProgram + r <- liftIO $ run (testVerbosity env) + (Just (testSourceDir env)) + (testEnvironment env) + (programPath configured_prog) + ["ls-files", "--cached", "--modified"] + Nothing + recordLog r + _ <- requireSuccess r + return (lines $ resultOutput r) + +recordLog :: Result -> TestM () +recordLog res = do + env <- getTestEnv + let mode = testRecordMode env + initWorkDir + liftIO $ C.appendFile (testWorkDir env </> "test.log") + (C.pack $ "+ " ++ resultCommand res ++ "\n" + ++ resultOutput res ++ "\n\n") + liftIO . C.appendFile (testActualFile env) . C.pack $ + case mode of + RecordAll -> unlines (lines (resultOutput res)) + RecordMarked -> getMarkedOutput (resultOutput res) + DoNotRecord -> "" + +------------------------------------------------------------------------ +-- * Subprocess run results + +requireSuccess :: Result -> TestM Result +requireSuccess r@Result { resultCommand = cmd + , resultExitCode = exitCode + , resultOutput = output } = withFrozenCallStack $ do + env <- getTestEnv + when (exitCode /= ExitSuccess && not (testShouldFail env)) $ + assertFailure $ "Command " ++ cmd ++ " failed.\n" ++ + "Output:\n" ++ output ++ "\n" + when (exitCode == ExitSuccess && testShouldFail env) $ + assertFailure $ "Command " ++ cmd ++ " succeeded.\n" ++ + "Output:\n" ++ output ++ "\n" + return r + +assertFailure :: String -> m () +assertFailure msg = withFrozenCallStack $ error msg + + + -- | Runs 'diff' with some arguments on two files, outputting the -- diff to stderr, and returning true if the two files differ diff :: [String] -> FilePath -> FilePath -> TestM Bool @@ -402,11 +519,15 @@ mkNormalizerEnv = do ["list", "--global", "--simple-output"] "" tmpDir <- liftIO $ getTemporaryDirectory + canonicalizedTestTmpDir <- liftIO $ canonicalizePath (testTmpDir env) + return NormalizerEnv { normalizerRoot = addTrailingPathSeparator (testSourceDir env), normalizerTmpDir = addTrailingPathSeparator (testTmpDir env), + normalizerCanonicalTmpDir + = addTrailingPathSeparator canonicalizedTestTmpDir, normalizerGblTmpDir = addTrailingPathSeparator tmpDir, normalizerGhcVersion @@ -445,11 +566,21 @@ isAvailableProgram program = do Just _ -> return True Nothing -> return False --- | Run an IO action, and suppress a "does not exist" error. -onlyIfExists :: MonadIO m => IO () -> m () -onlyIfExists m = - liftIO $ E.catch m $ \(e :: IOError) -> - unless (isDoesNotExistError e) $ E.throwIO e + +getMarkedOutput :: String -> String -- trailing newline +getMarkedOutput out = unlines (go (lines out) False) + where + go [] _ = [] + go (x:xs) True + | "-----END CABAL OUTPUT-----" `isPrefixOf` x + = go xs False + | otherwise = x : go xs True + go (x:xs) False + -- NB: Windows has extra goo at the end + | "-----BEGIN CABAL OUTPUT-----" `isPrefixOf` x + = go xs True + | otherwise = go xs False + data TestEnv = TestEnv -- UNCHANGING: @@ -503,12 +634,10 @@ data TestEnv = TestEnv , testHavePackageDb :: Bool -- | Says if we've setup a repository , testHaveRepo :: Bool - -- | Says if we've copied the source to a hermetic directory - , testHaveSourceCopy :: Bool -- | Says if we're testing cabal-install as setup , testCabalInstallAsSetup :: Bool -- | Says what cabal.project file to use (probed) - , testCabalProjectFile :: FilePath + , testCabalProjectFile :: Maybe FilePath -- | Cached record of the plan metadata from a new-build -- invocation; controlled by 'withPlan'. , testPlan :: Maybe Plan @@ -516,9 +645,6 @@ data TestEnv = TestEnv , testRecordDefaultMode :: RecordMode -- | User explicitly set record mode. Not implemented ATM. , testRecordUserMode :: Maybe RecordMode - -- | Name of the subdirectory we copied the test's sources to, - -- relative to 'testSourceDir' - , testSourceCopyRelativeDir :: FilePath } deriving Show @@ -538,10 +664,7 @@ getTestEnv = ask -- where the Cabal file lives. This is what you want the CWD of cabal -- calls to be. testCurrentDir :: TestEnv -> FilePath -testCurrentDir env = - (if testHaveSourceCopy env - then testSourceCopyDir env - else testSourceDir env) </> testRelativeCurrentDir env +testCurrentDir env = testSourceCopyDir env </> testRelativeCurrentDir env testName :: TestEnv -> String testName env = testSubName env <.> testMode env @@ -550,8 +673,7 @@ testName env = testSubName env <.> testMode env -- files for ALL tests associated with a test (respecting -- subtests.) To clean, you ONLY need to delete this directory. testWorkDir :: TestEnv -> FilePath -testWorkDir env = - testSourceDir env </> (testName env <.> "dist") +testWorkDir env = testTmpDir env </> (testName env <.> "dist") -- | The absolute prefix where installs go. testPrefixDir :: TestEnv -> FilePath @@ -592,7 +714,7 @@ testKeysDir env = testWorkDir env </> "keys" -- | If 'withSourceCopy' is used, where the source files go. testSourceCopyDir :: TestEnv -> FilePath -testSourceCopyDir env = testWorkDir env </> testSourceCopyRelativeDir env +testSourceCopyDir env = testTmpDir env -- | The user cabal directory testCabalDir :: TestEnv -> FilePath diff --git a/cabal-testsuite/src/Test/Cabal/OutputNormalizer.hs b/cabal-testsuite/src/Test/Cabal/OutputNormalizer.hs index 6c58b8872b284d2adb670759c8cba87f6208a74e..a0b7d3ac669abfc08d2d995e2ac5c0ea3ba937c5 100644 --- a/cabal-testsuite/src/Test/Cabal/OutputNormalizer.hs +++ b/cabal-testsuite/src/Test/Cabal/OutputNormalizer.hs @@ -36,8 +36,8 @@ normalizeOutput nenv = -- string search-replace. Make sure we do this before backslash -- normalization! . resub (posixRegexEscape (normalizerGblTmpDir nenv) ++ "[a-z0-9\\.-]+") "<GBLTMPDIR>" -- note, after TMPDIR - . resub (posixRegexEscape (normalizerRoot nenv)) "<ROOT>/" - . resub (posixRegexEscape (normalizerTmpDir nenv)) "<TMPDIR>/" + . resub (posixRegexEscape (normalizerTmpDir nenv)) "<ROOT>/" + . resub (posixRegexEscape (normalizerCanonicalTmpDir nenv)) "<ROOT>/" -- before normalizerTmpDir . appEndo (F.fold (map (Endo . packageIdRegex) (normalizerKnownPackages nenv))) -- Look for 0.1/installed-0d6uzW7Ubh1Fb4TB5oeQ3G -- These installed packages will vary depending on GHC version @@ -99,6 +99,9 @@ normalizeOutput nenv = data NormalizerEnv = NormalizerEnv { normalizerRoot :: FilePath , normalizerTmpDir :: FilePath + , normalizerCanonicalTmpDir :: FilePath + -- ^ May differ from 'normalizerTmpDir', especially e.g. on macos, where + -- `/var` is a symlink for `/private/var`. , normalizerGblTmpDir :: FilePath , normalizerGhcVersion :: Version , normalizerKnownPackages :: [PackageId] diff --git a/cabal-testsuite/src/Test/Cabal/Prelude.hs b/cabal-testsuite/src/Test/Cabal/Prelude.hs index 2c54deaa2a242b98b127fccb5b8560c4f1dbb404..22f109f16af67420eff22b7bf50bdd6338231ab1 100644 --- a/cabal-testsuite/src/Test/Cabal/Prelude.hs +++ b/cabal-testsuite/src/Test/Cabal/Prelude.hs @@ -29,10 +29,10 @@ import Distribution.Simple.Program.Types import Distribution.Simple.Program.Db import Distribution.Simple.Program import Distribution.System (OS(Windows,Linux,OSX), Arch(JavaScript), buildOS, buildArch) -import Distribution.Simple.Utils - ( withFileContents, tryFindPackageDesc ) import Distribution.Simple.Configure ( getPersistBuildConfig ) +import Distribution.Simple.Utils + ( withFileContents, tryFindPackageDesc ) import Distribution.Version import Distribution.Package import Distribution.Parsec (eitherParsec) @@ -289,9 +289,6 @@ cabalG' global_args cmd args = cabalGArgs global_args cmd args Nothing cabalGArgs :: [String] -> String -> [String] -> Maybe String -> TestM Result cabalGArgs global_args cmd args input = do env <- getTestEnv - -- Freeze writes out cabal.config to source directory, this is not - -- overwritable - when (cmd == "v1-freeze") requireHasSourceCopy let extra_args | cmd `elem` [ "v1-update" @@ -311,16 +308,16 @@ cabalGArgs global_args cmd args input = do -- new-build commands are affected by testCabalProjectFile | cmd == "v2-sdist" - = [ "--project-file", testCabalProjectFile env ] + = [ "--project-file=" ++ fp | Just fp <- [testCabalProjectFile env] ] | cmd == "v2-clean" - = [ "--builddir", testDistDir env - , "--project-file", testCabalProjectFile env ] + = [ "--builddir", testDistDir env ] + ++ [ "--project-file=" ++ fp | Just fp <- [testCabalProjectFile env] ] | "v2-" `isPrefixOf` cmd = [ "--builddir", testDistDir env - , "--project-file", testCabalProjectFile env , "-j1" ] + ++ [ "--project-file=" ++ fp | Just fp <- [testCabalProjectFile env] ] | otherwise = [ "--builddir", testDistDir env ] ++ @@ -343,7 +340,7 @@ cabal_raw' cabal_args input = runProgramM cabalProgram cabal_args input withProjectFile :: FilePath -> TestM a -> TestM a withProjectFile fp m = - withReaderT (\env -> env { testCabalProjectFile = fp }) m + withReaderT (\env -> env { testCabalProjectFile = Just fp }) m -- | Assuming we've successfully configured a new-build project, -- read out the plan metadata so that we can use it to do other @@ -667,26 +664,6 @@ withRemoteRepo repoDir m = do runReaderT m (env { testHaveRepo = True })) ------------------------------------------------------------------------- --- * Subprocess run results - -requireSuccess :: Result -> TestM Result -requireSuccess r@Result { resultCommand = cmd - , resultExitCode = exitCode - , resultOutput = output } = withFrozenCallStack $ do - env <- getTestEnv - when (exitCode /= ExitSuccess && not (testShouldFail env)) $ - assertFailure $ "Command " ++ cmd ++ " failed.\n" ++ - "Output:\n" ++ output ++ "\n" - when (exitCode == ExitSuccess && testShouldFail env) $ - assertFailure $ "Command " ++ cmd ++ " succeeded.\n" ++ - "Output:\n" ++ output ++ "\n" - return r - -initWorkDir :: TestM () -initWorkDir = do - env <- getTestEnv - liftIO $ createDirectoryIfMissing True (testWorkDir env) -- | Record a header to help identify the output to the expect -- log. Unlike the 'recordLog', we don't record all arguments; @@ -698,46 +675,21 @@ recordHeader args = do env <- getTestEnv let mode = testRecordMode env str_header = "# " ++ intercalate " " args ++ "\n" - header = C.pack str_header + rec_header = C.pack str_header case mode of DoNotRecord -> return () _ -> do initWorkDir liftIO $ putStr str_header - liftIO $ C.appendFile (testWorkDir env </> "test.log") header - liftIO $ C.appendFile (testActualFile env) header + liftIO $ C.appendFile (testWorkDir env </> "test.log") rec_header + liftIO $ C.appendFile (testActualFile env) rec_header -recordLog :: Result -> TestM () -recordLog res = do - env <- getTestEnv - let mode = testRecordMode env - initWorkDir - liftIO $ C.appendFile (testWorkDir env </> "test.log") - (C.pack $ "+ " ++ resultCommand res ++ "\n" - ++ resultOutput res ++ "\n\n") - liftIO . C.appendFile (testActualFile env) . C.pack $ - case mode of - RecordAll -> unlines (lines (resultOutput res)) - RecordMarked -> getMarkedOutput (resultOutput res) - DoNotRecord -> "" - -getMarkedOutput :: String -> String -- trailing newline -getMarkedOutput out = unlines (go (lines out) False) - where - go [] _ = [] - go (x:xs) True - | "-----END CABAL OUTPUT-----" `isPrefixOf` x - = go xs False - | otherwise = x : go xs True - go (x:xs) False - -- NB: Windows has extra goo at the end - | "-----BEGIN CABAL OUTPUT-----" `isPrefixOf` x - = go xs True - | otherwise = go xs False ------------------------------------------------------------------------ -- * Test helpers +------------------------------------------------------------------------ +-- * Subprocess run results assertFailure :: WithCallStack (String -> m ()) assertFailure msg = withFrozenCallStack $ error msg @@ -994,8 +946,7 @@ expectBrokenIf True ticket m = expectBroken ticket m expectBrokenUnless :: Bool -> Int -> TestM a -> TestM () expectBrokenUnless b = expectBrokenIf (not b) ------------------------------------------------------------------------- --- * Miscellaneous +-- * Programs git :: String -> [String] -> TestM () git cmd args = void $ git' cmd args @@ -1029,41 +980,6 @@ python3' args = do recordHeader ["python3"] runProgramM python3Program args Nothing --- | If a test needs to modify or write out source files, it's --- necessary to make a hermetic copy of the source files to operate --- on. This function arranges for this to be done. --- --- This requires the test repository to be a Git checkout, because --- we use the Git metadata to figure out what files to copy into the --- hermetic copy. --- --- Also see 'withSourceCopyDir'. -withSourceCopy :: TestM a -> TestM a -withSourceCopy m = do - env <- getTestEnv - let cwd = testCurrentDir env - dest = testSourceCopyDir env - r <- git' "ls-files" ["--cached", "--modified"] - forM_ (lines (resultOutput r)) $ \f -> do - unless (isTestFile f) $ do - liftIO $ createDirectoryIfMissing True (takeDirectory (dest </> f)) - liftIO $ copyFile (cwd </> f) (dest </> f) - withReaderT (\nenv -> nenv { testHaveSourceCopy = True }) m - --- | If a test needs to modify or write out source files, it's --- necessary to make a hermetic copy of the source files to operate --- on. This function arranges for this to be done in a subdirectory --- with a given name, so that tests that are sensitive to the path --- that they're running in (e.g., autoconf tests) can run. --- --- This requires the test repository to be a Git checkout, because --- we use the Git metadata to figure out what files to copy into the --- hermetic copy. --- --- Also see 'withSourceCopy'. -withSourceCopyDir :: FilePath -> TestM a -> TestM a -withSourceCopyDir dir = - withReaderT (\nenv -> nenv { testSourceCopyRelativeDir = dir }) . withSourceCopy -- | Look up the 'InstalledPackageId' of a package name. getIPID :: String -> TestM String @@ -1125,30 +1041,14 @@ withSymlink oldpath newpath0 act = do writeSourceFile :: FilePath -> String -> TestM () writeSourceFile fp s = do - requireHasSourceCopy cwd <- fmap testCurrentDir getTestEnv liftIO $ writeFile (cwd </> fp) s copySourceFileTo :: FilePath -> FilePath -> TestM () copySourceFileTo src dest = do - requireHasSourceCopy cwd <- fmap testCurrentDir getTestEnv liftIO $ copyFile (cwd </> src) (cwd </> dest) -requireHasSourceCopy :: TestM () -requireHasSourceCopy = do - env <- getTestEnv - unless (testHaveSourceCopy env) $ do - error "This operation requires a source copy; use withSourceCopy and 'git add' all test files" - --- NB: Keep this synchronized with partitionTests -isTestFile :: FilePath -> Bool -isTestFile f = - case takeExtensions f of - ".test.hs" -> True - ".multitest.hs" -> True - _ -> False - -- | Work around issue #4515 (store paths exceeding the Windows path length -- limit) by creating a temporary directory for the new-build store. This -- function creates a directory immediately under the current drive on Windows.