diff --git a/Cabal-syntax/src/Distribution/Utils/Structured.hs b/Cabal-syntax/src/Distribution/Utils/Structured.hs index 5327ed6a4270b363c317cf46529248bab1727268..ca3147710c8a8551de1e3f7b88bfaaf899fffada 100644 --- a/Cabal-syntax/src/Distribution/Utils/Structured.hs +++ b/Cabal-syntax/src/Distribution/Utils/Structured.hs @@ -7,7 +7,6 @@ {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE PatternSynonyms #-} -{-# LANGUAGE TypeInType #-} -- | -- -- Copyright: (c) 2019 Oleg Grenrus diff --git a/cabal-install/src/Distribution/Client/VCS.hs b/cabal-install/src/Distribution/Client/VCS.hs index 8b0a95462dada0c6be16de48879e0f9478935f95..aca3f4b109f4023d7815ebb0bbfdf7fd395e7977 100644 --- a/cabal-install/src/Distribution/Client/VCS.hs +++ b/cabal-install/src/Distribution/Client/VCS.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE CPP #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE NamedFieldPuns, RecordWildCards, RankNTypes #-} @@ -53,8 +54,11 @@ import Distribution.Version ( mkVersion ) import qualified Distribution.PackageDescription as PD +#if !MIN_VERSION_base(4,18,0) import Control.Applicative ( liftA2 ) +#endif + import Control.Exception ( throw, try ) import Control.Monad.Trans diff --git a/cabal-testsuite/PackageTests/Backpack/Includes2/setup-external.test.hs b/cabal-testsuite/PackageTests/Backpack/Includes2/setup-external.test.hs index fb6843f5a526ea6176181f7bf0e25a3ca0cf8069..3e4577aecfa62d01254bbd0efb13f8a4c1c69170 100644 --- a/cabal-testsuite/PackageTests/Backpack/Includes2/setup-external.test.hs +++ b/cabal-testsuite/PackageTests/Backpack/Includes2/setup-external.test.hs @@ -1,7 +1,7 @@ import Test.Cabal.Prelude main = setupAndCabalTest $ do skipUnlessGhcVersion ">= 8.1" - ghc <- isGhcVersion "== 9.0.2 || == 9.2.* || == 9.4.*" + ghc <- isGhcVersion "== 9.0.2 || == 9.2.* || == 9.4.* || == 9.6.*" expectBrokenIf ghc 7987 $ do withPackageDb $ do withDirectory "mylib" $ setup_install_with_docs ["--ipid", "mylib-0.1.0.0"] diff --git a/cabal-testsuite/PackageTests/Backpack/Includes2/setup-per-component.test.hs b/cabal-testsuite/PackageTests/Backpack/Includes2/setup-per-component.test.hs index 1f01eff1efa03ae21ea1cc7ec26d5b3f8e53f8b7..5196d404f658643c1bf87591938738b1421c80db 100644 --- a/cabal-testsuite/PackageTests/Backpack/Includes2/setup-per-component.test.hs +++ b/cabal-testsuite/PackageTests/Backpack/Includes2/setup-per-component.test.hs @@ -2,7 +2,7 @@ import Test.Cabal.Prelude main = setupTest $ do -- No cabal test because per-component is broken with it skipUnlessGhcVersion ">= 8.1" - ghc <- isGhcVersion "== 9.0.2 || == 9.2.* || == 9.4.*" + ghc <- isGhcVersion "== 9.0.2 || == 9.2.* || == 9.4.* || == 9.6.*" expectBrokenIf ghc 7987 $ withPackageDb $ do let setup_install' args = setup_install_with_docs (["--cabal-file", "Includes2.cabal"] ++ args) diff --git a/cabal-testsuite/PackageTests/Backpack/Includes3/setup-external-ok.test.hs b/cabal-testsuite/PackageTests/Backpack/Includes3/setup-external-ok.test.hs index bea7f9a089dcece1cd2d4098ea25022eba3072ce..d7ae9a1921d19c0c3a9fce1c6ac4e62708ac4dee 100644 --- a/cabal-testsuite/PackageTests/Backpack/Includes3/setup-external-ok.test.hs +++ b/cabal-testsuite/PackageTests/Backpack/Includes3/setup-external-ok.test.hs @@ -3,7 +3,7 @@ import Data.List import qualified Data.Char as Char main = setupAndCabalTest $ do skipUnlessGhcVersion ">= 8.1" - ghc <- isGhcVersion "== 9.0.2 || == 9.2.* || == 9.4.*" + ghc <- isGhcVersion "== 9.0.2 || == 9.2.* || == 9.4.* || == 9.6.*" expectBrokenIf ghc 7987 $ withPackageDb $ do containers_id <- getIPID "containers" diff --git a/cabal-testsuite/PackageTests/JS/JsSources/js-arch.test.hs b/cabal-testsuite/PackageTests/JS/JsSources/js-arch.test.hs index 612c9829cde9e46cf60249490b6fd4957bc17215..1fed749bdb8eadf820ce3868cf5f97eb787a5498 100644 --- a/cabal-testsuite/PackageTests/JS/JsSources/js-arch.test.hs +++ b/cabal-testsuite/PackageTests/JS/JsSources/js-arch.test.hs @@ -3,6 +3,7 @@ import Test.Cabal.Prelude main = setupAndCabalTest $ do skipUnlessGhcVersion ">= 9.6" skipUnlessJavaScript + skipIfWindows res <- cabal' "v2-run" ["demo"] assertOutputContains "Hello JS!" res