{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -Wno-unused-imports -Wno-unused-matches #-}
module HaskellCI.Travis (
makeTravis,
travisHeader,
) where
import HaskellCI.Prelude
import Prelude (head)
import qualified Data.Map.Strict as M
import qualified Data.Set as S
import qualified Distribution.CabalSpecVersion as C
import qualified Distribution.FieldGrammar as C
import qualified Distribution.FieldGrammar.Pretty as C
import qualified Distribution.Fields.Pretty as C
import qualified Distribution.Package as C
import qualified Distribution.PackageDescription as C
import qualified Distribution.PackageDescription.Configuration as C
import qualified Distribution.PackageDescription.FieldGrammar as C
import qualified Distribution.Pretty as C
import qualified Distribution.Types.GenericPackageDescription as C
import qualified Distribution.Types.SourceRepo as C
import qualified Distribution.Types.VersionRange as C
import qualified Distribution.Version as C
import qualified Text.PrettyPrint as PP
import qualified Distribution.Types.BuildInfo.Lens as L
import qualified Distribution.Types.PackageDescription.Lens as L
import Cabal.Optimization
import Cabal.Project
import Cabal.SourceRepo
import HaskellCI.Cli
import HaskellCI.Compiler
import HaskellCI.Config
import HaskellCI.Config.ConstraintSet
import HaskellCI.Config.CopyFields
import HaskellCI.Config.Doctest
import HaskellCI.Config.Folds
import HaskellCI.Config.HLint
import HaskellCI.Config.Installed
import HaskellCI.Config.Jobs
import HaskellCI.Config.PackageScope
import HaskellCI.Config.Ubuntu
import HaskellCI.Jobs
import HaskellCI.List
import HaskellCI.MonadErr
import HaskellCI.Package
import HaskellCI.Sh
import HaskellCI.ShVersionRange
import HaskellCI.Tools
import HaskellCI.Travis.Yaml
import HaskellCI.VersionInfo
travisHeader :: Bool -> [String] -> [String]
travisHeader insertVersion argv =
[ "This Travis job script has been generated by a script via"
, ""
, " haskell-ci " ++ unwords [ "'" ++ a ++ "'" | a <- argv ]
, ""
, "To regenerate the script (for example after adjusting tested-with) run"
, ""
, " haskell-ci regenerate"
, ""
, "For more information, see https://github.com/haskell-CI/haskell-ci"
, ""
] ++
if insertVersion then
[ "version: " ++ haskellCIVerStr
, ""
] else []
makeTravis
:: [String]
-> Config
-> Project URI Void Package
-> JobVersions
-> Either ShError Travis
makeTravis argv Config {..} prj JobVersions {..} = do
beforeCache <- runSh $ when cfgCache $ do
sh "rm -fv $CABALHOME/packages/hackage.haskell.org/build-reports.log"
comment "remove files that are regenerated by 'cabal update'"
sh "rm -fv $CABALHOME/packages/hackage.haskell.org/00-index.*"
sh "rm -fv $CABALHOME/packages/hackage.haskell.org/*.json"
sh "rm -fv $CABALHOME/packages/hackage.haskell.org/01-index.cache"
sh "rm -fv $CABALHOME/packages/hackage.haskell.org/01-index.tar"
sh "rm -fv $CABALHOME/packages/hackage.haskell.org/01-index.tar.idx"
sh "rm -rfv $CABALHOME/packages/head.hackage"
beforeInstall <- runSh $ do
when anyGHCJS $ sh $ unlines
[ "if echo $CC | grep -q ghcjs; then"
, " GHCJS=true;"
, "else"
, " GHCJS=false;"
, "fi"
]
sh "HC=$(echo \"/opt/$CC/bin/ghc\" | sed 's/-/\\//')"
sh "WITHCOMPILER=\"-w $HC\""
shForJob RangeGHCJS "HC=${HC}js"
shForJob RangeGHCJS "WITHCOMPILER=\"--ghcjs ${WITHCOMPILER}js\""
sh "HADDOCK=$(echo \"/opt/$CC/bin/haddock\" | sed 's/-/\\//')"
unless (null cfgOsx) $ do
sh $ "if [ \"$TRAVIS_OS_NAME\" = \"osx\" ]; then HADDOCK=$(echo $HADDOCK | sed \"s:^/opt:$HOME/.ghc-install:\"); fi"
when anyGHCJS $ do
shForJob RangeGHCJS $ "PATH=\"/opt/ghc/8.4.4/bin:$PATH\""
sh "HCPKG=\"$HC-pkg\""
sh "unset CC"
sh "CABAL=/opt/ghc/bin/cabal"
sh "CABALHOME=$HOME/.cabal"
sh "export PATH=\"$CABALHOME/bin:$PATH\""
sh "TOP=$(pwd)"
let haskellOnMacos = "https://haskell.futurice.com/haskell-on-macos.py"
unless (null cfgOsx) $ do
sh $ "if [ \"$TRAVIS_OS_NAME\" = \"osx\" ]; then curl " ++ haskellOnMacos ++ " | python3 - --make-dirs --install-dir=$HOME/.ghc-install --cabal-alias=3.2.0.0 install cabal-install-3.2.0.0 ${TRAVIS_COMPILER}; fi"
sh' [2034,2039] "if [ \"$TRAVIS_OS_NAME\" = \"osx\" ]; then HC=$HOME/.ghc-install/ghc/bin/$TRAVIS_COMPILER; WITHCOMPILER=\"-w $HC\"; HCPKG=$HOME/.ghc-install/ghc/bin/${TRAVIS_COMPILER/ghc/ghc-pkg}; CABAL=$HOME/.ghc-install/ghc/bin/cabal; fi"
sh "HCNUMVER=$(${HC} --numeric-version|perl -ne '/^(\\d+)\\.(\\d+)\\.(\\d+)(\\.(\\d+))?$/; print(10000 * $1 + 100 * $2 + ($3 == 0 ? $5 != 1 : $3))')"
sh "echo $HCNUMVER"
sh "CABAL=\"$CABAL -vnormal+nowrap\""
sh' [2039] "set -o pipefail"
sh "TEST=--enable-tests"
shForJob (invertCompilerRange $ Range cfgTests) "TEST=--disable-tests"
sh "BENCH=--enable-benchmarks"
shForJob (invertCompilerRange $ Range cfgBenchmarks) "BENCH=--disable-benchmarks"
sh "HEADHACKAGE=false"
shForJob (Range cfgHeadHackage \/ RangePoints (S.singleton GHCHead)) "HEADHACKAGE=true"
sh "rm -f $CABALHOME/config"
cat "$CABALHOME/config"
[ "verbose: normal +nowrap +markoutput"
, "remote-build-reporting: anonymous"
, "write-ghc-environment-files: always"
, "remote-repo-cache: $CABALHOME/packages"
, "logs-dir: $CABALHOME/logs"
, "world-file: $CABALHOME/world"
, "extra-prog-path: $CABALHOME/bin"
, "symlink-bindir: $CABALHOME/bin"
, "installdir: $CABALHOME/bin"
, "build-summary: $CABALHOME/logs/build.log"
, "store-dir: $CABALHOME/store"
, "install-dirs user"
, " prefix: $CABALHOME"
, "repository hackage.haskell.org"
, " url: http://hackage.haskell.org/"
]
unless (S.null headGhcVers) $ sh $ unlines $
[ "if $HEADHACKAGE; then"
, "echo \"allow-newer: $($HCPKG list --simple-output | sed -E 's/([a-zA-Z-]+)-[0-9.]+/*:\\1/g')\" >> $CABALHOME/config"
] ++
lines (catCmd Double "$CABALHOME/config"
[ "repository head.hackage.ghc.haskell.org"
, " url: https://ghc.gitlab.haskell.org/head.hackage/"
, " secure: True"
, " root-keys: 7541f32a4ccca4f97aea3b22f5e593ba2c0267546016b992dfadcd2fe944e55d"
, " 26021a13b401500c8eb2761ca95c61f2d625bfef951b939a8124ed12ecf07329"
, " f76d08be13e9a61a377a85e2fb63f4c5435d40f8feb3e12eb05905edb8cdea89"
, " key-threshold: 3"
]) ++
[ "fi"
]
install <- runSh $ do
sh "${CABAL} --version"
sh "echo \"$(${HC} --version) [$(${HC} --print-project-git-commit-id 2> /dev/null || echo '?')]\""
when anyGHCJS $ do
sh "node --version"
sh "echo $GHCJS"
for_ (cfgJobs >>= cabalJobs) $ \n ->
sh $ "echo 'jobs: " ++ show n ++ "' >> $CABALHOME/config"
for_ (cfgJobs >>= ghcJobs) $ \m -> do
shForJob (Range $ C.orLaterVersion (C.mkVersion [7,8])) $ "GHCJOBS=-j" ++ show m
cat "$CABALHOME/config"
[ "program-default-options"
, " ghc-options: $GHCJOBS +RTS -M6G -RTS"
]
sh "cat $CABALHOME/config"
sh "rm -fv cabal.project cabal.project.local cabal.project.freeze"
sh "travis_retry ${CABAL} v2-update -v"
let doctestVersionConstraint
| C.isAnyVersion (cfgDoctestVersion cfgDoctest) = ""
| otherwise = " --constraint='doctest " ++ C.prettyShow (cfgDoctestVersion cfgDoctest) ++ "'"
when doctestEnabled $
shForJob (Range (cfgDoctestEnabled cfgDoctest) /\ doctestJobVersionRange) $
cabal $ "v2-install $WITHCOMPILER --ignore-project -j2 doctest" ++ doctestVersionConstraint
let hlintVersionConstraint
| C.isAnyVersion (cfgHLintVersion cfgHLint) = ""
| otherwise = " --constraint='hlint " ++ C.prettyShow (cfgHLintVersion cfgHLint) ++ "'"
when (cfgHLintEnabled cfgHLint) $ do
let forHLint = shForJob (hlintJobVersionRange versions cfgHeadHackage (cfgHLintJob cfgHLint))
if cfgHLintDownload cfgHLint
then do
forHLint $ "HLINTVER=$(cd /tmp && (${CABAL} v2-install -v $WITHCOMPILER --dry-run hlint " ++ hlintVersionConstraint ++ " | perl -ne 'if (/\\bhlint-(\\d+(\\.\\d+)*)\\b/) { print \"$1\"; last; }')); echo \"HLint version $HLINTVER\""
forHLint $ "if [ ! -e $HOME/.hlint/hlint-$HLINTVER/hlint ]; then " ++ unwords
[ "echo \"Downloading HLint version $HLINTVER\";"
, "mkdir -p $HOME/.hlint;"
, "curl --write-out 'Status Code: %{http_code} Redirects: %{num_redirects} Total time: %{time_total} Total Dsize: %{size_download}\\n' --silent --location --output $HOME/.hlint/hlint-$HLINTVER.tar.gz \"https://github.com/ndmitchell/hlint/releases/download/v$HLINTVER/hlint-$HLINTVER-x86_64-linux.tar.gz\";"
, "tar -xzv -f $HOME/.hlint/hlint-$HLINTVER.tar.gz -C $HOME/.hlint;"
, "fi"
]
forHLint "mkdir -p $CABALHOME/bin && ln -sf \"$HOME/.hlint/hlint-$HLINTVER/hlint\" $CABALHOME/bin/hlint"
forHLint "hlint --version"
else forHLint $ cabal $ "v2-install $WITHCOMPILER --ignore-project -j2 hlint" ++ hlintVersionConstraint
when (anyGHCJS && cfgGhcjsTests) $ do
shForJob RangeGHCJS $ cabal "v2-install -w ghc-8.4.4 --ignore-project cabal-plan --constraint='cabal-plan ^>=0.6.0.0' --constraint='cabal-plan +exe'"
when anyGHCJS $ for_ cfgGhcjsTools $ \t ->
shForJob RangeGHCJS $ cabal $ "v2-install -w ghc-8.4.4 --ignore-project " ++ C.prettyShow t
generateCabalProject False
for_ pkgs $ \Pkg{pkgDir} ->
sh $ "if [ -f \"" ++ pkgDir ++ "/configure.ac\" ]; then (cd \"" ++ pkgDir ++ "\" && autoreconf -i); fi"
sh $ cabal "v2-freeze $WITHCOMPILER ${TEST} ${BENCH}"
sh "cat cabal.project.freeze | sed -E 's/^(constraints: *| *)//' | sed 's/any.//'"
sh "rm cabal.project.freeze"
when cfgInstallDeps $ do
sh $ cabalTW "v2-build $WITHCOMPILER ${TEST} ${BENCH} --dep -j2 all"
shForJob (Range cfgNoTestsNoBench) $ cabalTW "v2-build $WITHCOMPILER --disable-tests --disable-benchmarks --dep -j2 all"
script <- runSh $ do
sh "DISTDIR=$(mktemp -d /tmp/dist-test.XXXX)"
foldedSh FoldSDist "Packaging..." cfgFolds $ do
sh $ cabal "v2-sdist all"
foldedSh FoldUnpack "Unpacking..." cfgFolds $ do
sh "mv dist-newstyle/sdist/*.tar.gz ${DISTDIR}/"
sh "cd ${DISTDIR} || false"
sh "find . -maxdepth 1 -type f -name '*.tar.gz' -exec tar -xvf '{}' \\;"
sh "find . -maxdepth 1 -type f -name '*.tar.gz' -exec rm '{}' \\;"
for_ pkgs $ \Pkg{pkgName} -> do
sh $ pkgNameDirVariable' pkgName ++ "=\"$(find . -maxdepth 1 -type d -regex '.*/" ++ pkgName ++ "-[0-9.]*')\""
generateCabalProject True
when (anyGHCJS && cfgGhcjsTests) $ sh $ unlines $
[ "pkgdir() {"
, " case $1 in"
] ++
[ " " ++ pkgName ++ ") echo " ++ pkgNameDirVariable pkgName ++ " ;;"
| Pkg{pkgName} <- pkgs
] ++
[ " esac"
, "}"
]
unless (equivVersionRanges C.noVersion cfgNoTestsNoBench) $ foldedSh FoldBuild "Building..." cfgFolds $ do
comment "this builds all libraries and executables (without tests/benchmarks)"
shForJob (Range cfgNoTestsNoBench) $ cabal "v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all"
foldedSh FoldBuildEverything "Building with tests and benchmarks..." cfgFolds $ do
comment "build & run tests, build benchmarks"
sh $ cabal "v2-build $WITHCOMPILER ${TEST} ${BENCH} all"
foldedSh FoldTest "Testing..." cfgFolds $ do
shForJob (RangeGHC /\ Range (cfgTests /\ cfgRunTests) /\ hasTests) $
cabal "v2-test $WITHCOMPILER ${TEST} ${BENCH} all"
when cfgGhcjsTests $ shForJob (RangeGHCJS /\ hasTests) $ unwords
[ "cabal-plan list-bins '*:test:*' | while read -r line; do"
, "testpkg=$(echo \"$line\" | perl -pe 's/:.*//');"
, "testexe=$(echo \"$line\" | awk '{ print $2 }');"
, "echo \"testing $textexe in package $textpkg\";"
, "(cd \"$(pkgdir $testpkg)\" && nodejs \"$testexe\".jsexe/all.js);"
, "done"
]
when doctestEnabled $ foldedSh FoldDoctest "Doctest..." cfgFolds $ do
let doctestOptions = unwords $ cfgDoctestOptions cfgDoctest
unless (null $ cfgDoctestFilterEnvPkgs cfgDoctest) $ do
let manglePkgNames :: String -> [String]
manglePkgNames n
| null cfgOsx = [n]
| otherwise = [n, filter notVowel n]
where
notVowel c = notElem c ("aeiou" :: String)
let filterPkgs = intercalate "|" $ concatMap (manglePkgNames . C.unPackageName) $ cfgDoctestFilterEnvPkgs cfgDoctest
sh $ "perl -i -e 'while (<ARGV>) { print unless /package-id\\s+(" ++ filterPkgs ++ ")-\\d+(\\.\\d+)*/; }' .ghc.environment.*"
for_ pkgs $ \Pkg{pkgName,pkgGpd,pkgJobs} ->
when (C.mkPackageName pkgName `notElem` cfgDoctestFilterSrcPkgs cfgDoctest) $ do
for_ (doctestArgs pkgGpd) $ \args -> do
let args' = unwords args
let vr = Range (cfgDoctestEnabled cfgDoctest)
/\ doctestJobVersionRange
/\ RangePoints pkgJobs
unless (null args) $ shForJob vr $
"(cd " ++ pkgNameDirVariable pkgName ++ " && doctest " ++ doctestOptions ++ " " ++ args' ++ ")"
when (cfgHLintEnabled cfgHLint) $ foldedSh FoldHLint "HLint.." cfgFolds $ do
let "" <+> ys = ys
xs <+> "" = xs
xs <+> ys = xs ++ " " ++ ys
prependSpace "" = ""
prependSpace xs = " " ++ xs
let hlintOptions = prependSpace $ maybe "" ("-h ${TOP}/" ++) (cfgHLintYaml cfgHLint) <+> unwords (cfgHLintOptions cfgHLint)
for_ pkgs $ \Pkg{pkgName,pkgGpd,pkgJobs} -> do
for_ (hlintArgs pkgGpd) $ \args -> do
let args' = unwords args
unless (null args) $
shForJob (hlintJobVersionRange versions cfgHeadHackage (cfgHLintJob cfgHLint) /\ RangePoints pkgJobs) $
"(cd " ++ pkgNameDirVariable pkgName ++ " && hlint" ++ hlintOptions ++ " " ++ args' ++ ")"
when cfgCheck $ foldedSh FoldCheck "cabal check..." cfgFolds $ do
for_ pkgs $ \Pkg{pkgName,pkgJobs} -> shForJob (RangePoints pkgJobs) $
"(cd " ++ pkgNameDirVariable pkgName ++ " && ${CABAL} -vnormal check)"
when (hasLibrary && not (equivVersionRanges C.noVersion cfgHaddock)) $
foldedSh FoldHaddock "haddock..." cfgFolds $
shForJob (RangeGHC /\ Range cfgHaddock) $ cabal $ "v2-haddock $WITHCOMPILER " ++ withHaddock ++ " ${TEST} ${BENCH} all"
unless (equivVersionRanges C.noVersion cfgUnconstrainted) $
foldedSh FoldBuildInstalled "Building without installed constraints for packages in global-db..." cfgFolds $ do
shForJob (Range cfgUnconstrainted) "rm -f cabal.project.local"
shForJob (Range cfgUnconstrainted) $ cabal "v2-build $WITHCOMPILER --disable-tests --disable-benchmarks all"
unless (null cfgConstraintSets) $ do
comment "Constraint sets"
sh "rm -rf cabal.project.local"
for_ cfgConstraintSets $ \cs -> do
let name = csName cs
let shForCs = shForJob (Range (csGhcVersions cs))
let shForCs' r = shForJob (Range (csGhcVersions cs) /\ r)
let testFlag = if csTests cs then "--enable-tests" else "--disable-tests"
let benchFlag = if csBenchmarks cs then "--enable-benchmarks" else "--disable-benchmarks"
let constraintFlags = map (\x -> "--constraint='" ++ x ++ "'") (csConstraints cs)
let allFlags = unwords (testFlag : benchFlag : constraintFlags)
foldedSh' FoldConstraintSets name ("Constraint set " ++ name) cfgFolds $ do
shForCs $ cabal $ "v2-build $WITHCOMPILER " ++ allFlags ++ " all"
when (csRunTests cs) $
shForCs' hasTests $ cabal $ "v2-test $WITHCOMPILER " ++ allFlags ++ " all"
when (hasLibrary && csHaddock cs) $
shForCs $ cabal $ "v2-haddock $WITHCOMPILER " ++ withHaddock ++ " " ++ allFlags ++ " all"
unless (null cfgRawTravis) $ do
comment "Raw travis commands"
traverse_ sh
[ l
| l <- lines cfgRawTravis
, not (null l)
]
return Travis
{ travisLanguage = "c"
, travisUbuntu = cfgUbuntu
, travisGit = TravisGit
{ tgSubmodules = cfgSubmodules
}
, travisCache = TravisCache
{ tcDirectories = buildList $ when cfgCache $ do
item "$HOME/.cabal/packages"
item "$HOME/.cabal/store"
item "$HOME/.hlint"
when (cfgCache && not (null cfgOsx)) $ do
item "$HOME/.ghc-install"
}
, travisBranches = TravisBranches
{ tbOnly = cfgOnlyBranches
}
, travisNotifications = TravisNotifications
{ tnIRC = justIf (not $ null cfgIrcChannels) $ TravisIRC
{ tiChannels = cfgIrcChannels
, tiSkipJoin = True
, tiTemplate =
[ "\x0313" ++ projectName ++ "\x03/\x0306%{branch}\x03 \x0314%{commit}\x03 %{build_url} %{message}"
]
}
, tnEmail = cfgEmailNotifications
}
, travisServices = buildList $ do
when cfgPostgres $ item "postgresql"
, travisAddons = TravisAddons
{ taApt = TravisApt [] []
, taPostgres = if cfgPostgres then Just "10" else Nothing
, taGoogleChrome = cfgGoogleChrome
}
, travisMatrix = TravisMatrix
{ tmInclude = buildList $ do
let tellJob :: Bool -> CompilerVersion -> ListBuilder TravisJob ()
tellJob osx gv = do
let cvs = dispCabalVersion $ correspondingCabalVersion cfgCabalInstallVersion gv
let gvs = dispGhcVersion gv
let hvrppa :: TravisAptSource
hvrppa = TravisAptSourceLine ("deb http://ppa.launchpad.net/hvr/ghc/ubuntu " ++ C.prettyShow cfgUbuntu ++ " main") (Just "https://keyserver.ubuntu.com/pks/lookup?op=get&search=0x063dab2bdc0b3f9fcebc378bff3aeacef6f88286")
let ghcjsAptSources :: [TravisAptSource]
ghcjsAptSources | not (isGHCJS gv) = []
| otherwise =
[ TravisAptSourceLine ("deb http://ppa.launchpad.net/hvr/ghcjs/ubuntu " ++ C.prettyShow cfgUbuntu ++ " main") Nothing
, TravisAptSourceLine ("deb https://deb.nodesource.com/node_10.x " ++ C.prettyShow cfgUbuntu ++ " main") (Just "https://deb.nodesource.com/gpgkey/nodesource.gpg.key")
]
let ghcjsPackages :: [String]
ghcjsPackages = case maybeGHCJS gv of
Just v -> [ "ghc-" ++ C.prettyShow v', "nodejs" ] where
v' = maximum $ filter (`C.withinRange` C.withinVersion v) $ knownGhcVersions
Nothing -> []
item TravisJob
{ tjCompiler = gvs
, tjOS = if osx then "osx" else "linux"
, tjEnv = case gv of
GHC v -> M.lookup v cfgEnv
_ -> Nothing
, tjAddons = TravisAddons
{ taApt = TravisApt
{ taPackages = gvs : ("cabal-install-" ++ cvs) : ghcjsPackages ++ S.toList cfgApt
, taSources = hvrppa : ghcjsAptSources
}
, taPostgres = Nothing
, taGoogleChrome = False
}
}
for_ (reverse $ S.toList versions) $ tellJob False
for_ (reverse $ S.toList osxVersions) $ tellJob True . GHC
, tmAllowFailures =
[ TravisAllowFailure $ dispGhcVersion compiler
| compiler <- toList versions
, previewGHC cfgHeadHackage compiler || maybeGHC False (`C.withinRange` cfgAllowFailures) compiler
]
}
, travisBeforeCache = beforeCache
, travisBeforeInstall = beforeInstall
, travisInstall = install
, travisScript = script
}
where
pkgs = prjPackages prj
uris = prjUriPackages prj
projectName = fromMaybe (pkgName $ Prelude.head pkgs) cfgProjectName
justIf True x = Just x
justIf False _ = Nothing
foldedSh label = foldedSh' label ""
anyGHCJS = any isGHCJS versions
foldedSh' :: Fold -> String -> String -> Set Fold -> ShM () -> ShM ()
foldedSh' label sfx plabel labels block
| label `S.notMember` labels = commentedBlock plabel block
| otherwise = case runSh block of
Left err -> throwErr err
Right shs
| all isComment shs -> pure ()
| otherwise -> ShM $ \shs1 -> Right $
( shs1
. (Comment plabel :)
. (Sh ("echo '" ++ plabel ++ "' && echo -en 'travis_fold:start:" ++ label' ++ "\\\\r'") :)
. (shs ++)
. (Sh ("echo -en 'travis_fold:end:" ++ label' ++ "\\\\r'") :)
, ()
)
where
label' | null sfx = showFold label
| otherwise = showFold label ++ "-" ++ sfx
doctestEnabled = any (maybeGHC False (`C.withinRange` cfgDoctestEnabled cfgDoctest)) versions
hasTests :: CompilerRange
hasTests = RangePoints $ S.unions
[ pkgJobs
| Pkg{pkgGpd,pkgJobs} <- pkgs
, not $ null $ C.condTestSuites pkgGpd
]
hasLibrary = any (\Pkg{pkgGpd} -> isJust $ C.condLibrary pkgGpd) pkgs
headGhcVers :: Set CompilerVersion
headGhcVers = S.filter (previewGHC cfgHeadHackage) versions
cabal :: String -> String
cabal cmd = "${CABAL} " ++ cmd
cabalTW :: String -> String
cabalTW cmd = "travis_wait 40 ${CABAL} " ++ cmd
forJob :: CompilerRange -> String -> Maybe String
forJob vr cmd
| all (`compilerWithinRange` vr) versions = Just cmd
| not $ any (`compilerWithinRange` vr) versions = Nothing
| otherwise = Just $ unwords
[ "if"
, compilerVersionPredicate versions vr
, "; then"
, cmd
, "; fi"
]
shForJob :: CompilerRange -> String -> ShM ()
shForJob vr cmd = maybe (pure ()) sh (forJob vr cmd)
generateCabalProjectFields :: Bool -> [C.PrettyField ()]
generateCabalProjectFields dist = buildList $ do
for_ uris $ \uri ->
item $ C.PrettyField () "packages" $ PP.text $ uriToString id uri ""
case cfgCopyFields of
CopyFieldsNone -> pure ()
CopyFieldsSome -> copyFieldsSome
CopyFieldsAll -> copyFieldsSome *> traverse_ item (prjOtherFields prj)
unless (null cfgLocalGhcOptions) $ for_ pkgs $ \Pkg{pkgName} -> do
let s = unwords $ map (show . C.showToken) cfgLocalGhcOptions
item $ C.PrettySection () "package" [PP.text pkgName] $ buildList $
item $ C.PrettyField () "ghc-options" $ PP.text s
traverse_ item cfgRawProject
copyFieldsSome :: ListBuilder (C.PrettyField ()) ()
copyFieldsSome = do
for_ (prjConstraints prj) $ \xs -> do
let s = concat (lines xs)
item $ C.PrettyField () "constraints" $ PP.text s
for_ (prjAllowNewer prj) $ \xs -> do
let s = concat (lines xs)
item $ C.PrettyField () "allow-newer" $ PP.text s
when (prjReorderGoals prj) $
item $ C.PrettyField () "reorder-goals" $ PP.text "True"
for_ (prjMaxBackjumps prj) $ \bj ->
item $ C.PrettyField () "max-backjumps" $ PP.text $ show bj
case prjOptimization prj of
OptimizationOn -> return ()
OptimizationOff -> item $ C.PrettyField () "optimization" $ PP.text "False"
OptimizationLevel l -> item $ C.PrettyField () "optimization" $ PP.text $ show l
for_ (prjSourceRepos prj) $ \repo ->
item $ C.PrettySection () "source-repository-package" [] $
C.prettyFieldGrammar C.cabalSpecLatest sourceRepositoryPackageGrammar (srpHoist toList repo)
generateCabalProject :: Bool -> ShM ()
generateCabalProject dist = do
comment "Generate cabal.project"
sh "rm -rf cabal.project cabal.project.local cabal.project.freeze"
sh "touch cabal.project"
sh $ unlines
[ cmd
| pkg <- pkgs
, let p | dist = pkgNameDirVariable (pkgName pkg)
| otherwise = pkgDir pkg
, cmd <- toList $ forJob (RangePoints $ pkgJobs pkg) $
"echo \"packages: " ++ p ++ "\" >> cabal.project"
]
case cfgErrorMissingMethods of
PackageScopeNone -> pure ()
PackageScopeLocal -> for_ pkgs $ \Pkg{pkgName,pkgJobs} -> do
shForJob (Range (C.orLaterVersion (C.mkVersion [8,2])) /\ RangePoints pkgJobs) $
"echo 'package " ++ pkgName ++ "' >> cabal.project"
shForJob (Range (C.orLaterVersion (C.mkVersion [8,2])) /\ RangePoints pkgJobs) $
"echo ' ghc-options: -Werror=missing-methods' >> cabal.project"
PackageScopeAll -> do
sh "echo 'package *' >> cabal.project"
sh "echo ' ghc-options: -Werror=missing-methods' >> cabal.project"
cat "cabal.project" $ lines $ C.showFields' (const []) 2 $ generateCabalProjectFields dist
case normaliseInstalled cfgInstalled of
InstalledDiff pns -> sh $ unwords
[ "for pkg in $($HCPKG list --simple-output); do"
, "echo $pkg"
, "| sed 's/-[^-]*$//'"
, "| (grep -vE -- " ++ re ++ " || true)"
, "| sed 's/^/constraints: /'"
, "| sed 's/$/ installed/'"
, ">> cabal.project.local; done"
]
where
pns' = S.map C.unPackageName pns `S.union` foldMap (S.singleton . pkgName) pkgs
re = "'^(" ++ intercalate "|" (S.toList pns') ++ ")$'"
InstalledOnly pns | not (null pns') -> sh' [2043] $ unwords
[ "for pkg in " ++ unwords (S.toList pns') ++ "; do"
, "echo \"constraints: $pkg installed\""
, ">> cabal.project.local; done"
]
where
pns' = S.map C.unPackageName pns `S.difference` foldMap (S.singleton . pkgName) pkgs
_ -> pure ()
sh "cat cabal.project || true"
sh "cat cabal.project.local || true"
withHaddock :: String
withHaddock = "--with-haddock $HADDOCK"
pkgNameDirVariable' :: String -> String
pkgNameDirVariable' n = "PKGDIR_" ++ map f n where
f '-' = '_'
f c = c
pkgNameDirVariable :: String -> String
pkgNameDirVariable n = "${PKGDIR_" ++ map f n ++ "}" where
f '-' = '_'
f c = c
data Quotes = Single | Double
escape :: Quotes -> String -> String
escape Single xs = "'" ++ concatMap f xs ++ "'" where
f '\0' = ""
f '\'' = "'\"'\"'"
f x = [x]
escape Double xs = show xs
catCmd :: Quotes -> FilePath -> [String] -> String
catCmd q fp contents = unlines
[ "echo " ++ escape q l ++ replicate (maxLength - length l) ' ' ++ " >> " ++ fp
| l <- contents
]
where
maxLength = foldl' (\a l -> max a (length l)) 0 contents
cat :: FilePath -> [String] -> ShM ()
cat fp contents = sh $ catCmd Double fp contents