Skip to content
Snippets Groups Projects
Commit 1981ebac authored by Artem Pelenitsyn's avatar Artem Pelenitsyn Committed by Mergify
Browse files

GHC 9.6 compatibility

- -XTypeInType is deprecated
- skip failing JS test on Windows
  Cf. https://github.com/haskell/cabal/pull/8754#issuecomment-1435535763
- deal with lift2A in Prelude since base-4.18 (GHC 9.6)
- disable everfailing Backpack tests

(cherry picked from commit 87ac1203)
parent 7de5460c
No related branches found
No related tags found
No related merge requests found
......@@ -7,7 +7,6 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE TypeInType #-}
-- |
--
-- Copyright: (c) 2019 Oleg Grenrus
......
{-# 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
......
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"]
......
......@@ -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)
......
......@@ -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"
......
......@@ -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
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