Skip to content

Commit fc27efb

Browse files
committed
Add GHC-8.8 job to travis
Use cabal-install-3.0, as otherwise we won't be able to build custom setup for GHC-8.8
1 parent 53eddce commit fc27efb

File tree

14 files changed

+128
-101
lines changed

14 files changed

+128
-101
lines changed

.travis.yml

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -53,6 +53,9 @@ matrix:
5353
- env: GHCVER=8.6.5 SCRIPT=script USE_GOLD=YES
5454
os: linux
5555
sudo: required
56+
- env: GHCVER=8.8.1 SCRIPT=script USE_GOLD=YES
57+
os: linux
58+
sudo: required
5659
#- env: GHCVER=8.8.1 SCRIPT=script USE_GOLD=YES
5760
# os: linux
5861
# sudo: required
@@ -120,7 +123,7 @@ before_install:
120123
- export PATH=$HOME/bin:$PATH
121124
- export PATH=$HOME/.cabal/bin:$PATH
122125
- export PATH=$HOME/.local/bin:$PATH
123-
- export PATH=/opt/cabal/2.4/bin:$PATH
126+
- export PATH=/opt/cabal/3.0/bin:$PATH
124127
- if [ "$USE_GOLD" = "YES" ]; then sudo update-alternatives --install "/usr/bin/ld" "ld" "/usr/bin/ld.gold" 20; fi
125128
- if [ "$USE_GOLD" = "YES" ]; then sudo update-alternatives --install "/usr/bin/ld" "ld" "/usr/bin/ld.bfd" 10; fi
126129
- ld -v

Cabal/Cabal.cabal

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -294,7 +294,9 @@ library
294294
ghc-options: -Wall -fno-ignore-asserts -fwarn-tabs
295295
if impl(ghc >= 8.0)
296296
ghc-options: -Wcompat -Wnoncanonical-monad-instances
297-
-Wnoncanonical-monadfail-instances
297+
298+
if impl(ghc <8.8)
299+
ghc-options: -Wnoncanonical-monadfail-instances
298300

299301
if !impl(ghc >= 8.0)
300302
-- at least one of lib:Cabal's dependency (i.e. `parsec`)

cabal-install/Distribution/Client/CmdBuild.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -11,10 +11,12 @@ module Distribution.Client.CmdBuild (
1111
selectComponentTarget
1212
) where
1313

14+
import Prelude ()
15+
import Distribution.Client.Compat.Prelude
16+
1417
import Distribution.Client.ProjectOrchestration
1518
import Distribution.Client.CmdErrorMessages
1619

17-
import Distribution.Compat.Semigroup ((<>))
1820
import Distribution.Client.Setup
1921
( GlobalFlags, ConfigFlags(..), ConfigExFlags, InstallFlags
2022
, liftOptions, yesNoOpt )

cabal-install/Distribution/Client/CmdSdist.hs

Lines changed: 8 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,9 @@ module Distribution.Client.CmdSdist
99
, SdistFlags(..), defaultSdistFlags
1010
, OutputFormat(..)) where
1111

12+
import Prelude ()
13+
import Distribution.Client.Compat.Prelude
14+
1215
import Distribution.Client.CmdErrorMessages
1316
( Plural(..), renderComponentKind )
1417
import Distribution.Client.ProjectOrchestration
@@ -29,9 +32,6 @@ import Distribution.Client.DistDirLayout
2932
import Distribution.Client.ProjectConfig
3033
( findProjectRoot, readProjectConfig )
3134

32-
import Distribution.Compat.Semigroup
33-
((<>))
34-
3535
import Distribution.Package
3636
( Package(packageId) )
3737
import Distribution.PackageDescription.Configuration
@@ -64,8 +64,6 @@ import qualified Codec.Archive.Tar.Entry as Tar
6464
import qualified Codec.Compression.GZip as GZip
6565
import Control.Exception
6666
( throwIO )
67-
import Control.Monad
68-
( when, forM_ )
6967
import Control.Monad.Trans
7068
( liftIO )
7169
import Control.Monad.State.Lazy
@@ -77,7 +75,7 @@ import qualified Data.ByteString.Lazy.Char8 as BSL
7775
import Data.Either
7876
( partitionEithers )
7977
import Data.List
80-
( find, sortOn, nub )
78+
( sortOn )
8179
import qualified Data.Set as Set
8280
import System.Directory
8381
( getCurrentDirectory, setCurrentDirectory
@@ -192,7 +190,7 @@ sdistAction SdistFlags{..} targetStrings globalFlags = do
192190
| length pkgs > 1, not listSources, Just "-" <- mOutputPath' ->
193191
die' verbosity "Can't write multiple tarballs to standard output!"
194192
| otherwise ->
195-
mapM_ (\pkg -> packageToSdist verbosity (distProjectRootDirectory distLayout) format (outputPath pkg) pkg) pkgs
193+
traverse_ (\pkg -> packageToSdist verbosity (distProjectRootDirectory distLayout) format (outputPath pkg) pkg) pkgs
196194

197195
data IsExec = Exec | NoExec
198196
deriving (Show, Eq)
@@ -256,7 +254,7 @@ packageToSdist verbosity projectRootDir format outputFile pkg = do
256254
Left err -> liftIO $ die' verbosity ("Error packing sdist: " ++ err)
257255
Right path -> tell [Tar.directoryEntry path]
258256

259-
forM_ files $ \(perm, file) -> do
257+
for_ files $ \(perm, file) -> do
260258
let fileDir = takeDirectory (prefix </> file)
261259
perm' = case perm of
262260
Exec -> Tar.executableFilePermissions
@@ -276,9 +274,9 @@ packageToSdist verbosity projectRootDir format outputFile pkg = do
276274

277275
entries <- execWriterT (evalStateT entriesM mempty)
278276
let -- Pretend our GZip file is made on Unix.
279-
normalize bs = BSL.concat [first, "\x03", rest']
277+
normalize bs = BSL.concat [pfx, "\x03", rest']
280278
where
281-
(first, rest) = BSL.splitAt 9 bs
279+
(pfx, rest) = BSL.splitAt 9 bs
282280
rest' = BSL.tail rest
283281
-- The Unix epoch, which is the default value, is
284282
-- unsuitable because it causes unpacking problems on

cabal-install/Distribution/Client/GZipUtils.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -18,12 +18,14 @@ module Distribution.Client.GZipUtils (
1818
maybeDecompress,
1919
) where
2020

21+
import Prelude ()
22+
import Distribution.Client.Compat.Prelude
23+
2124
import Codec.Compression.Zlib.Internal
2225
import Data.ByteString.Lazy.Internal as BS (ByteString(Empty, Chunk))
2326

2427
#if MIN_VERSION_zlib(0,6,0)
2528
import Control.Exception (throw)
26-
import Control.Monad (liftM)
2729
import Control.Monad.ST.Lazy (ST, runST)
2830
import qualified Data.ByteString as Strict
2931
#endif

cabal-install/cabal-install.cabal

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -141,7 +141,9 @@ executable cabal
141141
if impl(ghc >= 8.0)
142142
ghc-options: -Wcompat
143143
-Wnoncanonical-monad-instances
144-
-Wnoncanonical-monadfail-instances
144+
if impl(ghc < 8.8)
145+
ghc-options: -Wnoncanonical-monadfail-instances
146+
145147

146148
ghc-options: -rtsopts -threaded
147149

cabal-install/cabal-install.cabal.pp

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -73,7 +73,9 @@
7373
if impl(ghc >= 8.0)
7474
ghc-options: -Wcompat
7575
-Wnoncanonical-monad-instances
76-
-Wnoncanonical-monadfail-instances
76+
if impl(ghc < 8.8)
77+
ghc-options: -Wnoncanonical-monadfail-instances
78+
7779
%enddef
7880
%def CABAL_BUILDINFO
7981
%if CABAL_FLAG_LIB

cabal-install/tests/UnitTests/Distribution/Client/GZipUtils.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -2,17 +2,17 @@ module UnitTests.Distribution.Client.GZipUtils (
22
tests
33
) where
44

5+
import Prelude ()
6+
import Distribution.Client.Compat.Prelude
7+
58
import Codec.Compression.GZip as GZip
69
import Codec.Compression.Zlib as Zlib
710
import Control.Exception.Base (evaluate)
811
import Control.Exception (try, SomeException)
9-
import Control.Monad (void)
1012
import Data.ByteString as BS (null)
1113
import Data.ByteString.Lazy as BSL (pack, toChunks)
1214
import Data.ByteString.Lazy.Char8 as BSLL (pack, init, length)
13-
import Data.Monoid ((<>))
1415
import Distribution.Client.GZipUtils (maybeDecompress)
15-
import Data.Word (Word8)
1616

1717
import Test.Tasty
1818
import Test.Tasty.HUnit
@@ -34,7 +34,7 @@ maybeDecompressUnitTest =
3434
>> assertBool "decompress gzip (with show)" (show (maybeDecompress compressedGZip) == show original)
3535
>> assertBool "decompress zlib" (maybeDecompress compressedZlib == original)
3636
>> assertBool "decompress gzip" (maybeDecompress compressedGZip == original)
37-
>> assertBool "have no empty chunks" (Prelude.all (not . BS.null) . BSL.toChunks . maybeDecompress $ compressedZlib)
37+
>> assertBool "have no empty chunks" (all (not . BS.null) . BSL.toChunks . maybeDecompress $ compressedZlib)
3838
>> (runBrokenStream >>= assertBool "decompress broken stream" . isLeft)
3939
where
4040
original = BSLL.pack "original uncompressed input"

cabal-testsuite/Test/Cabal/Monad.hs

Lines changed: 4 additions & 70 deletions
Original file line numberDiff line numberDiff line change
@@ -23,8 +23,6 @@ module Test.Cabal.Monad (
2323
-- * Recording mode
2424
RecordMode(..),
2525
testRecordMode,
26-
-- * Regex utility (move me somewhere else)
27-
resub,
2826
-- * Derived values from 'TestEnv'
2927
testCurrentDir,
3028
testWorkDir,
@@ -58,6 +56,7 @@ module Test.Cabal.Monad (
5856

5957
import Test.Cabal.Script
6058
import Test.Cabal.Plan
59+
import Test.Cabal.OutputNormalizer
6160

6261
import Distribution.Simple.Compiler
6362
( PackageDBStack, PackageDB(..), compilerFlavor
@@ -67,20 +66,17 @@ import Distribution.Simple.Program.Db
6766
import Distribution.Simple.Program
6867
import Distribution.Simple.Configure
6968
( configCompilerEx )
70-
import Distribution.Version
7169
import Distribution.Text
72-
import Distribution.Package
7370

7471
import Distribution.Verbosity
7572

73+
import Data.Monoid ((<>), mempty)
7674
import qualified Control.Exception as E
7775
import Control.Monad
7876
import Control.Monad.Trans.Reader
7977
import Control.Monad.IO.Class
8078
import Data.Maybe
8179
import Control.Applicative
82-
import Data.Monoid
83-
import qualified Data.Foldable as F
8480
import System.Directory
8581
import System.Exit
8682
import System.FilePath
@@ -89,7 +85,6 @@ import System.IO.Error (isDoesNotExistError)
8985
import System.IO.Temp (withSystemTempDirectory)
9086
import System.Process hiding (env)
9187
import Options.Applicative
92-
import Text.Regex
9388

9489
data CommonArgs = CommonArgs {
9590
argCabalInstallPath :: Maybe FilePath,
@@ -104,7 +99,7 @@ commonArgParser :: Parser CommonArgs
10499
commonArgParser = CommonArgs
105100
<$> optional (option str
106101
( help "Path to cabal-install executable to test"
107-
<> long "with-cabal"
102+
Data.Monoid.<> long "with-cabal"
108103
<> metavar "PATH"
109104
))
110105
<*> optional (option str
@@ -233,7 +228,7 @@ diffProgram = simpleProgram "diff"
233228
-- | Run a test in the test monad according to program's arguments.
234229
runTestM :: String -> TestM a -> IO a
235230
runTestM mode m = withSystemTempDirectory "cabal-testsuite" $ \tmp_dir -> do
236-
args <- execParser (info testArgParser mempty)
231+
args <- execParser (info testArgParser Data.Monoid.mempty)
237232
let dist_dir = testArgDistDir args
238233
(script_dir0, script_filename) = splitFileName (testArgScriptPath args)
239234
script_base = dropExtensions script_filename
@@ -397,57 +392,6 @@ writeFileNoCR f s =
397392
hSetNewlineMode h noNewlineTranslation
398393
hPutStr h s
399394

400-
normalizeOutput :: NormalizerEnv -> String -> String
401-
normalizeOutput nenv =
402-
-- Munge away .exe suffix on filenames (Windows)
403-
resub "([A-Za-z0-9.-]+)\\.exe" "\\1"
404-
-- Normalize backslashes to forward slashes to normalize
405-
-- file paths
406-
. map (\c -> if c == '\\' then '/' else c)
407-
-- Install path frequently has architecture specific elements, so
408-
-- nub it out
409-
. resub "Installing (.+) in .+" "Installing \\1 in <PATH>"
410-
-- Things that look like libraries
411-
. resub "libHS[A-Za-z0-9.-]+\\.(so|dll|a|dynlib)" "<LIBRARY>"
412-
-- This is dumb but I don't feel like pulling in another dep for
413-
-- string search-replace. Make sure we do this before backslash
414-
-- normalization!
415-
. resub (posixRegexEscape (normalizerRoot nenv)) "<ROOT>/"
416-
. resub (posixRegexEscape (normalizerTmpDir nenv)) "<TMPDIR>/"
417-
. appEndo (F.fold (map (Endo . packageIdRegex) (normalizerKnownPackages nenv)))
418-
-- Look for foo-0.1/installed-0d6...
419-
-- These installed packages will vary depending on GHC version
420-
-- Makes assumption that installed packages don't have numbers
421-
-- in package name segment.
422-
-- Apply this before packageIdRegex, otherwise this regex doesn't match.
423-
. resub "([a-zA-Z]+(-[a-zA-Z])*)-[0-9]+(\\.[0-9]+)*/installed-[A-Za-z0-9.]+"
424-
"\\1-<VERSION>/installed-<HASH>..."
425-
-- Normalize architecture
426-
. resub (posixRegexEscape (display (normalizerPlatform nenv))) "<ARCH>"
427-
-- Some GHC versions are chattier than others
428-
. resub "^ignoring \\(possibly broken\\) abi-depends field for packages" ""
429-
-- Normalize the current GHC version. Apply this BEFORE packageIdRegex,
430-
-- which will pick up the install ghc library (which doesn't have the
431-
-- date glob).
432-
. (if normalizerGhcVersion nenv /= nullVersion
433-
then resub (posixRegexEscape (display (normalizerGhcVersion nenv))
434-
-- Also glob the date, for nightly GHC builds
435-
++ "(\\.[0-9]+)?")
436-
"<GHCVER>"
437-
else id)
438-
where
439-
packageIdRegex pid =
440-
resub (posixRegexEscape (display pid) ++ "(-[A-Za-z0-9.-]+)?")
441-
((display (packageName pid)) ++ "-<VERSION>")
442-
443-
data NormalizerEnv = NormalizerEnv {
444-
normalizerRoot :: FilePath,
445-
normalizerTmpDir :: FilePath,
446-
normalizerGhcVersion :: Version,
447-
normalizerKnownPackages :: [PackageId],
448-
normalizerPlatform :: Platform
449-
}
450-
451395
mkNormalizerEnv :: TestM NormalizerEnv
452396
mkNormalizerEnv = do
453397
env <- getTestEnv
@@ -469,16 +413,6 @@ mkNormalizerEnv = do
469413
= testPlatform env
470414
}
471415

472-
posixSpecialChars :: [Char]
473-
posixSpecialChars = ".^$*+?()[{\\|"
474-
475-
posixRegexEscape :: String -> String
476-
posixRegexEscape = concatMap (\c -> if c `elem` posixSpecialChars then ['\\', c] else [c])
477-
478-
resub :: String {- search -} -> String {- replace -} -> String {- input -} -> String
479-
resub search replace s =
480-
subRegex (mkRegex search) s replace
481-
482416
requireProgramM :: Program -> TestM ConfiguredProgram
483417
requireProgramM program = do
484418
env <- getTestEnv
Lines changed: 79 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,79 @@
1+
module Test.Cabal.OutputNormalizer (
2+
NormalizerEnv (..),
3+
normalizeOutput,
4+
) where
5+
6+
import Data.Monoid (Endo (..))
7+
8+
import Distribution.Version
9+
import Distribution.Text
10+
import Distribution.Pretty
11+
import Distribution.Package
12+
import Distribution.System
13+
14+
import qualified Data.Foldable as F
15+
16+
import Text.Regex
17+
18+
normalizeOutput :: NormalizerEnv -> String -> String
19+
normalizeOutput nenv =
20+
-- Munge away .exe suffix on filenames (Windows)
21+
resub "([A-Za-z0-9.-]+)\\.exe" "\\1"
22+
-- Normalize backslashes to forward slashes to normalize
23+
-- file paths
24+
. map (\c -> if c == '\\' then '/' else c)
25+
-- Install path frequently has architecture specific elements, so
26+
-- nub it out
27+
. resub "Installing (.+) in .+" "Installing \\1 in <PATH>"
28+
-- Things that look like libraries
29+
. resub "libHS[A-Za-z0-9.-]+\\.(so|dll|a|dynlib)" "<LIBRARY>"
30+
-- This is dumb but I don't feel like pulling in another dep for
31+
-- string search-replace. Make sure we do this before backslash
32+
-- normalization!
33+
. resub (posixRegexEscape (normalizerRoot nenv)) "<ROOT>/"
34+
. resub (posixRegexEscape (normalizerTmpDir nenv)) "<TMPDIR>/"
35+
. appEndo (F.fold (map (Endo . packageIdRegex) (normalizerKnownPackages nenv)))
36+
-- Look for foo-0.1/installed-0d6...
37+
-- These installed packages will vary depending on GHC version
38+
-- Makes assumption that installed packages don't have numbers
39+
-- in package name segment.
40+
-- Apply this before packageIdRegex, otherwise this regex doesn't match.
41+
. resub "([a-zA-Z]+(-[a-zA-Z])*)-[0-9]+(\\.[0-9]+)*/installed-[A-Za-z0-9.]+"
42+
"\\1-<VERSION>/installed-<HASH>..."
43+
-- Normalize architecture
44+
. resub (posixRegexEscape (display (normalizerPlatform nenv))) "<ARCH>"
45+
-- Some GHC versions are chattier than others
46+
. resub "^ignoring \\(possibly broken\\) abi-depends field for packages" ""
47+
-- Normalize the current GHC version. Apply this BEFORE packageIdRegex,
48+
-- which will pick up the install ghc library (which doesn't have the
49+
-- date glob).
50+
. (if normalizerGhcVersion nenv /= nullVersion
51+
then resub (posixRegexEscape (display (normalizerGhcVersion nenv))
52+
-- Also glob the date, for nightly GHC builds
53+
++ "(\\.[0-9]+)?")
54+
"<GHCVER>"
55+
else id)
56+
-- hackage-security locks occur non-deterministically
57+
. resub "(Released|Acquired|Waiting) .*hackage-security-lock\n" ""
58+
where
59+
packageIdRegex pid =
60+
resub (posixRegexEscape (display pid) ++ "(-[A-Za-z0-9.-]+)?")
61+
(prettyShow (packageName pid) ++ "-<VERSION>")
62+
63+
data NormalizerEnv = NormalizerEnv
64+
{ normalizerRoot :: FilePath
65+
, normalizerTmpDir :: FilePath
66+
, normalizerGhcVersion :: Version
67+
, normalizerKnownPackages :: [PackageId]
68+
, normalizerPlatform :: Platform
69+
}
70+
71+
posixSpecialChars :: [Char]
72+
posixSpecialChars = ".^$*+?()[{\\|"
73+
74+
posixRegexEscape :: String -> String
75+
posixRegexEscape = concatMap (\c -> if c `elem` posixSpecialChars then ['\\', c] else [c])
76+
77+
resub :: String {- search -} -> String {- replace -} -> String {- input -} -> String
78+
resub search replace s =
79+
subRegex (mkRegex search) s replace

0 commit comments

Comments
 (0)