Skip to content
Snippets Groups Projects
Commit 420ccd80 authored by Artem Pelenitsyn's avatar Artem Pelenitsyn
Browse files

After moving GHC 9.4.2->9.4.4 some broken Windows tests work

Partially revert 78cbeba1.
parent 2e8a1e1d
No related branches found
No related tags found
No related merge requests found
Showing
with 0 additions and 42 deletions
import Test.Cabal.Prelude
-- Test internal custom preprocessor
main = cabalTest $ do
isWin <- isWindows
ghc94 <- isGhcVersion "== 9.4.*"
expectBrokenIf (isWin && ghc94) 8451 $ do
skipUnless "no Cabal for GHC" =<< hasCabalForGhc
-- old Cabal's ./Setup.hs output is difficult to normalise
......
import Test.Cabal.Prelude
main = cabalTest $ do
isWin <- isWindows
ghc94 <- isGhcVersion "== 9.4.*"
expectBrokenIf (isWin && ghc94) 8451 $ do
cabal "v2-build" ["foreign-opts-c-exe"]
withPlan $ runPlanExe "foreign-opts-c" "foreign-opts-c-exe" []
import Test.Cabal.Prelude
main = cabalTest $ do
isWin <- isWindows
ghc94 <- isGhcVersion "== 9.4.*"
expectBrokenIf (isWin && ghc94) 8451 $ do
cabal "v2-build" ["foreign-opts-cxx-exe"]
withPlan $ runPlanExe "foreign-opts-cxx" "foreign-opts-cxx-exe" []
import Test.Cabal.Prelude
main = cabalTest $ do
isWin <- isWindows
ghc94 <- isGhcVersion "== 9.4.*"
expectBrokenIf (isWin && ghc94) 8451 $ do
cabal "v2-bench"
[ "--benchmark-option=1"
, "--benchmark-options=\"2 3\""
......
import Test.Cabal.Prelude
main = cabalTest . void $ do
isWin <- isWindows
ghc94 <- isGhcVersion "== 9.4.*"
expectBrokenIf (isWin && ghc94) 8451 $ do
cabal' "v2-build" ["script.hs"]
env <- getTestEnv
......
import Test.Cabal.Prelude
main = cabalTest . void $ do
isWin <- isWindows
ghc94 <- isGhcVersion "== 9.4.*"
expectBrokenIf (isWin && ghc94) 8451 $ do
cabal' "v2-build" ["script.hs"]
cabal' "v2-build" ["script.hs"]
......@@ -2,9 +2,6 @@ import Test.Cabal.Prelude
import System.Directory (copyFile, removeFile)
main = cabalTest . void $ do
isWin <- isWindows
ghc94 <- isGhcVersion "== 9.4.*"
expectBrokenIf (isWin && ghc94) 8451 $ do
env <- getTestEnv
let td = testCurrentDir env
......
......@@ -2,9 +2,6 @@ import Test.Cabal.Prelude
import System.Directory (copyFile, removeFile)
main = cabalTest . void $ do
isWin <- isWindows
ghc94 <- isGhcVersion "== 9.4.*"
expectBrokenIf (isWin && ghc94) 8451 $ do
env <- getTestEnv
let td = testCurrentDir env
......
import Test.Cabal.Prelude
main = cabalTest . void $ do
isWin <- isWindows
ghc94 <- isGhcVersion "== 9.4.*"
expectBrokenIf (isWin && ghc94) 8451 $ do
cabal' "v2-build" ["script.hs"]
cabal' "v2-clean" ["script.hs"]
......
import Test.Cabal.Prelude
main = cabalTest $ do
isWin <- isWindows
ghc94 <- isGhcVersion "== 9.4.*"
expectBrokenIf (isWin && ghc94) 8451 $ do
res <- cabal' "v2-run" ["script.hs"]
assertOutputContains "Hello World" res
......
import Test.Cabal.Prelude
main = cabalTest . void $ do
isWin <- isWindows
ghc94 <- isGhcVersion "== 9.4.*"
expectBrokenIf (isWin && ghc94) 8451 $ do
cabal' "v2-run" ["with sp"] >>= assertOutputContains "Hello World"
import Test.Cabal.Prelude
main = cabalTest . void $ do
isWin <- isWindows
ghc94 <- isGhcVersion "== 9.4.*"
expectBrokenIf (isWin && ghc94) 8451 $ do
cabal' "v2-run" ["script.hs"]
cabal' "v2-run" ["script.hs"]
import Test.Cabal.Prelude
main = cabalTest $ do
isWin <- isWindows
ghc94 <- isGhcVersion "== 9.4.*"
expectBrokenIf (isWin && ghc94) 8451 $ do
-- script is called "s.hs" to avoid Windows long path issue in CI
res <- cabal' "v2-run" ["s.hs"]
assertOutputContains "Hello World" res
import Test.Cabal.Prelude
main = cabalTest $ do
isWin <- isWindows
ghc94 <- isGhcVersion "== 9.4.*"
expectBrokenIf (isWin && ghc94) 8451 $ do
cabal "v2-test"
[ "--test-option=1"
, "--test-options=\"2 3\""
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment